{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Avro.Internal.Get
where
import qualified Codec.Compression.Zlib as Z
import Control.Monad (replicateM, when)
import Data.Binary.Get (Get)
import qualified Data.Binary.Get as G
import Data.Binary.IEEE754 as IEEE
import Data.Bits
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BC
import Data.Int
import qualified Data.Map as Map
import Data.Maybe
import Data.Monoid ((<>))
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Vector as V
import Prelude as P
import Data.Avro.Internal.DecodeRaw
getBoolean :: Get Bool
getBoolean =
do w <- G.getWord8
return $! (w == 0x01)
getInt :: Get Int32
getInt = getZigZag
getLong :: Get Int64
getLong = getZigZag
getZigZag :: (Bits i, Integral i, DecodeRaw i) => Get i
getZigZag = decodeRaw
getBytes :: Get ByteString
getBytes = getLong >>= (G.getByteString . fromIntegral)
getBytesLazy :: Get BL.ByteString
getBytesLazy = getLong >>= (G.getLazyByteString . fromIntegral)
getString :: Get Text
getString = do
bytes <- getBytes
case Text.decodeUtf8' bytes of
Left unicodeExc -> fail (show unicodeExc)
Right text -> return text
getFloat :: Get Float
getFloat = IEEE.wordToFloat <$> G.getWord32le
getDouble :: Get Double
getDouble = IEEE.wordToDouble <$> G.getWord64le
decodeBlocks :: Get a -> Get [a]
decodeBlocks element = do
count <- getLong
if | count == 0 -> return []
| count < 0 -> do
_bytes <- getLong
items <- replicateM (fromIntegral $ abs count) element'
rest <- decodeBlocks element
pure $ items <> rest
| otherwise -> do
items <- replicateM (fromIntegral count) element'
rest <- decodeBlocks element
pure $ items <> rest
where element' = do
!x <- element
pure x
sFromIntegral :: forall a b m. (Monad m, Bounded a, Bounded b, Integral a, Integral b) => a -> m b
sFromIntegral a
| aI > fromIntegral (maxBound :: b) ||
aI < fromIntegral (minBound :: b) = error "Integral overflow."
| otherwise = return (fromIntegral a)
where aI = fromIntegral a :: Integer