{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module DataFrame.IO.Parquet.Thrift where
import Control.Monad
import Data.Bits
import qualified Data.ByteString as BS
import Data.Char
import Data.IORef
import Data.Int
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Text as T
import Data.Word
import DataFrame.IO.Parquet.Binary
import DataFrame.IO.Parquet.Types
data SchemaElement = SchemaElement
{ SchemaElement -> Text
elementName :: T.Text
, SchemaElement -> TType
elementType :: TType
, SchemaElement -> Int32
typeLength :: Int32
, SchemaElement -> Int32
numChildren :: Int32
, SchemaElement -> Int32
fieldId :: Int32
, SchemaElement -> RepetitionType
repetitionType :: RepetitionType
, SchemaElement -> Int32
convertedType :: Int32
, SchemaElement -> Int32
scale :: Int32
, SchemaElement -> Int32
precision :: Int32
, SchemaElement -> LogicalType
logicalType :: LogicalType
}
deriving (Int -> SchemaElement -> ShowS
[SchemaElement] -> ShowS
SchemaElement -> [Char]
(Int -> SchemaElement -> ShowS)
-> (SchemaElement -> [Char])
-> ([SchemaElement] -> ShowS)
-> Show SchemaElement
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SchemaElement -> ShowS
showsPrec :: Int -> SchemaElement -> ShowS
$cshow :: SchemaElement -> [Char]
show :: SchemaElement -> [Char]
$cshowList :: [SchemaElement] -> ShowS
showList :: [SchemaElement] -> ShowS
Show, SchemaElement -> SchemaElement -> Bool
(SchemaElement -> SchemaElement -> Bool)
-> (SchemaElement -> SchemaElement -> Bool) -> Eq SchemaElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaElement -> SchemaElement -> Bool
== :: SchemaElement -> SchemaElement -> Bool
$c/= :: SchemaElement -> SchemaElement -> Bool
/= :: SchemaElement -> SchemaElement -> Bool
Eq)
data KeyValue = KeyValue
{ KeyValue -> [Char]
key :: String
, KeyValue -> [Char]
value :: String
}
deriving (Int -> KeyValue -> ShowS
[KeyValue] -> ShowS
KeyValue -> [Char]
(Int -> KeyValue -> ShowS)
-> (KeyValue -> [Char]) -> ([KeyValue] -> ShowS) -> Show KeyValue
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyValue -> ShowS
showsPrec :: Int -> KeyValue -> ShowS
$cshow :: KeyValue -> [Char]
show :: KeyValue -> [Char]
$cshowList :: [KeyValue] -> ShowS
showList :: [KeyValue] -> ShowS
Show, KeyValue -> KeyValue -> Bool
(KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool) -> Eq KeyValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyValue -> KeyValue -> Bool
== :: KeyValue -> KeyValue -> Bool
$c/= :: KeyValue -> KeyValue -> Bool
/= :: KeyValue -> KeyValue -> Bool
Eq)
data FileMetadata = FileMetaData
{ FileMetadata -> Int32
version :: Int32
, FileMetadata -> [SchemaElement]
schema :: [SchemaElement]
, FileMetadata -> Integer
numRows :: Integer
, FileMetadata -> [RowGroup]
rowGroups :: [RowGroup]
, FileMetadata -> [KeyValue]
keyValueMetadata :: [KeyValue]
, FileMetadata -> Maybe [Char]
createdBy :: Maybe String
, FileMetadata -> [ColumnOrder]
columnOrders :: [ColumnOrder]
, FileMetadata -> EncryptionAlgorithm
encryptionAlgorithm :: EncryptionAlgorithm
, :: [Word8]
}
deriving (Int -> FileMetadata -> ShowS
[FileMetadata] -> ShowS
FileMetadata -> [Char]
(Int -> FileMetadata -> ShowS)
-> (FileMetadata -> [Char])
-> ([FileMetadata] -> ShowS)
-> Show FileMetadata
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileMetadata -> ShowS
showsPrec :: Int -> FileMetadata -> ShowS
$cshow :: FileMetadata -> [Char]
show :: FileMetadata -> [Char]
$cshowList :: [FileMetadata] -> ShowS
showList :: [FileMetadata] -> ShowS
Show, FileMetadata -> FileMetadata -> Bool
(FileMetadata -> FileMetadata -> Bool)
-> (FileMetadata -> FileMetadata -> Bool) -> Eq FileMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileMetadata -> FileMetadata -> Bool
== :: FileMetadata -> FileMetadata -> Bool
$c/= :: FileMetadata -> FileMetadata -> Bool
/= :: FileMetadata -> FileMetadata -> Bool
Eq)
data TType
= STOP
| BOOL
| BYTE
| I16
| I32
| I64
| DOUBLE
| STRING
| LIST
| SET
| MAP
| STRUCT
| UUID
deriving (Int -> TType -> ShowS
[TType] -> ShowS
TType -> [Char]
(Int -> TType -> ShowS)
-> (TType -> [Char]) -> ([TType] -> ShowS) -> Show TType
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TType -> ShowS
showsPrec :: Int -> TType -> ShowS
$cshow :: TType -> [Char]
show :: TType -> [Char]
$cshowList :: [TType] -> ShowS
showList :: [TType] -> ShowS
Show, TType -> TType -> Bool
(TType -> TType -> Bool) -> (TType -> TType -> Bool) -> Eq TType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TType -> TType -> Bool
== :: TType -> TType -> Bool
$c/= :: TType -> TType -> Bool
/= :: TType -> TType -> Bool
Eq)
defaultMetadata :: FileMetadata
defaultMetadata :: FileMetadata
defaultMetadata =
FileMetaData
{ version :: Int32
version = Int32
0
, schema :: [SchemaElement]
schema = []
, numRows :: Integer
numRows = Integer
0
, rowGroups :: [RowGroup]
rowGroups = []
, keyValueMetadata :: [KeyValue]
keyValueMetadata = []
, createdBy :: Maybe [Char]
createdBy = Maybe [Char]
forall a. Maybe a
Nothing
, columnOrders :: [ColumnOrder]
columnOrders = []
, encryptionAlgorithm :: EncryptionAlgorithm
encryptionAlgorithm = EncryptionAlgorithm
ENCRYPTION_ALGORITHM_UNKNOWN
, footerSigningKeyMetadata :: [Word8]
footerSigningKeyMetadata = []
}
data ColumnMetaData = ColumnMetaData
{ ColumnMetaData -> ParquetType
columnType :: ParquetType
, ColumnMetaData -> [ParquetEncoding]
columnEncodings :: [ParquetEncoding]
, ColumnMetaData -> [[Char]]
columnPathInSchema :: [String]
, ColumnMetaData -> CompressionCodec
columnCodec :: CompressionCodec
, ColumnMetaData -> Int64
columnNumValues :: Int64
, ColumnMetaData -> Int64
columnTotalUncompressedSize :: Int64
, ColumnMetaData -> Int64
columnTotalCompressedSize :: Int64
, ColumnMetaData -> [KeyValue]
columnKeyValueMetadata :: [KeyValue]
, ColumnMetaData -> Int64
columnDataPageOffset :: Int64
, ColumnMetaData -> Int64
columnIndexPageOffset :: Int64
, ColumnMetaData -> Int64
columnDictionaryPageOffset :: Int64
, ColumnMetaData -> ColumnStatistics
columnStatistics :: ColumnStatistics
, ColumnMetaData -> [PageEncodingStats]
columnEncodingStats :: [PageEncodingStats]
, ColumnMetaData -> Int64
bloomFilterOffset :: Int64
, ColumnMetaData -> Int32
bloomFilterLength :: Int32
, ColumnMetaData -> SizeStatistics
columnSizeStatistics :: SizeStatistics
, ColumnMetaData -> GeospatialStatistics
columnGeospatialStatistics :: GeospatialStatistics
}
deriving (Int -> ColumnMetaData -> ShowS
[ColumnMetaData] -> ShowS
ColumnMetaData -> [Char]
(Int -> ColumnMetaData -> ShowS)
-> (ColumnMetaData -> [Char])
-> ([ColumnMetaData] -> ShowS)
-> Show ColumnMetaData
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnMetaData -> ShowS
showsPrec :: Int -> ColumnMetaData -> ShowS
$cshow :: ColumnMetaData -> [Char]
show :: ColumnMetaData -> [Char]
$cshowList :: [ColumnMetaData] -> ShowS
showList :: [ColumnMetaData] -> ShowS
Show, ColumnMetaData -> ColumnMetaData -> Bool
(ColumnMetaData -> ColumnMetaData -> Bool)
-> (ColumnMetaData -> ColumnMetaData -> Bool) -> Eq ColumnMetaData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnMetaData -> ColumnMetaData -> Bool
== :: ColumnMetaData -> ColumnMetaData -> Bool
$c/= :: ColumnMetaData -> ColumnMetaData -> Bool
/= :: ColumnMetaData -> ColumnMetaData -> Bool
Eq)
data ColumnChunk = ColumnChunk
{ ColumnChunk -> [Char]
columnChunkFilePath :: String
, ColumnChunk -> Int64
columnChunkMetadataFileOffset :: Int64
, ColumnChunk -> ColumnMetaData
columnMetaData :: ColumnMetaData
, ColumnChunk -> Int64
columnChunkOffsetIndexOffset :: Int64
, ColumnChunk -> Int32
columnChunkOffsetIndexLength :: Int32
, ColumnChunk -> Int64
columnChunkColumnIndexOffset :: Int64
, ColumnChunk -> Int32
columnChunkColumnIndexLength :: Int32
, ColumnChunk -> ColumnCryptoMetadata
cryptoMetadata :: ColumnCryptoMetadata
, ColumnChunk -> [Word8]
encryptedColumnMetadata :: [Word8]
}
deriving (Int -> ColumnChunk -> ShowS
[ColumnChunk] -> ShowS
ColumnChunk -> [Char]
(Int -> ColumnChunk -> ShowS)
-> (ColumnChunk -> [Char])
-> ([ColumnChunk] -> ShowS)
-> Show ColumnChunk
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnChunk -> ShowS
showsPrec :: Int -> ColumnChunk -> ShowS
$cshow :: ColumnChunk -> [Char]
show :: ColumnChunk -> [Char]
$cshowList :: [ColumnChunk] -> ShowS
showList :: [ColumnChunk] -> ShowS
Show, ColumnChunk -> ColumnChunk -> Bool
(ColumnChunk -> ColumnChunk -> Bool)
-> (ColumnChunk -> ColumnChunk -> Bool) -> Eq ColumnChunk
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnChunk -> ColumnChunk -> Bool
== :: ColumnChunk -> ColumnChunk -> Bool
$c/= :: ColumnChunk -> ColumnChunk -> Bool
/= :: ColumnChunk -> ColumnChunk -> Bool
Eq)
data RowGroup = RowGroup
{ RowGroup -> [ColumnChunk]
rowGroupColumns :: [ColumnChunk]
, RowGroup -> Int64
totalByteSize :: Int64
, RowGroup -> Int64
rowGroupNumRows :: Int64
, RowGroup -> [SortingColumn]
rowGroupSortingColumns :: [SortingColumn]
, RowGroup -> Int64
fileOffset :: Int64
, RowGroup -> Int64
totalCompressedSize :: Int64
, RowGroup -> Int16
ordinal :: Int16
}
deriving (Int -> RowGroup -> ShowS
[RowGroup] -> ShowS
RowGroup -> [Char]
(Int -> RowGroup -> ShowS)
-> (RowGroup -> [Char]) -> ([RowGroup] -> ShowS) -> Show RowGroup
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RowGroup -> ShowS
showsPrec :: Int -> RowGroup -> ShowS
$cshow :: RowGroup -> [Char]
show :: RowGroup -> [Char]
$cshowList :: [RowGroup] -> ShowS
showList :: [RowGroup] -> ShowS
Show, RowGroup -> RowGroup -> Bool
(RowGroup -> RowGroup -> Bool)
-> (RowGroup -> RowGroup -> Bool) -> Eq RowGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RowGroup -> RowGroup -> Bool
== :: RowGroup -> RowGroup -> Bool
$c/= :: RowGroup -> RowGroup -> Bool
/= :: RowGroup -> RowGroup -> Bool
Eq)
defaultSchemaElement :: SchemaElement
defaultSchemaElement :: SchemaElement
defaultSchemaElement =
Text
-> TType
-> Int32
-> Int32
-> Int32
-> RepetitionType
-> Int32
-> Int32
-> Int32
-> LogicalType
-> SchemaElement
SchemaElement
Text
""
TType
STOP
Int32
0
Int32
0
(-Int32
1)
RepetitionType
UNKNOWN_REPETITION_TYPE
Int32
0
Int32
0
Int32
0
LogicalType
LOGICAL_TYPE_UNKNOWN
emptyColumnMetadata :: ColumnMetaData
emptyColumnMetadata :: ColumnMetaData
emptyColumnMetadata =
ParquetType
-> [ParquetEncoding]
-> [[Char]]
-> CompressionCodec
-> Int64
-> Int64
-> Int64
-> [KeyValue]
-> Int64
-> Int64
-> Int64
-> ColumnStatistics
-> [PageEncodingStats]
-> Int64
-> Int32
-> SizeStatistics
-> GeospatialStatistics
-> ColumnMetaData
ColumnMetaData
ParquetType
PARQUET_TYPE_UNKNOWN
[]
[]
CompressionCodec
COMPRESSION_CODEC_UNKNOWN
Int64
0
Int64
0
Int64
0
[]
Int64
0
Int64
0
Int64
0
ColumnStatistics
emptyColumnStatistics
[]
Int64
0
Int32
0
SizeStatistics
emptySizeStatistics
GeospatialStatistics
emptyGeospatialStatistics
emptyColumnChunk :: ColumnChunk
emptyColumnChunk :: ColumnChunk
emptyColumnChunk =
[Char]
-> Int64
-> ColumnMetaData
-> Int64
-> Int32
-> Int64
-> Int32
-> ColumnCryptoMetadata
-> [Word8]
-> ColumnChunk
ColumnChunk [Char]
"" Int64
0 ColumnMetaData
emptyColumnMetadata Int64
0 Int32
0 Int64
0 Int32
0 ColumnCryptoMetadata
COLUMN_CRYPTO_METADATA_UNKNOWN []
emptyKeyValue :: KeyValue
emptyKeyValue :: KeyValue
emptyKeyValue = KeyValue{key :: [Char]
key = [Char]
"", value :: [Char]
value = [Char]
""}
emptyRowGroup :: RowGroup
emptyRowGroup :: RowGroup
emptyRowGroup = [ColumnChunk]
-> Int64
-> Int64
-> [SortingColumn]
-> Int64
-> Int64
-> Int16
-> RowGroup
RowGroup [] Int64
0 Int64
0 [] Int64
0 Int64
0 Int16
0
compactBooleanTrue
, compactI32
, compactI64
, compactDouble
, compactBinary
, compactList
, compactStruct ::
Word8
compactBooleanTrue :: Word8
compactBooleanTrue = Word8
0x01
compactI32 :: Word8
compactI32 = Word8
0x05
compactI64 :: Word8
compactI64 = Word8
0x06
compactDouble :: Word8
compactDouble = Word8
0x07
compactBinary :: Word8
compactBinary = Word8
0x08
compactList :: Word8
compactList = Word8
0x09
compactStruct :: Word8
compactStruct = Word8
0x0C
toTType :: Word8 -> TType
toTType :: Word8 -> TType
toTType Word8
t =
TType -> Maybe TType -> TType
forall a. a -> Maybe a -> a
fromMaybe TType
STOP (Maybe TType -> TType) -> Maybe TType -> TType
forall a b. (a -> b) -> a -> b
$
Word8 -> Map Word8 TType -> Maybe TType
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) (Map Word8 TType -> Maybe TType) -> Map Word8 TType -> Maybe TType
forall a b. (a -> b) -> a -> b
$
[(Word8, TType)] -> Map Word8 TType
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Word8
compactBooleanTrue, TType
BOOL)
, (Word8
compactI32, TType
I32)
, (Word8
compactI64, TType
I64)
, (Word8
compactDouble, TType
DOUBLE)
, (Word8
compactBinary, TType
STRING)
, (Word8
compactList, TType
LIST)
, (Word8
compactStruct, TType
STRUCT)
]
readField ::
BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField :: ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Word8
t <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
if Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
then Maybe (TType, Int16) -> IO (Maybe (TType, Int16))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (TType, Int16)
forall a. Maybe a
Nothing
else do
let modifier :: Int16
modifier = Word8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0xf0) Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) :: Int16
Int16
identifier <-
if Int16
modifier Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
0
then forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int16 ByteString
buf IORef Int
pos
else Int16 -> IO Int16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int16
lastFieldId Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
+ Int16
modifier)
let elemType :: TType
elemType = Word8 -> TType
toTType (Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
Maybe (TType, Int16) -> IO (Maybe (TType, Int16))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (TType, Int16) -> IO (Maybe (TType, Int16)))
-> Maybe (TType, Int16) -> IO (Maybe (TType, Int16))
forall a b. (a -> b) -> a -> b
$ (TType, Int16) -> Maybe (TType, Int16)
forall a. a -> Maybe a
Just (TType
elemType, Int16
identifier)
skipToStructEnd :: BS.ByteString -> IORef Int -> IO ()
skipToStructEnd :: ByteString -> IORef Int -> IO ()
skipToStructEnd ByteString
buf IORef Int
pos = do
Word8
t <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
if Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
let modifier :: Int16
modifier = Word8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0xf0) Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) :: Int16
Int16
identifier <-
if Int16
modifier Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
0
then forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int16 ByteString
buf IORef Int
pos
else Int16 -> IO Int16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
0
let elemType :: TType
elemType = Word8 -> TType
toTType (Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
TType -> ByteString -> IORef Int -> IO ()
skipFieldData TType
elemType ByteString
buf IORef Int
pos
ByteString -> IORef Int -> IO ()
skipToStructEnd ByteString
buf IORef Int
pos
skipFieldData :: TType -> BS.ByteString -> IORef Int -> IO ()
skipFieldData :: TType -> ByteString -> IORef Int -> IO ()
skipFieldData TType
fieldType ByteString
buf IORef Int
pos = case TType
fieldType of
TType
BOOL -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
TType
I32 -> IO Int32 -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int32 ByteString
buf IORef Int
pos)
TType
I64 -> IO Int64 -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos)
TType
DOUBLE -> IO Int64 -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos)
TType
STRING -> IO [Word8] -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos)
TType
LIST -> ByteString -> IORef Int -> IO ()
skipList ByteString
buf IORef Int
pos
TType
STRUCT -> ByteString -> IORef Int -> IO ()
skipToStructEnd ByteString
buf IORef Int
pos
TType
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
skipList :: BS.ByteString -> IORef Int -> IO ()
skipList :: ByteString -> IORef Int -> IO ()
skipList ByteString
buf IORef Int
pos = do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let elemType :: TType
elemType = Word8 -> TType
toTType Word8
sizeAndType
Int -> IO () -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
sizeOnly (TType -> ByteString -> IORef Int -> IO ()
skipFieldData TType
elemType ByteString
buf IORef Int
pos)
readMetadata :: BS.ByteString -> Int -> IO FileMetadata
readMetadata :: ByteString -> Int -> IO FileMetadata
readMetadata ByteString
contents Int
size = do
let metadataStartPos :: Int
metadataStartPos = ByteString -> Int
BS.length ByteString
contents Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
footerSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
size
let metadataBytes :: ByteString
metadataBytes =
[Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$
(Int -> Word8) -> [Int] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map (HasCallStack => ByteString -> Int -> Word8
ByteString -> Int -> Word8
BS.index ByteString
contents) [Int
metadataStartPos .. (Int
metadataStartPos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)]
let lastFieldId :: Int16
lastFieldId = Int16
0
let fieldStack :: [a]
fieldStack = []
IORef Int
bufferPos <- Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef (Int
0 :: Int)
FileMetadata
metadata <-
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData FileMetadata
defaultMetadata ByteString
metadataBytes IORef Int
bufferPos Int16
lastFieldId [Int16]
forall a. [a]
fieldStack
FileMetadata -> IO FileMetadata
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FileMetadata
metadata
readFileMetaData ::
FileMetadata ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO FileMetadata
readFileMetaData :: FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData FileMetadata
metadata ByteString
metaDataBuf IORef Int
bufferPos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
metaDataBuf IORef Int
bufferPos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> FileMetadata -> IO FileMetadata
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FileMetadata
metadata
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Int32
version <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int32 ByteString
metaDataBuf IORef Int
bufferPos
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{version = version})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
2 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
bufferPos ByteString
metaDataBuf
Int
listSize <-
if (Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
15
then forall a. Integral a => ByteString -> IORef Int -> IO a
readVarIntFromBuffer @Int ByteString
metaDataBuf IORef Int
bufferPos
else Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[SchemaElement]
schemaElements <-
Int -> IO SchemaElement -> IO [SchemaElement]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM
Int
listSize
(SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement SchemaElement
defaultSchemaElement ByteString
metaDataBuf IORef Int
bufferPos Int16
0 [])
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{schema = schemaElements})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
3 -> do
Int64
numRows <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
metaDataBuf IORef Int
bufferPos
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{numRows = fromIntegral numRows})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
4 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
bufferPos ByteString
metaDataBuf
Int
listSize <-
if (Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
15
then forall a. Integral a => ByteString -> IORef Int -> IO a
readVarIntFromBuffer @Int ByteString
metaDataBuf IORef Int
bufferPos
else Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[RowGroup]
rowGroups <-
Int -> IO RowGroup -> IO [RowGroup]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
listSize (RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup RowGroup
emptyRowGroup ByteString
metaDataBuf IORef Int
bufferPos Int16
0 [])
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{rowGroups = rowGroups})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
5 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
bufferPos ByteString
metaDataBuf
Int
listSize <-
if (Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
15
then forall a. Integral a => ByteString -> IORef Int -> IO a
readVarIntFromBuffer @Int ByteString
metaDataBuf IORef Int
bufferPos
else Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[KeyValue]
keyValueMetadata <-
Int -> IO KeyValue -> IO [KeyValue]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
listSize (KeyValue
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO KeyValue
readKeyValue KeyValue
emptyKeyValue ByteString
metaDataBuf IORef Int
bufferPos Int16
0 [])
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{keyValueMetadata = keyValueMetadata})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
6 -> do
[Char]
createdBy <- ByteString -> IORef Int -> IO [Char]
readString ByteString
metaDataBuf IORef Int
bufferPos
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{createdBy = Just createdBy})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
7 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
bufferPos ByteString
metaDataBuf
Int
listSize <-
if (Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
15
then forall a. Integral a => ByteString -> IORef Int -> IO a
readVarIntFromBuffer @Int ByteString
metaDataBuf IORef Int
bufferPos
else Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[ColumnOrder]
columnOrders <- Int -> IO ColumnOrder -> IO [ColumnOrder]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
listSize (ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readColumnOrder ByteString
metaDataBuf IORef Int
bufferPos Int16
0 [])
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{columnOrders = columnOrders})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
8 -> do
EncryptionAlgorithm
encryptionAlgorithm <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO EncryptionAlgorithm
readEncryptionAlgorithm ByteString
metaDataBuf IORef Int
bufferPos Int16
0 []
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{encryptionAlgorithm = encryptionAlgorithm})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
9 -> do
[Word8]
footerSigningKeyMetadata <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
metaDataBuf IORef Int
bufferPos
FileMetadata
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO FileMetadata
readFileMetaData
(FileMetadata
metadata{footerSigningKeyMetadata = footerSigningKeyMetadata})
ByteString
metaDataBuf
IORef Int
bufferPos
Int16
identifier
[Int16]
fieldStack
Int16
n -> FileMetadata -> IO FileMetadata
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileMetadata -> IO FileMetadata)
-> FileMetadata -> IO FileMetadata
forall a b. (a -> b) -> a -> b
$ [Char] -> FileMetadata
forall a. HasCallStack => [Char] -> a
error ([Char] -> FileMetadata) -> [Char] -> FileMetadata
forall a b. (a -> b) -> a -> b
$ [Char]
"UNIMPLEMENTED " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int16 -> [Char]
forall a. Show a => a -> [Char]
show Int16
n
readSchemaElement ::
SchemaElement ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO SchemaElement
readSchemaElement :: SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement SchemaElement
schemaElement ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> SchemaElement -> IO SchemaElement
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SchemaElement
schemaElement
Just (TType
STOP, Int16
_) -> SchemaElement -> IO SchemaElement
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SchemaElement
schemaElement
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
TType
schemaElemType <- Int32 -> TType
toIntegralType (Int32 -> TType) -> IO Int32 -> IO TType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{elementType = schemaElemType})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
2 -> do
Int32
typeLength <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{typeLength = typeLength})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
3 -> do
Int32
fieldRepetitionType <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{repetitionType = repetitionTypeFromInt fieldRepetitionType})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
4 -> do
Int
nameSize <- forall a. Integral a => ByteString -> IORef Int -> IO a
readVarIntFromBuffer @Int ByteString
buf IORef Int
pos
if Int
nameSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
then SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement SchemaElement
schemaElement ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
else do
[Word8]
contents <- Int -> IO Word8 -> IO [Word8]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
nameSize (IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf)
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{elementName = T.pack (map (chr . fromIntegral) contents)})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
5 -> do
Int32
numChildren <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{numChildren = numChildren})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
6 -> do
Int32
convertedType <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{convertedType = convertedType})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
7 -> do
Int32
scale <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement (SchemaElement
schemaElement{scale = scale}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
8 -> do
Int32
precision <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{precision = precision})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
9 -> do
Int32
fieldId <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{fieldId = fieldId})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
10 -> do
LogicalType
logicalType <- ByteString -> IORef Int -> Int16 -> [Int16] -> IO LogicalType
readLogicalType ByteString
buf IORef Int
pos Int16
0 []
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement
(SchemaElement
schemaElement{logicalType = logicalType})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
_ -> do
TType -> ByteString -> IORef Int -> IO ()
skipFieldData TType
elemType ByteString
buf IORef Int
pos
SchemaElement
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SchemaElement
readSchemaElement SchemaElement
schemaElement ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
readRowGroup ::
RowGroup -> BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup :: RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup RowGroup
r ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> RowGroup -> IO RowGroup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RowGroup
r
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[ColumnChunk]
columnChunks <-
Int -> IO ColumnChunk -> IO [ColumnChunk]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk ColumnChunk
emptyColumnChunk ByteString
buf IORef Int
pos Int16
0 [])
RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup (RowGroup
r{rowGroupColumns = columnChunks}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
2 -> do
Int64
totalBytes <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup (RowGroup
r{totalByteSize = totalBytes}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
3 -> do
Int64
nRows <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup (RowGroup
r{rowGroupNumRows = nRows}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
4 -> RowGroup -> IO RowGroup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RowGroup
r
Int16
5 -> do
Int64
offset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup (RowGroup
r{fileOffset = offset}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
6 -> do
Int64
compressedSize <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup
(RowGroup
r{totalCompressedSize = compressedSize})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
7 -> do
Int16
ordinal <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int16 ByteString
buf IORef Int
pos
RowGroup
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO RowGroup
readRowGroup (RowGroup
r{ordinal = ordinal}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
_ -> [Char] -> IO RowGroup
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO RowGroup) -> [Char] -> IO RowGroup
forall a b. (a -> b) -> a -> b
$ [Char]
"Unknown row group field: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int16 -> [Char]
forall a. Show a => a -> [Char]
show Int16
identifier
readColumnChunk ::
ColumnChunk -> BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk :: ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk ColumnChunk
c ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> ColumnChunk -> IO ColumnChunk
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnChunk
c
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Int
stringSize <- forall a. Integral a => ByteString -> IORef Int -> IO a
readVarIntFromBuffer @Int ByteString
buf IORef Int
pos
[Char]
contents <-
(Word8 -> Char) -> [Word8] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ([Word8] -> [Char]) -> IO [Word8] -> IO [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> IO Word8 -> IO [Word8]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
stringSize (IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf)
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnChunkFilePath = contents})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
2 -> do
Int64
columnChunkMetadataFileOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnChunkMetadataFileOffset = columnChunkMetadataFileOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
3 -> do
ColumnMetaData
columnMetadata <- ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata ColumnMetaData
emptyColumnMetadata ByteString
buf IORef Int
pos Int16
0 []
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnMetaData = columnMetadata})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
4 -> do
Int64
columnOffsetIndexOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnChunkOffsetIndexOffset = columnOffsetIndexOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
5 -> do
Int32
columnOffsetIndexLength <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnChunkOffsetIndexLength = columnOffsetIndexLength})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
6 -> do
Int64
columnChunkColumnIndexOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnChunkColumnIndexOffset = columnChunkColumnIndexOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
7 -> do
Int32
columnChunkColumnIndexLength <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
ColumnChunk
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnChunk
readColumnChunk
(ColumnChunk
c{columnChunkColumnIndexLength = columnChunkColumnIndexLength})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
_ -> ColumnChunk -> IO ColumnChunk
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnChunk
c
readColumnMetadata ::
ColumnMetaData ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO ColumnMetaData
readColumnMetadata :: ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata ColumnMetaData
cm ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> ColumnMetaData -> IO ColumnMetaData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnMetaData
cm
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
ParquetType
cType <- Int32 -> ParquetType
parquetTypeFromInt (Int32 -> ParquetType) -> IO Int32 -> IO ParquetType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata (ColumnMetaData
cm{columnType = cType}) ByteString
buf IORef Int
pos Int16
identifier []
Int16
2 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[ParquetEncoding]
encodings <- Int -> IO ParquetEncoding -> IO [ParquetEncoding]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (ByteString -> IORef Int -> Int16 -> [Int16] -> IO ParquetEncoding
readParquetEncoding ByteString
buf IORef Int
pos Int16
0 [])
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnEncodings = encodings})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
3 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[[Char]]
paths <- Int -> IO [Char] -> IO [[Char]]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (ByteString -> IORef Int -> IO [Char]
readString ByteString
buf IORef Int
pos)
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnPathInSchema = paths})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
4 -> do
CompressionCodec
cType <- Int32 -> CompressionCodec
compressionCodecFromInt (Int32 -> CompressionCodec) -> IO Int32 -> IO CompressionCodec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata (ColumnMetaData
cm{columnCodec = cType}) ByteString
buf IORef Int
pos Int16
identifier []
Int16
5 -> do
Int64
numValues <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata (ColumnMetaData
cm{columnNumValues = numValues}) ByteString
buf IORef Int
pos Int16
identifier []
Int16
6 -> do
Int64
columnTotalUncompressedSize <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnTotalUncompressedSize = columnTotalUncompressedSize})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
7 -> do
Int64
columnTotalCompressedSize <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnTotalCompressedSize = columnTotalCompressedSize})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
8 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[KeyValue]
columnKeyValueMetadata <-
Int -> IO KeyValue -> IO [KeyValue]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (KeyValue
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO KeyValue
readKeyValue KeyValue
emptyKeyValue ByteString
buf IORef Int
pos Int16
0 [])
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnKeyValueMetadata = columnKeyValueMetadata})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
9 -> do
Int64
columnDataPageOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnDataPageOffset = columnDataPageOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
10 -> do
Int64
columnIndexPageOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnIndexPageOffset = columnIndexPageOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
11 -> do
Int64
columnDictionaryPageOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnDictionaryPageOffset = columnDictionaryPageOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
12 -> do
ColumnStatistics
stats <- ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics ColumnStatistics
emptyColumnStatistics ByteString
buf IORef Int
pos Int16
0 []
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata (ColumnMetaData
cm{columnStatistics = stats}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
13 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[PageEncodingStats]
pageEncodingStats <-
Int -> IO PageEncodingStats -> IO [PageEncodingStats]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (PageEncodingStats
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO PageEncodingStats
readPageEncodingStats PageEncodingStats
emptyPageEncodingStats ByteString
buf IORef Int
pos Int16
0 [])
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnEncodingStats = pageEncodingStats})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
14 -> do
Int64
bloomFilterOffset <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{bloomFilterOffset = bloomFilterOffset})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
15 -> do
Int32
bloomFilterLength <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{bloomFilterLength = bloomFilterLength})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
16 -> do
SizeStatistics
stats <- SizeStatistics
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SizeStatistics
readSizeStatistics SizeStatistics
emptySizeStatistics ByteString
buf IORef Int
pos Int16
0 []
ColumnMetaData
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnMetaData
readColumnMetadata
(ColumnMetaData
cm{columnSizeStatistics = stats})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
17 -> ColumnMetaData -> IO ColumnMetaData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ColumnMetaData -> IO ColumnMetaData)
-> ColumnMetaData -> IO ColumnMetaData
forall a b. (a -> b) -> a -> b
$ [Char] -> ColumnMetaData
forall a. HasCallStack => [Char] -> a
error [Char]
"UNIMPLEMENTED"
Int16
_ -> ColumnMetaData -> IO ColumnMetaData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnMetaData
cm
readEncryptionAlgorithm ::
BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO EncryptionAlgorithm
readEncryptionAlgorithm :: ByteString
-> IORef Int -> Int16 -> [Int16] -> IO EncryptionAlgorithm
readEncryptionAlgorithm ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> EncryptionAlgorithm -> IO EncryptionAlgorithm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncryptionAlgorithm
ENCRYPTION_ALGORITHM_UNKNOWN
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmV1
(AesGcmV1{aadPrefix :: [Word8]
aadPrefix = [], aadFileUnique :: [Word8]
aadFileUnique = [], supplyAadPrefix :: Bool
supplyAadPrefix = Bool
False})
ByteString
buf
IORef Int
pos
Int16
0
[]
Int16
2 -> do
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmCtrV1
(AesGcmCtrV1{aadPrefix :: [Word8]
aadPrefix = [], aadFileUnique :: [Word8]
aadFileUnique = [], supplyAadPrefix :: Bool
supplyAadPrefix = Bool
False})
ByteString
buf
IORef Int
pos
Int16
0
[]
Int16
n -> EncryptionAlgorithm -> IO EncryptionAlgorithm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncryptionAlgorithm
ENCRYPTION_ALGORITHM_UNKNOWN
readColumnOrder ::
BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readColumnOrder :: ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readColumnOrder ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> ColumnOrder -> IO ColumnOrder
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnOrder
COLUMN_ORDER_UNKNOWN
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Int -> IO ColumnOrder -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readTypeOrder ByteString
buf IORef Int
pos Int16
0 [])
ColumnOrder -> IO ColumnOrder
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnOrder
TYPE_ORDER
Int16
_ -> ColumnOrder -> IO ColumnOrder
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnOrder
COLUMN_ORDER_UNKNOWN
readAesGcmCtrV1 ::
EncryptionAlgorithm ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO EncryptionAlgorithm
readAesGcmCtrV1 :: EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmCtrV1 v :: EncryptionAlgorithm
v@(AesGcmCtrV1 [Word8]
aadPrefix [Word8]
aadFileUnique Bool
supplyAadPrefix) ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> EncryptionAlgorithm -> IO EncryptionAlgorithm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncryptionAlgorithm
v
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
[Word8]
aadPrefix <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmCtrV1 (EncryptionAlgorithm
v{aadPrefix = aadPrefix}) ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
2 -> do
[Word8]
aadFileUnique <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmCtrV1
(EncryptionAlgorithm
v{aadFileUnique = aadFileUnique})
ByteString
buf
IORef Int
pos
Int16
lastFieldId
[Int16]
fieldStack
Int16
3 -> do
Word8
supplyAadPrefix <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmCtrV1
(EncryptionAlgorithm
v{supplyAadPrefix = supplyAadPrefix == compactBooleanTrue})
ByteString
buf
IORef Int
pos
Int16
lastFieldId
[Int16]
fieldStack
Int16
_ -> EncryptionAlgorithm -> IO EncryptionAlgorithm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncryptionAlgorithm
ENCRYPTION_ALGORITHM_UNKNOWN
readAesGcmCtrV1 EncryptionAlgorithm
_ ByteString
_ IORef Int
_ Int16
_ [Int16]
_ =
[Char] -> IO EncryptionAlgorithm
forall a. HasCallStack => [Char] -> a
error [Char]
"readAesGcmCtrV1 called with non AesGcmCtrV1"
readAesGcmV1 ::
EncryptionAlgorithm ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO EncryptionAlgorithm
readAesGcmV1 :: EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmV1 v :: EncryptionAlgorithm
v@(AesGcmV1 [Word8]
aadPrefix [Word8]
aadFileUnique Bool
supplyAadPrefix) ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> EncryptionAlgorithm -> IO EncryptionAlgorithm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncryptionAlgorithm
v
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
[Word8]
aadPrefix <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmV1 (EncryptionAlgorithm
v{aadPrefix = aadPrefix}) ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
2 -> do
[Word8]
aadFileUnique <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmV1 (EncryptionAlgorithm
v{aadFileUnique = aadFileUnique}) ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
3 -> do
Word8
supplyAadPrefix <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
EncryptionAlgorithm
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO EncryptionAlgorithm
readAesGcmV1
(EncryptionAlgorithm
v{supplyAadPrefix = supplyAadPrefix == compactBooleanTrue})
ByteString
buf
IORef Int
pos
Int16
lastFieldId
[Int16]
fieldStack
Int16
_ -> EncryptionAlgorithm -> IO EncryptionAlgorithm
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncryptionAlgorithm
ENCRYPTION_ALGORITHM_UNKNOWN
readAesGcmV1 EncryptionAlgorithm
_ ByteString
_ IORef Int
_ Int16
_ [Int16]
_ =
[Char] -> IO EncryptionAlgorithm
forall a. HasCallStack => [Char] -> a
error [Char]
"readAesGcmV1 called with non AesGcmV1"
readTypeOrder ::
BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readTypeOrder :: ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readTypeOrder ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> ColumnOrder -> IO ColumnOrder
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnOrder
TYPE_ORDER
Just (TType
elemType, Int16
identifier) ->
if TType
elemType TType -> TType -> Bool
forall a. Eq a => a -> a -> Bool
== TType
STOP
then ColumnOrder -> IO ColumnOrder
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnOrder
TYPE_ORDER
else ByteString -> IORef Int -> Int16 -> [Int16] -> IO ColumnOrder
readTypeOrder ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
readKeyValue ::
KeyValue -> BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO KeyValue
readKeyValue :: KeyValue
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO KeyValue
readKeyValue KeyValue
kv ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> KeyValue -> IO KeyValue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return KeyValue
kv
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
[Char]
k <- ByteString -> IORef Int -> IO [Char]
readString ByteString
buf IORef Int
pos
KeyValue
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO KeyValue
readKeyValue (KeyValue
kv{key = k}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
2 -> do
[Char]
v <- ByteString -> IORef Int -> IO [Char]
readString ByteString
buf IORef Int
pos
KeyValue
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO KeyValue
readKeyValue (KeyValue
kv{value = v}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
_ -> KeyValue -> IO KeyValue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return KeyValue
kv
readPageEncodingStats ::
PageEncodingStats ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO PageEncodingStats
readPageEncodingStats :: PageEncodingStats
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO PageEncodingStats
readPageEncodingStats PageEncodingStats
pes ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> PageEncodingStats -> IO PageEncodingStats
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PageEncodingStats
pes
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
PageType
pType <- Int32 -> PageType
pageTypeFromInt (Int32 -> PageType) -> IO Int32 -> IO PageType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
PageEncodingStats
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO PageEncodingStats
readPageEncodingStats (PageEncodingStats
pes{pageEncodingPageType = pType}) ByteString
buf IORef Int
pos Int16
identifier []
Int16
2 -> do
ParquetEncoding
pEnc <- Int32 -> ParquetEncoding
parquetEncodingFromInt (Int32 -> ParquetEncoding) -> IO Int32 -> IO ParquetEncoding
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
PageEncodingStats
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO PageEncodingStats
readPageEncodingStats (PageEncodingStats
pes{pageEncoding = pEnc}) ByteString
buf IORef Int
pos Int16
identifier []
Int16
3 -> do
Int32
encodedCount <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
PageEncodingStats
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO PageEncodingStats
readPageEncodingStats
(PageEncodingStats
pes{pagesWithEncoding = encodedCount})
ByteString
buf
IORef Int
pos
Int16
identifier
[]
Int16
_ -> PageEncodingStats -> IO PageEncodingStats
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PageEncodingStats
pes
readParquetEncoding ::
BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO ParquetEncoding
readParquetEncoding :: ByteString -> IORef Int -> Int16 -> [Int16] -> IO ParquetEncoding
readParquetEncoding ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = Int32 -> ParquetEncoding
parquetEncodingFromInt (Int32 -> ParquetEncoding) -> IO Int32 -> IO ParquetEncoding
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
readStatistics ::
ColumnStatistics ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO ColumnStatistics
readStatistics :: ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics ColumnStatistics
cs ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> ColumnStatistics -> IO ColumnStatistics
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnStatistics
cs
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
[Word8]
maxInBytes <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics (ColumnStatistics
cs{columnMax = maxInBytes}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
2 -> do
[Word8]
minInBytes <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics (ColumnStatistics
cs{columnMin = minInBytes}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
3 -> do
Int64
nullCount <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics (ColumnStatistics
cs{columnNullCount = nullCount}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
4 -> do
Int64
distinctCount <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics
(ColumnStatistics
cs{columnDistictCount = distinctCount})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
5 -> do
[Word8]
maxInBytes <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics (ColumnStatistics
cs{columnMaxValue = maxInBytes}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
6 -> do
[Word8]
minInBytes <- ByteString -> IORef Int -> IO [Word8]
readByteString ByteString
buf IORef Int
pos
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics (ColumnStatistics
cs{columnMinValue = minInBytes}) ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
7 -> do
Word8
isMaxValueExact <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics
(ColumnStatistics
cs{isColumnMaxValueExact = isMaxValueExact == compactBooleanTrue})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
8 -> do
Word8
isMinValueExact <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
ColumnStatistics
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO ColumnStatistics
readStatistics
(ColumnStatistics
cs{isColumnMinValueExact = isMinValueExact == compactBooleanTrue})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
_ -> ColumnStatistics -> IO ColumnStatistics
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ColumnStatistics
cs
readSizeStatistics ::
SizeStatistics ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO SizeStatistics
readSizeStatistics :: SizeStatistics
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SizeStatistics
readSizeStatistics SizeStatistics
ss ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> SizeStatistics -> IO SizeStatistics
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SizeStatistics
ss
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Int64
unencodedByteArrayDataTypes <- forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos
SizeStatistics
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SizeStatistics
readSizeStatistics
(SizeStatistics
ss{unencodedByteArrayDataTypes = unencodedByteArrayDataTypes})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
2 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[Int64]
repetitionLevelHistogram <-
Int -> IO Int64 -> IO [Int64]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos)
SizeStatistics
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SizeStatistics
readSizeStatistics
(SizeStatistics
ss{repetitionLevelHistogram = repetitionLevelHistogram})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
3 -> do
Word8
sizeAndType <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
let sizeOnly :: Int
sizeOnly = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
sizeAndType Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) :: Int
let _elemType :: TType
_elemType = Word8 -> TType
toTType Word8
sizeAndType
[Int64]
definitionLevelHistogram <-
Int -> IO Int64 -> IO [Int64]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
sizeOnly (forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int64 ByteString
buf IORef Int
pos)
SizeStatistics
-> ByteString -> IORef Int -> Int16 -> [Int16] -> IO SizeStatistics
readSizeStatistics
(SizeStatistics
ss{definitionLevelHistogram = definitionLevelHistogram})
ByteString
buf
IORef Int
pos
Int16
identifier
[Int16]
fieldStack
Int16
_ -> SizeStatistics -> IO SizeStatistics
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SizeStatistics
ss
footerSize :: Int
= Int
8
toIntegralType :: Int32 -> TType
toIntegralType :: Int32 -> TType
toIntegralType Int32
n
| Int32
n Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
1 = TType
I32
| Int32
n Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
2 = TType
I64
| Int32
n Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
4 = TType
DOUBLE
| Int32
n Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
6 = TType
STRING
| Bool
otherwise = TType
STRING
readLogicalType ::
BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO LogicalType
readLogicalType :: ByteString -> IORef Int -> Int16 -> [Int16] -> IO LogicalType
readLogicalType ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Word8
t <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
if Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
then LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
LOGICAL_TYPE_UNKNOWN
else do
let modifier :: Int16
modifier = Word8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0xf0) Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) :: Int16
Int16
identifier <-
if Int16
modifier Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
0
then forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int16 ByteString
buf IORef Int
pos
else Int16 -> IO Int16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int16
lastFieldId Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
+ Int16
modifier)
let _elemType :: TType
_elemType = Word8 -> TType
toTType (Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
case Int16
identifier of
Int16
1 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
STRING_TYPE
Int16
2 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
MAP_TYPE
Int16
3 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
LIST_TYPE
Int16
4 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
ENUM_TYPE
Int16
5 -> do
Int32
-> Int32
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readDecimalType Int32
0 Int32
0 ByteString
buf IORef Int
pos Int16
0 []
Int16
6 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
DATE_TYPE
Int16
7 -> do
Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimeType Bool
False TimeUnit
MILLISECONDS ByteString
buf IORef Int
pos Int16
0 []
Int16
8 -> do
Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimestampType Bool
False TimeUnit
MILLISECONDS ByteString
buf IORef Int
pos Int16
0 []
Int16
9 -> LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
LOGICAL_TYPE_UNKNOWN
Int16
10 -> do
LogicalType
intType <- Int8
-> Bool
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readIntType Int8
0 Bool
False ByteString
buf IORef Int
pos Int16
0 []
Maybe (TType, Int16)
_ <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 []
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure LogicalType
intType
Int16
11 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
LOGICAL_TYPE_UNKNOWN
Int16
12 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
JSON_TYPE
Int16
13 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
BSON_TYPE
Int16
14 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
UUID_TYPE
Int16
15 -> do
Int -> IO (Maybe (TType, Int16)) -> IO ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 (ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 [])
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
FLOAT16_TYPE
Int16
16 -> do
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return VariantType{specificationVersion :: Int8
specificationVersion = Int8
1}
Int16
17 -> do
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GeometryType{crs :: Text
crs = Text
""}
Int16
18 -> do
LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GeographyType{crs :: Text
crs = Text
"", algorithm :: EdgeInterpolationAlgorithm
algorithm = EdgeInterpolationAlgorithm
SPHERICAL}
Int16
_ -> LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LogicalType
LOGICAL_TYPE_UNKNOWN
readIntType ::
Int8 ->
Bool ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO LogicalType
readIntType :: Int8
-> Bool
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readIntType Int8
bitWidth Bool
intIsSigned ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Word8
t <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
if Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
then LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int8 -> Bool -> LogicalType
IntType Int8
bitWidth Bool
intIsSigned)
else do
let modifier :: Int16
modifier = Word8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0xf0) Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
4) :: Int16
Int16
identifier <-
if Int16
modifier Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
0
then forall a. Integral a => ByteString -> IORef Int -> IO a
readIntFromBuffer @Int16 ByteString
buf IORef Int
pos
else Int16 -> IO Int16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int16
lastFieldId Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
+ Int16
modifier)
case Int16
identifier of
Int16
1 -> do
Word8
bitWidth' <- IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
Int8
-> Bool
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readIntType (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
bitWidth') Bool
intIsSigned ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
2 -> do
let intIsSigned' :: Bool
intIsSigned' = (Word8
t Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f) Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
compactBooleanTrue
Int8
-> Bool
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readIntType Int8
bitWidth Bool
intIsSigned' ByteString
buf IORef Int
pos Int16
identifier [Int16]
fieldStack
Int16
_ -> [Char] -> IO LogicalType
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO LogicalType) -> [Char] -> IO LogicalType
forall a b. (a -> b) -> a -> b
$ [Char]
"UNKNOWN field ID for IntType: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int16 -> [Char]
forall a. Show a => a -> [Char]
show Int16
identifier
readDecimalType ::
Int32 ->
Int32 ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO LogicalType
readDecimalType :: Int32
-> Int32
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readDecimalType Int32
precision Int32
scale ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32 -> Int32 -> LogicalType
DecimalType Int32
precision Int32
scale)
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Int32
scale' <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
Int32
-> Int32
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readDecimalType Int32
precision Int32
scale' ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
2 -> do
Int32
precision' <- ByteString -> IORef Int -> IO Int32
readInt32FromBuffer ByteString
buf IORef Int
pos
Int32
-> Int32
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readDecimalType Int32
precision' Int32
scale ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
_ -> [Char] -> IO LogicalType
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO LogicalType) -> [Char] -> IO LogicalType
forall a b. (a -> b) -> a -> b
$ [Char]
"UNKNOWN field ID for DecimalType" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int16 -> [Char]
forall a. Show a => a -> [Char]
show Int16
identifier
readTimeType ::
Bool ->
TimeUnit ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO LogicalType
readTimeType :: Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimeType Bool
isAdjustedToUTC TimeUnit
unit ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> TimeUnit -> LogicalType
TimeType Bool
isAdjustedToUTC TimeUnit
unit)
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Bool
isAdjustedToUTC' <- (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
compactBooleanTrue) (Word8 -> Bool) -> IO Word8 -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimeType Bool
isAdjustedToUTC' TimeUnit
unit ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
2 -> do
TimeUnit
unit' <- ByteString -> IORef Int -> Int16 -> [Int16] -> IO TimeUnit
readUnit ByteString
buf IORef Int
pos Int16
0 []
Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimeType Bool
isAdjustedToUTC TimeUnit
unit' ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
_ -> [Char] -> IO LogicalType
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO LogicalType) -> [Char] -> IO LogicalType
forall a b. (a -> b) -> a -> b
$ [Char]
"UNKNOWN field ID for TimeType" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int16 -> [Char]
forall a. Show a => a -> [Char]
show Int16
identifier
readTimestampType ::
Bool ->
TimeUnit ->
BS.ByteString ->
IORef Int ->
Int16 ->
[Int16] ->
IO LogicalType
readTimestampType :: Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimestampType Bool
isAdjustedToUTC TimeUnit
unit ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> LogicalType -> IO LogicalType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> TimeUnit -> LogicalType
TimestampType Bool
isAdjustedToUTC TimeUnit
unit)
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Bool
isAdjustedToUTC' <- (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
compactBooleanTrue) (Word8 -> Bool) -> IO Word8 -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef Int -> ByteString -> IO Word8
readAndAdvance IORef Int
pos ByteString
buf
Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimestampType Bool
isAdjustedToUTC' TimeUnit
unit ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
2 -> do
TimeUnit
unit' <- ByteString -> IORef Int -> Int16 -> [Int16] -> IO TimeUnit
readUnit ByteString
buf IORef Int
pos Int16
0 []
Bool
-> TimeUnit
-> ByteString
-> IORef Int
-> Int16
-> [Int16]
-> IO LogicalType
readTimestampType Bool
isAdjustedToUTC TimeUnit
unit' ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
Int16
_ -> [Char] -> IO LogicalType
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO LogicalType) -> [Char] -> IO LogicalType
forall a b. (a -> b) -> a -> b
$ [Char]
"UNKNOWN field ID for TimestampType" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int16 -> [Char]
forall a. Show a => a -> [Char]
show Int16
identifier
readUnit :: BS.ByteString -> IORef Int -> Int16 -> [Int16] -> IO TimeUnit
readUnit :: ByteString -> IORef Int -> Int16 -> [Int16] -> IO TimeUnit
readUnit ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack = do
Maybe (TType, Int16)
fieldContents <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
lastFieldId [Int16]
fieldStack
case Maybe (TType, Int16)
fieldContents of
Maybe (TType, Int16)
Nothing -> TimeUnit -> IO TimeUnit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeUnit
TIME_UNIT_UNKNOWN
Just (TType
elemType, Int16
identifier) -> case Int16
identifier of
Int16
1 -> do
Maybe (TType, Int16)
_ <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 []
TimeUnit -> IO TimeUnit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeUnit
MILLISECONDS
Int16
2 -> do
Maybe (TType, Int16)
_ <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 []
TimeUnit -> IO TimeUnit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeUnit
MICROSECONDS
Int16
3 -> do
Maybe (TType, Int16)
_ <- ByteString
-> IORef Int -> Int16 -> [Int16] -> IO (Maybe (TType, Int16))
readField ByteString
buf IORef Int
pos Int16
0 []
TimeUnit -> IO TimeUnit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeUnit
NANOSECONDS
Int16
_ -> TimeUnit -> IO TimeUnit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeUnit
TIME_UNIT_UNKNOWN