module Hydra.Langs.Parquet.Format where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data Type =
TypeBoolean |
TypeInt32 |
TypeInt64 |
TypeFloat |
TypeDouble |
TypeByteArray |
TypeFixedLenByteArray
deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
/= :: Type -> Type -> Bool
Eq, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type -> Type -> Ordering
compare :: Type -> Type -> Ordering
$c< :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
>= :: Type -> Type -> Bool
$cmax :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
min :: Type -> Type -> Type
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
(Int -> ReadS Type)
-> ReadS [Type] -> ReadPrec Type -> ReadPrec [Type] -> Read Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type
readsPrec :: Int -> ReadS Type
$creadList :: ReadS [Type]
readList :: ReadS [Type]
$creadPrec :: ReadPrec Type
readPrec :: ReadPrec Type
$creadListPrec :: ReadPrec [Type]
readListPrec :: ReadPrec [Type]
Read, Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type -> ShowS
showsPrec :: Int -> Type -> ShowS
$cshow :: Type -> String
show :: Type -> String
$cshowList :: [Type] -> ShowS
showList :: [Type] -> ShowS
Show)
_Type :: Name
_Type = (String -> Name
Core.Name String
"hydra/langs/parquet/format.Type")
_Type_boolean :: Name
_Type_boolean = (String -> Name
Core.Name String
"boolean")
_Type_int32 :: Name
_Type_int32 = (String -> Name
Core.Name String
"int32")
_Type_int64 :: Name
_Type_int64 = (String -> Name
Core.Name String
"int64")
_Type_float :: Name
_Type_float = (String -> Name
Core.Name String
"float")
_Type_double :: Name
_Type_double = (String -> Name
Core.Name String
"double")
_Type_byteArray :: Name
_Type_byteArray = (String -> Name
Core.Name String
"byteArray")
_Type_fixedLenByteArray :: Name
_Type_fixedLenByteArray = (String -> Name
Core.Name String
"fixedLenByteArray")
data FieldRepetitionType =
FieldRepetitionTypeRequired |
FieldRepetitionTypeOptional |
FieldRepetitionTypeRepeated
deriving (FieldRepetitionType -> FieldRepetitionType -> Bool
(FieldRepetitionType -> FieldRepetitionType -> Bool)
-> (FieldRepetitionType -> FieldRepetitionType -> Bool)
-> Eq FieldRepetitionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldRepetitionType -> FieldRepetitionType -> Bool
== :: FieldRepetitionType -> FieldRepetitionType -> Bool
$c/= :: FieldRepetitionType -> FieldRepetitionType -> Bool
/= :: FieldRepetitionType -> FieldRepetitionType -> Bool
Eq, Eq FieldRepetitionType
Eq FieldRepetitionType =>
(FieldRepetitionType -> FieldRepetitionType -> Ordering)
-> (FieldRepetitionType -> FieldRepetitionType -> Bool)
-> (FieldRepetitionType -> FieldRepetitionType -> Bool)
-> (FieldRepetitionType -> FieldRepetitionType -> Bool)
-> (FieldRepetitionType -> FieldRepetitionType -> Bool)
-> (FieldRepetitionType
-> FieldRepetitionType -> FieldRepetitionType)
-> (FieldRepetitionType
-> FieldRepetitionType -> FieldRepetitionType)
-> Ord FieldRepetitionType
FieldRepetitionType -> FieldRepetitionType -> Bool
FieldRepetitionType -> FieldRepetitionType -> Ordering
FieldRepetitionType -> FieldRepetitionType -> FieldRepetitionType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldRepetitionType -> FieldRepetitionType -> Ordering
compare :: FieldRepetitionType -> FieldRepetitionType -> Ordering
$c< :: FieldRepetitionType -> FieldRepetitionType -> Bool
< :: FieldRepetitionType -> FieldRepetitionType -> Bool
$c<= :: FieldRepetitionType -> FieldRepetitionType -> Bool
<= :: FieldRepetitionType -> FieldRepetitionType -> Bool
$c> :: FieldRepetitionType -> FieldRepetitionType -> Bool
> :: FieldRepetitionType -> FieldRepetitionType -> Bool
$c>= :: FieldRepetitionType -> FieldRepetitionType -> Bool
>= :: FieldRepetitionType -> FieldRepetitionType -> Bool
$cmax :: FieldRepetitionType -> FieldRepetitionType -> FieldRepetitionType
max :: FieldRepetitionType -> FieldRepetitionType -> FieldRepetitionType
$cmin :: FieldRepetitionType -> FieldRepetitionType -> FieldRepetitionType
min :: FieldRepetitionType -> FieldRepetitionType -> FieldRepetitionType
Ord, ReadPrec [FieldRepetitionType]
ReadPrec FieldRepetitionType
Int -> ReadS FieldRepetitionType
ReadS [FieldRepetitionType]
(Int -> ReadS FieldRepetitionType)
-> ReadS [FieldRepetitionType]
-> ReadPrec FieldRepetitionType
-> ReadPrec [FieldRepetitionType]
-> Read FieldRepetitionType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldRepetitionType
readsPrec :: Int -> ReadS FieldRepetitionType
$creadList :: ReadS [FieldRepetitionType]
readList :: ReadS [FieldRepetitionType]
$creadPrec :: ReadPrec FieldRepetitionType
readPrec :: ReadPrec FieldRepetitionType
$creadListPrec :: ReadPrec [FieldRepetitionType]
readListPrec :: ReadPrec [FieldRepetitionType]
Read, Int -> FieldRepetitionType -> ShowS
[FieldRepetitionType] -> ShowS
FieldRepetitionType -> String
(Int -> FieldRepetitionType -> ShowS)
-> (FieldRepetitionType -> String)
-> ([FieldRepetitionType] -> ShowS)
-> Show FieldRepetitionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldRepetitionType -> ShowS
showsPrec :: Int -> FieldRepetitionType -> ShowS
$cshow :: FieldRepetitionType -> String
show :: FieldRepetitionType -> String
$cshowList :: [FieldRepetitionType] -> ShowS
showList :: [FieldRepetitionType] -> ShowS
Show)
_FieldRepetitionType :: Name
_FieldRepetitionType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.FieldRepetitionType")
_FieldRepetitionType_required :: Name
_FieldRepetitionType_required = (String -> Name
Core.Name String
"required")
_FieldRepetitionType_optional :: Name
_FieldRepetitionType_optional = (String -> Name
Core.Name String
"optional")
_FieldRepetitionType_repeated :: Name
_FieldRepetitionType_repeated = (String -> Name
Core.Name String
"repeated")
data Statistics =
Statistics {
Statistics -> Maybe Integer
statisticsNullCount :: (Maybe Integer),
Statistics -> Maybe Integer
statisticsDistinctCount :: (Maybe Integer),
Statistics -> Maybe String
statisticsMaxValue :: (Maybe String),
Statistics -> Maybe String
statisticsMinValue :: (Maybe String)}
deriving (Statistics -> Statistics -> Bool
(Statistics -> Statistics -> Bool)
-> (Statistics -> Statistics -> Bool) -> Eq Statistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Statistics -> Statistics -> Bool
== :: Statistics -> Statistics -> Bool
$c/= :: Statistics -> Statistics -> Bool
/= :: Statistics -> Statistics -> Bool
Eq, Eq Statistics
Eq Statistics =>
(Statistics -> Statistics -> Ordering)
-> (Statistics -> Statistics -> Bool)
-> (Statistics -> Statistics -> Bool)
-> (Statistics -> Statistics -> Bool)
-> (Statistics -> Statistics -> Bool)
-> (Statistics -> Statistics -> Statistics)
-> (Statistics -> Statistics -> Statistics)
-> Ord Statistics
Statistics -> Statistics -> Bool
Statistics -> Statistics -> Ordering
Statistics -> Statistics -> Statistics
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Statistics -> Statistics -> Ordering
compare :: Statistics -> Statistics -> Ordering
$c< :: Statistics -> Statistics -> Bool
< :: Statistics -> Statistics -> Bool
$c<= :: Statistics -> Statistics -> Bool
<= :: Statistics -> Statistics -> Bool
$c> :: Statistics -> Statistics -> Bool
> :: Statistics -> Statistics -> Bool
$c>= :: Statistics -> Statistics -> Bool
>= :: Statistics -> Statistics -> Bool
$cmax :: Statistics -> Statistics -> Statistics
max :: Statistics -> Statistics -> Statistics
$cmin :: Statistics -> Statistics -> Statistics
min :: Statistics -> Statistics -> Statistics
Ord, ReadPrec [Statistics]
ReadPrec Statistics
Int -> ReadS Statistics
ReadS [Statistics]
(Int -> ReadS Statistics)
-> ReadS [Statistics]
-> ReadPrec Statistics
-> ReadPrec [Statistics]
-> Read Statistics
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Statistics
readsPrec :: Int -> ReadS Statistics
$creadList :: ReadS [Statistics]
readList :: ReadS [Statistics]
$creadPrec :: ReadPrec Statistics
readPrec :: ReadPrec Statistics
$creadListPrec :: ReadPrec [Statistics]
readListPrec :: ReadPrec [Statistics]
Read, Int -> Statistics -> ShowS
[Statistics] -> ShowS
Statistics -> String
(Int -> Statistics -> ShowS)
-> (Statistics -> String)
-> ([Statistics] -> ShowS)
-> Show Statistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Statistics -> ShowS
showsPrec :: Int -> Statistics -> ShowS
$cshow :: Statistics -> String
show :: Statistics -> String
$cshowList :: [Statistics] -> ShowS
showList :: [Statistics] -> ShowS
Show)
_Statistics :: Name
_Statistics = (String -> Name
Core.Name String
"hydra/langs/parquet/format.Statistics")
_Statistics_nullCount :: Name
_Statistics_nullCount = (String -> Name
Core.Name String
"nullCount")
_Statistics_distinctCount :: Name
_Statistics_distinctCount = (String -> Name
Core.Name String
"distinctCount")
_Statistics_maxValue :: Name
_Statistics_maxValue = (String -> Name
Core.Name String
"maxValue")
_Statistics_minValue :: Name
_Statistics_minValue = (String -> Name
Core.Name String
"minValue")
data DecimalType =
DecimalType {
DecimalType -> Int
decimalTypeScale :: Int,
DecimalType -> Int
decimalTypePrecision :: Int}
deriving (DecimalType -> DecimalType -> Bool
(DecimalType -> DecimalType -> Bool)
-> (DecimalType -> DecimalType -> Bool) -> Eq DecimalType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DecimalType -> DecimalType -> Bool
== :: DecimalType -> DecimalType -> Bool
$c/= :: DecimalType -> DecimalType -> Bool
/= :: DecimalType -> DecimalType -> Bool
Eq, Eq DecimalType
Eq DecimalType =>
(DecimalType -> DecimalType -> Ordering)
-> (DecimalType -> DecimalType -> Bool)
-> (DecimalType -> DecimalType -> Bool)
-> (DecimalType -> DecimalType -> Bool)
-> (DecimalType -> DecimalType -> Bool)
-> (DecimalType -> DecimalType -> DecimalType)
-> (DecimalType -> DecimalType -> DecimalType)
-> Ord DecimalType
DecimalType -> DecimalType -> Bool
DecimalType -> DecimalType -> Ordering
DecimalType -> DecimalType -> DecimalType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DecimalType -> DecimalType -> Ordering
compare :: DecimalType -> DecimalType -> Ordering
$c< :: DecimalType -> DecimalType -> Bool
< :: DecimalType -> DecimalType -> Bool
$c<= :: DecimalType -> DecimalType -> Bool
<= :: DecimalType -> DecimalType -> Bool
$c> :: DecimalType -> DecimalType -> Bool
> :: DecimalType -> DecimalType -> Bool
$c>= :: DecimalType -> DecimalType -> Bool
>= :: DecimalType -> DecimalType -> Bool
$cmax :: DecimalType -> DecimalType -> DecimalType
max :: DecimalType -> DecimalType -> DecimalType
$cmin :: DecimalType -> DecimalType -> DecimalType
min :: DecimalType -> DecimalType -> DecimalType
Ord, ReadPrec [DecimalType]
ReadPrec DecimalType
Int -> ReadS DecimalType
ReadS [DecimalType]
(Int -> ReadS DecimalType)
-> ReadS [DecimalType]
-> ReadPrec DecimalType
-> ReadPrec [DecimalType]
-> Read DecimalType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DecimalType
readsPrec :: Int -> ReadS DecimalType
$creadList :: ReadS [DecimalType]
readList :: ReadS [DecimalType]
$creadPrec :: ReadPrec DecimalType
readPrec :: ReadPrec DecimalType
$creadListPrec :: ReadPrec [DecimalType]
readListPrec :: ReadPrec [DecimalType]
Read, Int -> DecimalType -> ShowS
[DecimalType] -> ShowS
DecimalType -> String
(Int -> DecimalType -> ShowS)
-> (DecimalType -> String)
-> ([DecimalType] -> ShowS)
-> Show DecimalType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DecimalType -> ShowS
showsPrec :: Int -> DecimalType -> ShowS
$cshow :: DecimalType -> String
show :: DecimalType -> String
$cshowList :: [DecimalType] -> ShowS
showList :: [DecimalType] -> ShowS
Show)
_DecimalType :: Name
_DecimalType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.DecimalType")
_DecimalType_scale :: Name
_DecimalType_scale = (String -> Name
Core.Name String
"scale")
_DecimalType_precision :: Name
_DecimalType_precision = (String -> Name
Core.Name String
"precision")
data TimeUnit =
TimeUnitMillis |
TimeUnitMicros |
TimeUnitNanos
deriving (TimeUnit -> TimeUnit -> Bool
(TimeUnit -> TimeUnit -> Bool)
-> (TimeUnit -> TimeUnit -> Bool) -> Eq TimeUnit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TimeUnit -> TimeUnit -> Bool
== :: TimeUnit -> TimeUnit -> Bool
$c/= :: TimeUnit -> TimeUnit -> Bool
/= :: TimeUnit -> TimeUnit -> Bool
Eq, Eq TimeUnit
Eq TimeUnit =>
(TimeUnit -> TimeUnit -> Ordering)
-> (TimeUnit -> TimeUnit -> Bool)
-> (TimeUnit -> TimeUnit -> Bool)
-> (TimeUnit -> TimeUnit -> Bool)
-> (TimeUnit -> TimeUnit -> Bool)
-> (TimeUnit -> TimeUnit -> TimeUnit)
-> (TimeUnit -> TimeUnit -> TimeUnit)
-> Ord TimeUnit
TimeUnit -> TimeUnit -> Bool
TimeUnit -> TimeUnit -> Ordering
TimeUnit -> TimeUnit -> TimeUnit
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TimeUnit -> TimeUnit -> Ordering
compare :: TimeUnit -> TimeUnit -> Ordering
$c< :: TimeUnit -> TimeUnit -> Bool
< :: TimeUnit -> TimeUnit -> Bool
$c<= :: TimeUnit -> TimeUnit -> Bool
<= :: TimeUnit -> TimeUnit -> Bool
$c> :: TimeUnit -> TimeUnit -> Bool
> :: TimeUnit -> TimeUnit -> Bool
$c>= :: TimeUnit -> TimeUnit -> Bool
>= :: TimeUnit -> TimeUnit -> Bool
$cmax :: TimeUnit -> TimeUnit -> TimeUnit
max :: TimeUnit -> TimeUnit -> TimeUnit
$cmin :: TimeUnit -> TimeUnit -> TimeUnit
min :: TimeUnit -> TimeUnit -> TimeUnit
Ord, ReadPrec [TimeUnit]
ReadPrec TimeUnit
Int -> ReadS TimeUnit
ReadS [TimeUnit]
(Int -> ReadS TimeUnit)
-> ReadS [TimeUnit]
-> ReadPrec TimeUnit
-> ReadPrec [TimeUnit]
-> Read TimeUnit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TimeUnit
readsPrec :: Int -> ReadS TimeUnit
$creadList :: ReadS [TimeUnit]
readList :: ReadS [TimeUnit]
$creadPrec :: ReadPrec TimeUnit
readPrec :: ReadPrec TimeUnit
$creadListPrec :: ReadPrec [TimeUnit]
readListPrec :: ReadPrec [TimeUnit]
Read, Int -> TimeUnit -> ShowS
[TimeUnit] -> ShowS
TimeUnit -> String
(Int -> TimeUnit -> ShowS)
-> (TimeUnit -> String) -> ([TimeUnit] -> ShowS) -> Show TimeUnit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TimeUnit -> ShowS
showsPrec :: Int -> TimeUnit -> ShowS
$cshow :: TimeUnit -> String
show :: TimeUnit -> String
$cshowList :: [TimeUnit] -> ShowS
showList :: [TimeUnit] -> ShowS
Show)
_TimeUnit :: Name
_TimeUnit = (String -> Name
Core.Name String
"hydra/langs/parquet/format.TimeUnit")
_TimeUnit_millis :: Name
_TimeUnit_millis = (String -> Name
Core.Name String
"millis")
_TimeUnit_micros :: Name
_TimeUnit_micros = (String -> Name
Core.Name String
"micros")
_TimeUnit_nanos :: Name
_TimeUnit_nanos = (String -> Name
Core.Name String
"nanos")
data TimestampType =
TimestampType {
TimestampType -> Bool
timestampTypeIsAdjustedToUtc :: Bool,
TimestampType -> TimeUnit
timestampTypeUnit :: TimeUnit}
deriving (TimestampType -> TimestampType -> Bool
(TimestampType -> TimestampType -> Bool)
-> (TimestampType -> TimestampType -> Bool) -> Eq TimestampType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TimestampType -> TimestampType -> Bool
== :: TimestampType -> TimestampType -> Bool
$c/= :: TimestampType -> TimestampType -> Bool
/= :: TimestampType -> TimestampType -> Bool
Eq, Eq TimestampType
Eq TimestampType =>
(TimestampType -> TimestampType -> Ordering)
-> (TimestampType -> TimestampType -> Bool)
-> (TimestampType -> TimestampType -> Bool)
-> (TimestampType -> TimestampType -> Bool)
-> (TimestampType -> TimestampType -> Bool)
-> (TimestampType -> TimestampType -> TimestampType)
-> (TimestampType -> TimestampType -> TimestampType)
-> Ord TimestampType
TimestampType -> TimestampType -> Bool
TimestampType -> TimestampType -> Ordering
TimestampType -> TimestampType -> TimestampType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TimestampType -> TimestampType -> Ordering
compare :: TimestampType -> TimestampType -> Ordering
$c< :: TimestampType -> TimestampType -> Bool
< :: TimestampType -> TimestampType -> Bool
$c<= :: TimestampType -> TimestampType -> Bool
<= :: TimestampType -> TimestampType -> Bool
$c> :: TimestampType -> TimestampType -> Bool
> :: TimestampType -> TimestampType -> Bool
$c>= :: TimestampType -> TimestampType -> Bool
>= :: TimestampType -> TimestampType -> Bool
$cmax :: TimestampType -> TimestampType -> TimestampType
max :: TimestampType -> TimestampType -> TimestampType
$cmin :: TimestampType -> TimestampType -> TimestampType
min :: TimestampType -> TimestampType -> TimestampType
Ord, ReadPrec [TimestampType]
ReadPrec TimestampType
Int -> ReadS TimestampType
ReadS [TimestampType]
(Int -> ReadS TimestampType)
-> ReadS [TimestampType]
-> ReadPrec TimestampType
-> ReadPrec [TimestampType]
-> Read TimestampType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TimestampType
readsPrec :: Int -> ReadS TimestampType
$creadList :: ReadS [TimestampType]
readList :: ReadS [TimestampType]
$creadPrec :: ReadPrec TimestampType
readPrec :: ReadPrec TimestampType
$creadListPrec :: ReadPrec [TimestampType]
readListPrec :: ReadPrec [TimestampType]
Read, Int -> TimestampType -> ShowS
[TimestampType] -> ShowS
TimestampType -> String
(Int -> TimestampType -> ShowS)
-> (TimestampType -> String)
-> ([TimestampType] -> ShowS)
-> Show TimestampType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TimestampType -> ShowS
showsPrec :: Int -> TimestampType -> ShowS
$cshow :: TimestampType -> String
show :: TimestampType -> String
$cshowList :: [TimestampType] -> ShowS
showList :: [TimestampType] -> ShowS
Show)
_TimestampType :: Name
_TimestampType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.TimestampType")
_TimestampType_isAdjustedToUtc :: Name
_TimestampType_isAdjustedToUtc = (String -> Name
Core.Name String
"isAdjustedToUtc")
_TimestampType_unit :: Name
_TimestampType_unit = (String -> Name
Core.Name String
"unit")
data TimeType =
TimeType {
TimeType -> Bool
timeTypeIsAdjustedToUtc :: Bool,
TimeType -> TimeUnit
timeTypeUnit :: TimeUnit}
deriving (TimeType -> TimeType -> Bool
(TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> Bool) -> Eq TimeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TimeType -> TimeType -> Bool
== :: TimeType -> TimeType -> Bool
$c/= :: TimeType -> TimeType -> Bool
/= :: TimeType -> TimeType -> Bool
Eq, Eq TimeType
Eq TimeType =>
(TimeType -> TimeType -> Ordering)
-> (TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> TimeType)
-> (TimeType -> TimeType -> TimeType)
-> Ord TimeType
TimeType -> TimeType -> Bool
TimeType -> TimeType -> Ordering
TimeType -> TimeType -> TimeType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TimeType -> TimeType -> Ordering
compare :: TimeType -> TimeType -> Ordering
$c< :: TimeType -> TimeType -> Bool
< :: TimeType -> TimeType -> Bool
$c<= :: TimeType -> TimeType -> Bool
<= :: TimeType -> TimeType -> Bool
$c> :: TimeType -> TimeType -> Bool
> :: TimeType -> TimeType -> Bool
$c>= :: TimeType -> TimeType -> Bool
>= :: TimeType -> TimeType -> Bool
$cmax :: TimeType -> TimeType -> TimeType
max :: TimeType -> TimeType -> TimeType
$cmin :: TimeType -> TimeType -> TimeType
min :: TimeType -> TimeType -> TimeType
Ord, ReadPrec [TimeType]
ReadPrec TimeType
Int -> ReadS TimeType
ReadS [TimeType]
(Int -> ReadS TimeType)
-> ReadS [TimeType]
-> ReadPrec TimeType
-> ReadPrec [TimeType]
-> Read TimeType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TimeType
readsPrec :: Int -> ReadS TimeType
$creadList :: ReadS [TimeType]
readList :: ReadS [TimeType]
$creadPrec :: ReadPrec TimeType
readPrec :: ReadPrec TimeType
$creadListPrec :: ReadPrec [TimeType]
readListPrec :: ReadPrec [TimeType]
Read, Int -> TimeType -> ShowS
[TimeType] -> ShowS
TimeType -> String
(Int -> TimeType -> ShowS)
-> (TimeType -> String) -> ([TimeType] -> ShowS) -> Show TimeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TimeType -> ShowS
showsPrec :: Int -> TimeType -> ShowS
$cshow :: TimeType -> String
show :: TimeType -> String
$cshowList :: [TimeType] -> ShowS
showList :: [TimeType] -> ShowS
Show)
_TimeType :: Name
_TimeType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.TimeType")
_TimeType_isAdjustedToUtc :: Name
_TimeType_isAdjustedToUtc = (String -> Name
Core.Name String
"isAdjustedToUtc")
_TimeType_unit :: Name
_TimeType_unit = (String -> Name
Core.Name String
"unit")
data IntType =
IntType {
IntType -> Int16
intTypeBitWidth :: Int16,
IntType -> Bool
intTypeIsSigned :: Bool}
deriving (IntType -> IntType -> Bool
(IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool) -> Eq IntType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntType -> IntType -> Bool
== :: IntType -> IntType -> Bool
$c/= :: IntType -> IntType -> Bool
/= :: IntType -> IntType -> Bool
Eq, Eq IntType
Eq IntType =>
(IntType -> IntType -> Ordering)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> Bool)
-> (IntType -> IntType -> IntType)
-> (IntType -> IntType -> IntType)
-> Ord IntType
IntType -> IntType -> Bool
IntType -> IntType -> Ordering
IntType -> IntType -> IntType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IntType -> IntType -> Ordering
compare :: IntType -> IntType -> Ordering
$c< :: IntType -> IntType -> Bool
< :: IntType -> IntType -> Bool
$c<= :: IntType -> IntType -> Bool
<= :: IntType -> IntType -> Bool
$c> :: IntType -> IntType -> Bool
> :: IntType -> IntType -> Bool
$c>= :: IntType -> IntType -> Bool
>= :: IntType -> IntType -> Bool
$cmax :: IntType -> IntType -> IntType
max :: IntType -> IntType -> IntType
$cmin :: IntType -> IntType -> IntType
min :: IntType -> IntType -> IntType
Ord, ReadPrec [IntType]
ReadPrec IntType
Int -> ReadS IntType
ReadS [IntType]
(Int -> ReadS IntType)
-> ReadS [IntType]
-> ReadPrec IntType
-> ReadPrec [IntType]
-> Read IntType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IntType
readsPrec :: Int -> ReadS IntType
$creadList :: ReadS [IntType]
readList :: ReadS [IntType]
$creadPrec :: ReadPrec IntType
readPrec :: ReadPrec IntType
$creadListPrec :: ReadPrec [IntType]
readListPrec :: ReadPrec [IntType]
Read, Int -> IntType -> ShowS
[IntType] -> ShowS
IntType -> String
(Int -> IntType -> ShowS)
-> (IntType -> String) -> ([IntType] -> ShowS) -> Show IntType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntType -> ShowS
showsPrec :: Int -> IntType -> ShowS
$cshow :: IntType -> String
show :: IntType -> String
$cshowList :: [IntType] -> ShowS
showList :: [IntType] -> ShowS
Show)
_IntType :: Name
_IntType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.IntType")
_IntType_bitWidth :: Name
_IntType_bitWidth = (String -> Name
Core.Name String
"bitWidth")
_IntType_isSigned :: Name
_IntType_isSigned = (String -> Name
Core.Name String
"isSigned")
data LogicalType =
LogicalTypeString |
LogicalTypeMap |
LogicalTypeList |
LogicalTypeEnum |
LogicalTypeDecimal DecimalType |
LogicalTypeDate |
LogicalTypeTime TimeType |
LogicalTypeTimestamp TimestampType |
LogicalTypeInteger IntType |
LogicalTypeUnknown |
LogicalTypeJson |
LogicalTypeBson |
LogicalTypeUuid
deriving (LogicalType -> LogicalType -> Bool
(LogicalType -> LogicalType -> Bool)
-> (LogicalType -> LogicalType -> Bool) -> Eq LogicalType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogicalType -> LogicalType -> Bool
== :: LogicalType -> LogicalType -> Bool
$c/= :: LogicalType -> LogicalType -> Bool
/= :: LogicalType -> LogicalType -> Bool
Eq, Eq LogicalType
Eq LogicalType =>
(LogicalType -> LogicalType -> Ordering)
-> (LogicalType -> LogicalType -> Bool)
-> (LogicalType -> LogicalType -> Bool)
-> (LogicalType -> LogicalType -> Bool)
-> (LogicalType -> LogicalType -> Bool)
-> (LogicalType -> LogicalType -> LogicalType)
-> (LogicalType -> LogicalType -> LogicalType)
-> Ord LogicalType
LogicalType -> LogicalType -> Bool
LogicalType -> LogicalType -> Ordering
LogicalType -> LogicalType -> LogicalType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LogicalType -> LogicalType -> Ordering
compare :: LogicalType -> LogicalType -> Ordering
$c< :: LogicalType -> LogicalType -> Bool
< :: LogicalType -> LogicalType -> Bool
$c<= :: LogicalType -> LogicalType -> Bool
<= :: LogicalType -> LogicalType -> Bool
$c> :: LogicalType -> LogicalType -> Bool
> :: LogicalType -> LogicalType -> Bool
$c>= :: LogicalType -> LogicalType -> Bool
>= :: LogicalType -> LogicalType -> Bool
$cmax :: LogicalType -> LogicalType -> LogicalType
max :: LogicalType -> LogicalType -> LogicalType
$cmin :: LogicalType -> LogicalType -> LogicalType
min :: LogicalType -> LogicalType -> LogicalType
Ord, ReadPrec [LogicalType]
ReadPrec LogicalType
Int -> ReadS LogicalType
ReadS [LogicalType]
(Int -> ReadS LogicalType)
-> ReadS [LogicalType]
-> ReadPrec LogicalType
-> ReadPrec [LogicalType]
-> Read LogicalType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LogicalType
readsPrec :: Int -> ReadS LogicalType
$creadList :: ReadS [LogicalType]
readList :: ReadS [LogicalType]
$creadPrec :: ReadPrec LogicalType
readPrec :: ReadPrec LogicalType
$creadListPrec :: ReadPrec [LogicalType]
readListPrec :: ReadPrec [LogicalType]
Read, Int -> LogicalType -> ShowS
[LogicalType] -> ShowS
LogicalType -> String
(Int -> LogicalType -> ShowS)
-> (LogicalType -> String)
-> ([LogicalType] -> ShowS)
-> Show LogicalType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogicalType -> ShowS
showsPrec :: Int -> LogicalType -> ShowS
$cshow :: LogicalType -> String
show :: LogicalType -> String
$cshowList :: [LogicalType] -> ShowS
showList :: [LogicalType] -> ShowS
Show)
_LogicalType :: Name
_LogicalType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.LogicalType")
_LogicalType_string :: Name
_LogicalType_string = (String -> Name
Core.Name String
"string")
_LogicalType_map :: Name
_LogicalType_map = (String -> Name
Core.Name String
"map")
_LogicalType_list :: Name
_LogicalType_list = (String -> Name
Core.Name String
"list")
_LogicalType_enum :: Name
_LogicalType_enum = (String -> Name
Core.Name String
"enum")
_LogicalType_decimal :: Name
_LogicalType_decimal = (String -> Name
Core.Name String
"decimal")
_LogicalType_date :: Name
_LogicalType_date = (String -> Name
Core.Name String
"date")
_LogicalType_time :: Name
_LogicalType_time = (String -> Name
Core.Name String
"time")
_LogicalType_timestamp :: Name
_LogicalType_timestamp = (String -> Name
Core.Name String
"timestamp")
_LogicalType_integer :: Name
_LogicalType_integer = (String -> Name
Core.Name String
"integer")
_LogicalType_unknown :: Name
_LogicalType_unknown = (String -> Name
Core.Name String
"unknown")
_LogicalType_json :: Name
_LogicalType_json = (String -> Name
Core.Name String
"json")
_LogicalType_bson :: Name
_LogicalType_bson = (String -> Name
Core.Name String
"bson")
_LogicalType_uuid :: Name
_LogicalType_uuid = (String -> Name
Core.Name String
"uuid")
data SchemaElement =
SchemaElement {
SchemaElement -> Maybe Type
schemaElementType :: (Maybe Type),
SchemaElement -> Maybe Int
schemaElementTypeLength :: (Maybe Int),
SchemaElement -> Maybe FieldRepetitionType
schemaElementRepetitionType :: (Maybe FieldRepetitionType),
SchemaElement -> String
schemaElementName :: String,
SchemaElement -> Maybe Int
schemaElementNumChildren :: (Maybe Int),
SchemaElement -> Maybe Int
schemaElementFieldId :: (Maybe Int),
SchemaElement -> Maybe LogicalType
schemaElementLogicalType :: (Maybe LogicalType)}
deriving (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, Eq SchemaElement
Eq SchemaElement =>
(SchemaElement -> SchemaElement -> Ordering)
-> (SchemaElement -> SchemaElement -> Bool)
-> (SchemaElement -> SchemaElement -> Bool)
-> (SchemaElement -> SchemaElement -> Bool)
-> (SchemaElement -> SchemaElement -> Bool)
-> (SchemaElement -> SchemaElement -> SchemaElement)
-> (SchemaElement -> SchemaElement -> SchemaElement)
-> Ord SchemaElement
SchemaElement -> SchemaElement -> Bool
SchemaElement -> SchemaElement -> Ordering
SchemaElement -> SchemaElement -> SchemaElement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SchemaElement -> SchemaElement -> Ordering
compare :: SchemaElement -> SchemaElement -> Ordering
$c< :: SchemaElement -> SchemaElement -> Bool
< :: SchemaElement -> SchemaElement -> Bool
$c<= :: SchemaElement -> SchemaElement -> Bool
<= :: SchemaElement -> SchemaElement -> Bool
$c> :: SchemaElement -> SchemaElement -> Bool
> :: SchemaElement -> SchemaElement -> Bool
$c>= :: SchemaElement -> SchemaElement -> Bool
>= :: SchemaElement -> SchemaElement -> Bool
$cmax :: SchemaElement -> SchemaElement -> SchemaElement
max :: SchemaElement -> SchemaElement -> SchemaElement
$cmin :: SchemaElement -> SchemaElement -> SchemaElement
min :: SchemaElement -> SchemaElement -> SchemaElement
Ord, ReadPrec [SchemaElement]
ReadPrec SchemaElement
Int -> ReadS SchemaElement
ReadS [SchemaElement]
(Int -> ReadS SchemaElement)
-> ReadS [SchemaElement]
-> ReadPrec SchemaElement
-> ReadPrec [SchemaElement]
-> Read SchemaElement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SchemaElement
readsPrec :: Int -> ReadS SchemaElement
$creadList :: ReadS [SchemaElement]
readList :: ReadS [SchemaElement]
$creadPrec :: ReadPrec SchemaElement
readPrec :: ReadPrec SchemaElement
$creadListPrec :: ReadPrec [SchemaElement]
readListPrec :: ReadPrec [SchemaElement]
Read, Int -> SchemaElement -> ShowS
[SchemaElement] -> ShowS
SchemaElement -> String
(Int -> SchemaElement -> ShowS)
-> (SchemaElement -> String)
-> ([SchemaElement] -> ShowS)
-> Show SchemaElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SchemaElement -> ShowS
showsPrec :: Int -> SchemaElement -> ShowS
$cshow :: SchemaElement -> String
show :: SchemaElement -> String
$cshowList :: [SchemaElement] -> ShowS
showList :: [SchemaElement] -> ShowS
Show)
_SchemaElement :: Name
_SchemaElement = (String -> Name
Core.Name String
"hydra/langs/parquet/format.SchemaElement")
_SchemaElement_type :: Name
_SchemaElement_type = (String -> Name
Core.Name String
"type")
_SchemaElement_typeLength :: Name
_SchemaElement_typeLength = (String -> Name
Core.Name String
"typeLength")
_SchemaElement_repetitionType :: Name
_SchemaElement_repetitionType = (String -> Name
Core.Name String
"repetitionType")
_SchemaElement_name :: Name
_SchemaElement_name = (String -> Name
Core.Name String
"name")
_SchemaElement_numChildren :: Name
_SchemaElement_numChildren = (String -> Name
Core.Name String
"numChildren")
_SchemaElement_fieldId :: Name
_SchemaElement_fieldId = (String -> Name
Core.Name String
"fieldId")
_SchemaElement_logicalType :: Name
_SchemaElement_logicalType = (String -> Name
Core.Name String
"logicalType")
data Encoding =
EncodingPlain |
EncodingRle |
EncodingBitPacked |
EncodingDeltaBinaryPacked |
EncodingDeltaLengthByteArray |
EncodingDeltaByteArray |
EncodingRleDictionary |
EncodingByteStreamSplit
deriving (Encoding -> Encoding -> Bool
(Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Bool) -> Eq Encoding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Encoding -> Encoding -> Bool
== :: Encoding -> Encoding -> Bool
$c/= :: Encoding -> Encoding -> Bool
/= :: Encoding -> Encoding -> Bool
Eq, Eq Encoding
Eq Encoding =>
(Encoding -> Encoding -> Ordering)
-> (Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Bool)
-> (Encoding -> Encoding -> Encoding)
-> (Encoding -> Encoding -> Encoding)
-> Ord Encoding
Encoding -> Encoding -> Bool
Encoding -> Encoding -> Ordering
Encoding -> Encoding -> Encoding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Encoding -> Encoding -> Ordering
compare :: Encoding -> Encoding -> Ordering
$c< :: Encoding -> Encoding -> Bool
< :: Encoding -> Encoding -> Bool
$c<= :: Encoding -> Encoding -> Bool
<= :: Encoding -> Encoding -> Bool
$c> :: Encoding -> Encoding -> Bool
> :: Encoding -> Encoding -> Bool
$c>= :: Encoding -> Encoding -> Bool
>= :: Encoding -> Encoding -> Bool
$cmax :: Encoding -> Encoding -> Encoding
max :: Encoding -> Encoding -> Encoding
$cmin :: Encoding -> Encoding -> Encoding
min :: Encoding -> Encoding -> Encoding
Ord, ReadPrec [Encoding]
ReadPrec Encoding
Int -> ReadS Encoding
ReadS [Encoding]
(Int -> ReadS Encoding)
-> ReadS [Encoding]
-> ReadPrec Encoding
-> ReadPrec [Encoding]
-> Read Encoding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Encoding
readsPrec :: Int -> ReadS Encoding
$creadList :: ReadS [Encoding]
readList :: ReadS [Encoding]
$creadPrec :: ReadPrec Encoding
readPrec :: ReadPrec Encoding
$creadListPrec :: ReadPrec [Encoding]
readListPrec :: ReadPrec [Encoding]
Read, Int -> Encoding -> ShowS
[Encoding] -> ShowS
Encoding -> String
(Int -> Encoding -> ShowS)
-> (Encoding -> String) -> ([Encoding] -> ShowS) -> Show Encoding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Encoding -> ShowS
showsPrec :: Int -> Encoding -> ShowS
$cshow :: Encoding -> String
show :: Encoding -> String
$cshowList :: [Encoding] -> ShowS
showList :: [Encoding] -> ShowS
Show)
_Encoding :: Name
_Encoding = (String -> Name
Core.Name String
"hydra/langs/parquet/format.Encoding")
_Encoding_plain :: Name
_Encoding_plain = (String -> Name
Core.Name String
"plain")
_Encoding_rle :: Name
_Encoding_rle = (String -> Name
Core.Name String
"rle")
_Encoding_bitPacked :: Name
_Encoding_bitPacked = (String -> Name
Core.Name String
"bitPacked")
_Encoding_deltaBinaryPacked :: Name
_Encoding_deltaBinaryPacked = (String -> Name
Core.Name String
"deltaBinaryPacked")
_Encoding_deltaLengthByteArray :: Name
_Encoding_deltaLengthByteArray = (String -> Name
Core.Name String
"deltaLengthByteArray")
_Encoding_deltaByteArray :: Name
_Encoding_deltaByteArray = (String -> Name
Core.Name String
"deltaByteArray")
_Encoding_rleDictionary :: Name
_Encoding_rleDictionary = (String -> Name
Core.Name String
"rleDictionary")
_Encoding_byteStreamSplit :: Name
_Encoding_byteStreamSplit = (String -> Name
Core.Name String
"byteStreamSplit")
data CompressionCodec =
CompressionCodecUncompressed |
CompressionCodecSnappy |
CompressionCodecGzip |
CompressionCodecLzo |
CompressionCodecBrotli |
CompressionCodecZstd |
CompressionCodecLz4Raw
deriving (CompressionCodec -> CompressionCodec -> Bool
(CompressionCodec -> CompressionCodec -> Bool)
-> (CompressionCodec -> CompressionCodec -> Bool)
-> Eq CompressionCodec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompressionCodec -> CompressionCodec -> Bool
== :: CompressionCodec -> CompressionCodec -> Bool
$c/= :: CompressionCodec -> CompressionCodec -> Bool
/= :: CompressionCodec -> CompressionCodec -> Bool
Eq, Eq CompressionCodec
Eq CompressionCodec =>
(CompressionCodec -> CompressionCodec -> Ordering)
-> (CompressionCodec -> CompressionCodec -> Bool)
-> (CompressionCodec -> CompressionCodec -> Bool)
-> (CompressionCodec -> CompressionCodec -> Bool)
-> (CompressionCodec -> CompressionCodec -> Bool)
-> (CompressionCodec -> CompressionCodec -> CompressionCodec)
-> (CompressionCodec -> CompressionCodec -> CompressionCodec)
-> Ord CompressionCodec
CompressionCodec -> CompressionCodec -> Bool
CompressionCodec -> CompressionCodec -> Ordering
CompressionCodec -> CompressionCodec -> CompressionCodec
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CompressionCodec -> CompressionCodec -> Ordering
compare :: CompressionCodec -> CompressionCodec -> Ordering
$c< :: CompressionCodec -> CompressionCodec -> Bool
< :: CompressionCodec -> CompressionCodec -> Bool
$c<= :: CompressionCodec -> CompressionCodec -> Bool
<= :: CompressionCodec -> CompressionCodec -> Bool
$c> :: CompressionCodec -> CompressionCodec -> Bool
> :: CompressionCodec -> CompressionCodec -> Bool
$c>= :: CompressionCodec -> CompressionCodec -> Bool
>= :: CompressionCodec -> CompressionCodec -> Bool
$cmax :: CompressionCodec -> CompressionCodec -> CompressionCodec
max :: CompressionCodec -> CompressionCodec -> CompressionCodec
$cmin :: CompressionCodec -> CompressionCodec -> CompressionCodec
min :: CompressionCodec -> CompressionCodec -> CompressionCodec
Ord, ReadPrec [CompressionCodec]
ReadPrec CompressionCodec
Int -> ReadS CompressionCodec
ReadS [CompressionCodec]
(Int -> ReadS CompressionCodec)
-> ReadS [CompressionCodec]
-> ReadPrec CompressionCodec
-> ReadPrec [CompressionCodec]
-> Read CompressionCodec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CompressionCodec
readsPrec :: Int -> ReadS CompressionCodec
$creadList :: ReadS [CompressionCodec]
readList :: ReadS [CompressionCodec]
$creadPrec :: ReadPrec CompressionCodec
readPrec :: ReadPrec CompressionCodec
$creadListPrec :: ReadPrec [CompressionCodec]
readListPrec :: ReadPrec [CompressionCodec]
Read, Int -> CompressionCodec -> ShowS
[CompressionCodec] -> ShowS
CompressionCodec -> String
(Int -> CompressionCodec -> ShowS)
-> (CompressionCodec -> String)
-> ([CompressionCodec] -> ShowS)
-> Show CompressionCodec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompressionCodec -> ShowS
showsPrec :: Int -> CompressionCodec -> ShowS
$cshow :: CompressionCodec -> String
show :: CompressionCodec -> String
$cshowList :: [CompressionCodec] -> ShowS
showList :: [CompressionCodec] -> ShowS
Show)
_CompressionCodec :: Name
_CompressionCodec = (String -> Name
Core.Name String
"hydra/langs/parquet/format.CompressionCodec")
_CompressionCodec_uncompressed :: Name
_CompressionCodec_uncompressed = (String -> Name
Core.Name String
"uncompressed")
_CompressionCodec_snappy :: Name
_CompressionCodec_snappy = (String -> Name
Core.Name String
"snappy")
_CompressionCodec_gzip :: Name
_CompressionCodec_gzip = (String -> Name
Core.Name String
"gzip")
_CompressionCodec_lzo :: Name
_CompressionCodec_lzo = (String -> Name
Core.Name String
"lzo")
_CompressionCodec_brotli :: Name
_CompressionCodec_brotli = (String -> Name
Core.Name String
"brotli")
_CompressionCodec_zstd :: Name
_CompressionCodec_zstd = (String -> Name
Core.Name String
"zstd")
_CompressionCodec_lz4Raw :: Name
_CompressionCodec_lz4Raw = (String -> Name
Core.Name String
"lz4Raw")
data PageType =
PageTypeDataPage |
PageTypeIndexPage |
PageTypeDictionaryPage |
PageTypeDataPageV2
deriving (PageType -> PageType -> Bool
(PageType -> PageType -> Bool)
-> (PageType -> PageType -> Bool) -> Eq PageType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PageType -> PageType -> Bool
== :: PageType -> PageType -> Bool
$c/= :: PageType -> PageType -> Bool
/= :: PageType -> PageType -> Bool
Eq, Eq PageType
Eq PageType =>
(PageType -> PageType -> Ordering)
-> (PageType -> PageType -> Bool)
-> (PageType -> PageType -> Bool)
-> (PageType -> PageType -> Bool)
-> (PageType -> PageType -> Bool)
-> (PageType -> PageType -> PageType)
-> (PageType -> PageType -> PageType)
-> Ord PageType
PageType -> PageType -> Bool
PageType -> PageType -> Ordering
PageType -> PageType -> PageType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PageType -> PageType -> Ordering
compare :: PageType -> PageType -> Ordering
$c< :: PageType -> PageType -> Bool
< :: PageType -> PageType -> Bool
$c<= :: PageType -> PageType -> Bool
<= :: PageType -> PageType -> Bool
$c> :: PageType -> PageType -> Bool
> :: PageType -> PageType -> Bool
$c>= :: PageType -> PageType -> Bool
>= :: PageType -> PageType -> Bool
$cmax :: PageType -> PageType -> PageType
max :: PageType -> PageType -> PageType
$cmin :: PageType -> PageType -> PageType
min :: PageType -> PageType -> PageType
Ord, ReadPrec [PageType]
ReadPrec PageType
Int -> ReadS PageType
ReadS [PageType]
(Int -> ReadS PageType)
-> ReadS [PageType]
-> ReadPrec PageType
-> ReadPrec [PageType]
-> Read PageType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PageType
readsPrec :: Int -> ReadS PageType
$creadList :: ReadS [PageType]
readList :: ReadS [PageType]
$creadPrec :: ReadPrec PageType
readPrec :: ReadPrec PageType
$creadListPrec :: ReadPrec [PageType]
readListPrec :: ReadPrec [PageType]
Read, Int -> PageType -> ShowS
[PageType] -> ShowS
PageType -> String
(Int -> PageType -> ShowS)
-> (PageType -> String) -> ([PageType] -> ShowS) -> Show PageType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PageType -> ShowS
showsPrec :: Int -> PageType -> ShowS
$cshow :: PageType -> String
show :: PageType -> String
$cshowList :: [PageType] -> ShowS
showList :: [PageType] -> ShowS
Show)
_PageType :: Name
_PageType = (String -> Name
Core.Name String
"hydra/langs/parquet/format.PageType")
_PageType_dataPage :: Name
_PageType_dataPage = (String -> Name
Core.Name String
"dataPage")
_PageType_indexPage :: Name
_PageType_indexPage = (String -> Name
Core.Name String
"indexPage")
_PageType_dictionaryPage :: Name
_PageType_dictionaryPage = (String -> Name
Core.Name String
"dictionaryPage")
_PageType_dataPageV2 :: Name
_PageType_dataPageV2 = (String -> Name
Core.Name String
"dataPageV2")
data BoundaryOrder =
BoundaryOrderUnordered |
BoundaryOrderAscending |
BoundaryOrderDescending
deriving (BoundaryOrder -> BoundaryOrder -> Bool
(BoundaryOrder -> BoundaryOrder -> Bool)
-> (BoundaryOrder -> BoundaryOrder -> Bool) -> Eq BoundaryOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BoundaryOrder -> BoundaryOrder -> Bool
== :: BoundaryOrder -> BoundaryOrder -> Bool
$c/= :: BoundaryOrder -> BoundaryOrder -> Bool
/= :: BoundaryOrder -> BoundaryOrder -> Bool
Eq, Eq BoundaryOrder
Eq BoundaryOrder =>
(BoundaryOrder -> BoundaryOrder -> Ordering)
-> (BoundaryOrder -> BoundaryOrder -> Bool)
-> (BoundaryOrder -> BoundaryOrder -> Bool)
-> (BoundaryOrder -> BoundaryOrder -> Bool)
-> (BoundaryOrder -> BoundaryOrder -> Bool)
-> (BoundaryOrder -> BoundaryOrder -> BoundaryOrder)
-> (BoundaryOrder -> BoundaryOrder -> BoundaryOrder)
-> Ord BoundaryOrder
BoundaryOrder -> BoundaryOrder -> Bool
BoundaryOrder -> BoundaryOrder -> Ordering
BoundaryOrder -> BoundaryOrder -> BoundaryOrder
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BoundaryOrder -> BoundaryOrder -> Ordering
compare :: BoundaryOrder -> BoundaryOrder -> Ordering
$c< :: BoundaryOrder -> BoundaryOrder -> Bool
< :: BoundaryOrder -> BoundaryOrder -> Bool
$c<= :: BoundaryOrder -> BoundaryOrder -> Bool
<= :: BoundaryOrder -> BoundaryOrder -> Bool
$c> :: BoundaryOrder -> BoundaryOrder -> Bool
> :: BoundaryOrder -> BoundaryOrder -> Bool
$c>= :: BoundaryOrder -> BoundaryOrder -> Bool
>= :: BoundaryOrder -> BoundaryOrder -> Bool
$cmax :: BoundaryOrder -> BoundaryOrder -> BoundaryOrder
max :: BoundaryOrder -> BoundaryOrder -> BoundaryOrder
$cmin :: BoundaryOrder -> BoundaryOrder -> BoundaryOrder
min :: BoundaryOrder -> BoundaryOrder -> BoundaryOrder
Ord, ReadPrec [BoundaryOrder]
ReadPrec BoundaryOrder
Int -> ReadS BoundaryOrder
ReadS [BoundaryOrder]
(Int -> ReadS BoundaryOrder)
-> ReadS [BoundaryOrder]
-> ReadPrec BoundaryOrder
-> ReadPrec [BoundaryOrder]
-> Read BoundaryOrder
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BoundaryOrder
readsPrec :: Int -> ReadS BoundaryOrder
$creadList :: ReadS [BoundaryOrder]
readList :: ReadS [BoundaryOrder]
$creadPrec :: ReadPrec BoundaryOrder
readPrec :: ReadPrec BoundaryOrder
$creadListPrec :: ReadPrec [BoundaryOrder]
readListPrec :: ReadPrec [BoundaryOrder]
Read, Int -> BoundaryOrder -> ShowS
[BoundaryOrder] -> ShowS
BoundaryOrder -> String
(Int -> BoundaryOrder -> ShowS)
-> (BoundaryOrder -> String)
-> ([BoundaryOrder] -> ShowS)
-> Show BoundaryOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BoundaryOrder -> ShowS
showsPrec :: Int -> BoundaryOrder -> ShowS
$cshow :: BoundaryOrder -> String
show :: BoundaryOrder -> String
$cshowList :: [BoundaryOrder] -> ShowS
showList :: [BoundaryOrder] -> ShowS
Show)
_BoundaryOrder :: Name
_BoundaryOrder = (String -> Name
Core.Name String
"hydra/langs/parquet/format.BoundaryOrder")
_BoundaryOrder_unordered :: Name
_BoundaryOrder_unordered = (String -> Name
Core.Name String
"unordered")
_BoundaryOrder_ascending :: Name
_BoundaryOrder_ascending = (String -> Name
Core.Name String
"ascending")
_BoundaryOrder_descending :: Name
_BoundaryOrder_descending = (String -> Name
Core.Name String
"descending")
data =
{
:: Int,
:: Encoding,
:: Encoding,
:: Encoding,
:: (Maybe Statistics)}
deriving (DataPageHeader -> DataPageHeader -> Bool
(DataPageHeader -> DataPageHeader -> Bool)
-> (DataPageHeader -> DataPageHeader -> Bool) -> Eq DataPageHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPageHeader -> DataPageHeader -> Bool
== :: DataPageHeader -> DataPageHeader -> Bool
$c/= :: DataPageHeader -> DataPageHeader -> Bool
/= :: DataPageHeader -> DataPageHeader -> Bool
Eq, Eq DataPageHeader
Eq DataPageHeader =>
(DataPageHeader -> DataPageHeader -> Ordering)
-> (DataPageHeader -> DataPageHeader -> Bool)
-> (DataPageHeader -> DataPageHeader -> Bool)
-> (DataPageHeader -> DataPageHeader -> Bool)
-> (DataPageHeader -> DataPageHeader -> Bool)
-> (DataPageHeader -> DataPageHeader -> DataPageHeader)
-> (DataPageHeader -> DataPageHeader -> DataPageHeader)
-> Ord DataPageHeader
DataPageHeader -> DataPageHeader -> Bool
DataPageHeader -> DataPageHeader -> Ordering
DataPageHeader -> DataPageHeader -> DataPageHeader
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPageHeader -> DataPageHeader -> Ordering
compare :: DataPageHeader -> DataPageHeader -> Ordering
$c< :: DataPageHeader -> DataPageHeader -> Bool
< :: DataPageHeader -> DataPageHeader -> Bool
$c<= :: DataPageHeader -> DataPageHeader -> Bool
<= :: DataPageHeader -> DataPageHeader -> Bool
$c> :: DataPageHeader -> DataPageHeader -> Bool
> :: DataPageHeader -> DataPageHeader -> Bool
$c>= :: DataPageHeader -> DataPageHeader -> Bool
>= :: DataPageHeader -> DataPageHeader -> Bool
$cmax :: DataPageHeader -> DataPageHeader -> DataPageHeader
max :: DataPageHeader -> DataPageHeader -> DataPageHeader
$cmin :: DataPageHeader -> DataPageHeader -> DataPageHeader
min :: DataPageHeader -> DataPageHeader -> DataPageHeader
Ord, ReadPrec [DataPageHeader]
ReadPrec DataPageHeader
Int -> ReadS DataPageHeader
ReadS [DataPageHeader]
(Int -> ReadS DataPageHeader)
-> ReadS [DataPageHeader]
-> ReadPrec DataPageHeader
-> ReadPrec [DataPageHeader]
-> Read DataPageHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPageHeader
readsPrec :: Int -> ReadS DataPageHeader
$creadList :: ReadS [DataPageHeader]
readList :: ReadS [DataPageHeader]
$creadPrec :: ReadPrec DataPageHeader
readPrec :: ReadPrec DataPageHeader
$creadListPrec :: ReadPrec [DataPageHeader]
readListPrec :: ReadPrec [DataPageHeader]
Read, Int -> DataPageHeader -> ShowS
[DataPageHeader] -> ShowS
DataPageHeader -> String
(Int -> DataPageHeader -> ShowS)
-> (DataPageHeader -> String)
-> ([DataPageHeader] -> ShowS)
-> Show DataPageHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPageHeader -> ShowS
showsPrec :: Int -> DataPageHeader -> ShowS
$cshow :: DataPageHeader -> String
show :: DataPageHeader -> String
$cshowList :: [DataPageHeader] -> ShowS
showList :: [DataPageHeader] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.DataPageHeader")
= (String -> Name
Core.Name String
"numValues")
= (String -> Name
Core.Name String
"encoding")
= (String -> Name
Core.Name String
"definitionLevelEncoding")
= (String -> Name
Core.Name String
"repetitionLevelEncoding")
= (String -> Name
Core.Name String
"statistics")
data =
{}
deriving (IndexPageHeader -> IndexPageHeader -> Bool
(IndexPageHeader -> IndexPageHeader -> Bool)
-> (IndexPageHeader -> IndexPageHeader -> Bool)
-> Eq IndexPageHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexPageHeader -> IndexPageHeader -> Bool
== :: IndexPageHeader -> IndexPageHeader -> Bool
$c/= :: IndexPageHeader -> IndexPageHeader -> Bool
/= :: IndexPageHeader -> IndexPageHeader -> Bool
Eq, Eq IndexPageHeader
Eq IndexPageHeader =>
(IndexPageHeader -> IndexPageHeader -> Ordering)
-> (IndexPageHeader -> IndexPageHeader -> Bool)
-> (IndexPageHeader -> IndexPageHeader -> Bool)
-> (IndexPageHeader -> IndexPageHeader -> Bool)
-> (IndexPageHeader -> IndexPageHeader -> Bool)
-> (IndexPageHeader -> IndexPageHeader -> IndexPageHeader)
-> (IndexPageHeader -> IndexPageHeader -> IndexPageHeader)
-> Ord IndexPageHeader
IndexPageHeader -> IndexPageHeader -> Bool
IndexPageHeader -> IndexPageHeader -> Ordering
IndexPageHeader -> IndexPageHeader -> IndexPageHeader
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IndexPageHeader -> IndexPageHeader -> Ordering
compare :: IndexPageHeader -> IndexPageHeader -> Ordering
$c< :: IndexPageHeader -> IndexPageHeader -> Bool
< :: IndexPageHeader -> IndexPageHeader -> Bool
$c<= :: IndexPageHeader -> IndexPageHeader -> Bool
<= :: IndexPageHeader -> IndexPageHeader -> Bool
$c> :: IndexPageHeader -> IndexPageHeader -> Bool
> :: IndexPageHeader -> IndexPageHeader -> Bool
$c>= :: IndexPageHeader -> IndexPageHeader -> Bool
>= :: IndexPageHeader -> IndexPageHeader -> Bool
$cmax :: IndexPageHeader -> IndexPageHeader -> IndexPageHeader
max :: IndexPageHeader -> IndexPageHeader -> IndexPageHeader
$cmin :: IndexPageHeader -> IndexPageHeader -> IndexPageHeader
min :: IndexPageHeader -> IndexPageHeader -> IndexPageHeader
Ord, ReadPrec [IndexPageHeader]
ReadPrec IndexPageHeader
Int -> ReadS IndexPageHeader
ReadS [IndexPageHeader]
(Int -> ReadS IndexPageHeader)
-> ReadS [IndexPageHeader]
-> ReadPrec IndexPageHeader
-> ReadPrec [IndexPageHeader]
-> Read IndexPageHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IndexPageHeader
readsPrec :: Int -> ReadS IndexPageHeader
$creadList :: ReadS [IndexPageHeader]
readList :: ReadS [IndexPageHeader]
$creadPrec :: ReadPrec IndexPageHeader
readPrec :: ReadPrec IndexPageHeader
$creadListPrec :: ReadPrec [IndexPageHeader]
readListPrec :: ReadPrec [IndexPageHeader]
Read, Int -> IndexPageHeader -> ShowS
[IndexPageHeader] -> ShowS
IndexPageHeader -> String
(Int -> IndexPageHeader -> ShowS)
-> (IndexPageHeader -> String)
-> ([IndexPageHeader] -> ShowS)
-> Show IndexPageHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexPageHeader -> ShowS
showsPrec :: Int -> IndexPageHeader -> ShowS
$cshow :: IndexPageHeader -> String
show :: IndexPageHeader -> String
$cshowList :: [IndexPageHeader] -> ShowS
showList :: [IndexPageHeader] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.IndexPageHeader")
data =
{
:: Int,
:: Encoding,
:: (Maybe Bool)}
deriving (DictionaryPageHeader -> DictionaryPageHeader -> Bool
(DictionaryPageHeader -> DictionaryPageHeader -> Bool)
-> (DictionaryPageHeader -> DictionaryPageHeader -> Bool)
-> Eq DictionaryPageHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
== :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
$c/= :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
/= :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
Eq, Eq DictionaryPageHeader
Eq DictionaryPageHeader =>
(DictionaryPageHeader -> DictionaryPageHeader -> Ordering)
-> (DictionaryPageHeader -> DictionaryPageHeader -> Bool)
-> (DictionaryPageHeader -> DictionaryPageHeader -> Bool)
-> (DictionaryPageHeader -> DictionaryPageHeader -> Bool)
-> (DictionaryPageHeader -> DictionaryPageHeader -> Bool)
-> (DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader)
-> (DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader)
-> Ord DictionaryPageHeader
DictionaryPageHeader -> DictionaryPageHeader -> Bool
DictionaryPageHeader -> DictionaryPageHeader -> Ordering
DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DictionaryPageHeader -> DictionaryPageHeader -> Ordering
compare :: DictionaryPageHeader -> DictionaryPageHeader -> Ordering
$c< :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
< :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
$c<= :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
<= :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
$c> :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
> :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
$c>= :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
>= :: DictionaryPageHeader -> DictionaryPageHeader -> Bool
$cmax :: DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader
max :: DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader
$cmin :: DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader
min :: DictionaryPageHeader
-> DictionaryPageHeader -> DictionaryPageHeader
Ord, ReadPrec [DictionaryPageHeader]
ReadPrec DictionaryPageHeader
Int -> ReadS DictionaryPageHeader
ReadS [DictionaryPageHeader]
(Int -> ReadS DictionaryPageHeader)
-> ReadS [DictionaryPageHeader]
-> ReadPrec DictionaryPageHeader
-> ReadPrec [DictionaryPageHeader]
-> Read DictionaryPageHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DictionaryPageHeader
readsPrec :: Int -> ReadS DictionaryPageHeader
$creadList :: ReadS [DictionaryPageHeader]
readList :: ReadS [DictionaryPageHeader]
$creadPrec :: ReadPrec DictionaryPageHeader
readPrec :: ReadPrec DictionaryPageHeader
$creadListPrec :: ReadPrec [DictionaryPageHeader]
readListPrec :: ReadPrec [DictionaryPageHeader]
Read, Int -> DictionaryPageHeader -> ShowS
[DictionaryPageHeader] -> ShowS
DictionaryPageHeader -> String
(Int -> DictionaryPageHeader -> ShowS)
-> (DictionaryPageHeader -> String)
-> ([DictionaryPageHeader] -> ShowS)
-> Show DictionaryPageHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DictionaryPageHeader -> ShowS
showsPrec :: Int -> DictionaryPageHeader -> ShowS
$cshow :: DictionaryPageHeader -> String
show :: DictionaryPageHeader -> String
$cshowList :: [DictionaryPageHeader] -> ShowS
showList :: [DictionaryPageHeader] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.DictionaryPageHeader")
= (String -> Name
Core.Name String
"numValues")
= (String -> Name
Core.Name String
"encoding")
= (String -> Name
Core.Name String
"isSorted")
data =
{
:: Int,
:: Int,
:: Int,
:: Encoding,
:: Int,
:: Int,
:: (Maybe Bool),
:: (Maybe Statistics)}
deriving (DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
(DataPageHeaderV2 -> DataPageHeaderV2 -> Bool)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> Bool)
-> Eq DataPageHeaderV2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
== :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
$c/= :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
/= :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
Eq, Eq DataPageHeaderV2
Eq DataPageHeaderV2 =>
(DataPageHeaderV2 -> DataPageHeaderV2 -> Ordering)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> Bool)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> Bool)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> Bool)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> Bool)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2)
-> (DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2)
-> Ord DataPageHeaderV2
DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
DataPageHeaderV2 -> DataPageHeaderV2 -> Ordering
DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPageHeaderV2 -> DataPageHeaderV2 -> Ordering
compare :: DataPageHeaderV2 -> DataPageHeaderV2 -> Ordering
$c< :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
< :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
$c<= :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
<= :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
$c> :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
> :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
$c>= :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
>= :: DataPageHeaderV2 -> DataPageHeaderV2 -> Bool
$cmax :: DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2
max :: DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2
$cmin :: DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2
min :: DataPageHeaderV2 -> DataPageHeaderV2 -> DataPageHeaderV2
Ord, ReadPrec [DataPageHeaderV2]
ReadPrec DataPageHeaderV2
Int -> ReadS DataPageHeaderV2
ReadS [DataPageHeaderV2]
(Int -> ReadS DataPageHeaderV2)
-> ReadS [DataPageHeaderV2]
-> ReadPrec DataPageHeaderV2
-> ReadPrec [DataPageHeaderV2]
-> Read DataPageHeaderV2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPageHeaderV2
readsPrec :: Int -> ReadS DataPageHeaderV2
$creadList :: ReadS [DataPageHeaderV2]
readList :: ReadS [DataPageHeaderV2]
$creadPrec :: ReadPrec DataPageHeaderV2
readPrec :: ReadPrec DataPageHeaderV2
$creadListPrec :: ReadPrec [DataPageHeaderV2]
readListPrec :: ReadPrec [DataPageHeaderV2]
Read, Int -> DataPageHeaderV2 -> ShowS
[DataPageHeaderV2] -> ShowS
DataPageHeaderV2 -> String
(Int -> DataPageHeaderV2 -> ShowS)
-> (DataPageHeaderV2 -> String)
-> ([DataPageHeaderV2] -> ShowS)
-> Show DataPageHeaderV2
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPageHeaderV2 -> ShowS
showsPrec :: Int -> DataPageHeaderV2 -> ShowS
$cshow :: DataPageHeaderV2 -> String
show :: DataPageHeaderV2 -> String
$cshowList :: [DataPageHeaderV2] -> ShowS
showList :: [DataPageHeaderV2] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.DataPageHeaderV2")
= (String -> Name
Core.Name String
"numValues")
= (String -> Name
Core.Name String
"numNulls")
= (String -> Name
Core.Name String
"numRows")
= (String -> Name
Core.Name String
"encoding")
= (String -> Name
Core.Name String
"definitionLevelsByteLength")
= (String -> Name
Core.Name String
"repetitionLevelsByteLength")
= (String -> Name
Core.Name String
"isCompressed")
= (String -> Name
Core.Name String
"statistics")
data BloomFilterAlgorithm =
BloomFilterAlgorithmBlock
deriving (BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
(BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool)
-> (BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool)
-> Eq BloomFilterAlgorithm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
== :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
$c/= :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
/= :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
Eq, Eq BloomFilterAlgorithm
Eq BloomFilterAlgorithm =>
(BloomFilterAlgorithm -> BloomFilterAlgorithm -> Ordering)
-> (BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool)
-> (BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool)
-> (BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool)
-> (BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool)
-> (BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm)
-> (BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm)
-> Ord BloomFilterAlgorithm
BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
BloomFilterAlgorithm -> BloomFilterAlgorithm -> Ordering
BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Ordering
compare :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Ordering
$c< :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
< :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
$c<= :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
<= :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
$c> :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
> :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
$c>= :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
>= :: BloomFilterAlgorithm -> BloomFilterAlgorithm -> Bool
$cmax :: BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm
max :: BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm
$cmin :: BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm
min :: BloomFilterAlgorithm
-> BloomFilterAlgorithm -> BloomFilterAlgorithm
Ord, ReadPrec [BloomFilterAlgorithm]
ReadPrec BloomFilterAlgorithm
Int -> ReadS BloomFilterAlgorithm
ReadS [BloomFilterAlgorithm]
(Int -> ReadS BloomFilterAlgorithm)
-> ReadS [BloomFilterAlgorithm]
-> ReadPrec BloomFilterAlgorithm
-> ReadPrec [BloomFilterAlgorithm]
-> Read BloomFilterAlgorithm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BloomFilterAlgorithm
readsPrec :: Int -> ReadS BloomFilterAlgorithm
$creadList :: ReadS [BloomFilterAlgorithm]
readList :: ReadS [BloomFilterAlgorithm]
$creadPrec :: ReadPrec BloomFilterAlgorithm
readPrec :: ReadPrec BloomFilterAlgorithm
$creadListPrec :: ReadPrec [BloomFilterAlgorithm]
readListPrec :: ReadPrec [BloomFilterAlgorithm]
Read, Int -> BloomFilterAlgorithm -> ShowS
[BloomFilterAlgorithm] -> ShowS
BloomFilterAlgorithm -> String
(Int -> BloomFilterAlgorithm -> ShowS)
-> (BloomFilterAlgorithm -> String)
-> ([BloomFilterAlgorithm] -> ShowS)
-> Show BloomFilterAlgorithm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BloomFilterAlgorithm -> ShowS
showsPrec :: Int -> BloomFilterAlgorithm -> ShowS
$cshow :: BloomFilterAlgorithm -> String
show :: BloomFilterAlgorithm -> String
$cshowList :: [BloomFilterAlgorithm] -> ShowS
showList :: [BloomFilterAlgorithm] -> ShowS
Show)
_BloomFilterAlgorithm :: Name
_BloomFilterAlgorithm = (String -> Name
Core.Name String
"hydra/langs/parquet/format.BloomFilterAlgorithm")
_BloomFilterAlgorithm_block :: Name
_BloomFilterAlgorithm_block = (String -> Name
Core.Name String
"block")
data BloomFilterHash =
BloomFilterHashXxhash
deriving (BloomFilterHash -> BloomFilterHash -> Bool
(BloomFilterHash -> BloomFilterHash -> Bool)
-> (BloomFilterHash -> BloomFilterHash -> Bool)
-> Eq BloomFilterHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BloomFilterHash -> BloomFilterHash -> Bool
== :: BloomFilterHash -> BloomFilterHash -> Bool
$c/= :: BloomFilterHash -> BloomFilterHash -> Bool
/= :: BloomFilterHash -> BloomFilterHash -> Bool
Eq, Eq BloomFilterHash
Eq BloomFilterHash =>
(BloomFilterHash -> BloomFilterHash -> Ordering)
-> (BloomFilterHash -> BloomFilterHash -> Bool)
-> (BloomFilterHash -> BloomFilterHash -> Bool)
-> (BloomFilterHash -> BloomFilterHash -> Bool)
-> (BloomFilterHash -> BloomFilterHash -> Bool)
-> (BloomFilterHash -> BloomFilterHash -> BloomFilterHash)
-> (BloomFilterHash -> BloomFilterHash -> BloomFilterHash)
-> Ord BloomFilterHash
BloomFilterHash -> BloomFilterHash -> Bool
BloomFilterHash -> BloomFilterHash -> Ordering
BloomFilterHash -> BloomFilterHash -> BloomFilterHash
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BloomFilterHash -> BloomFilterHash -> Ordering
compare :: BloomFilterHash -> BloomFilterHash -> Ordering
$c< :: BloomFilterHash -> BloomFilterHash -> Bool
< :: BloomFilterHash -> BloomFilterHash -> Bool
$c<= :: BloomFilterHash -> BloomFilterHash -> Bool
<= :: BloomFilterHash -> BloomFilterHash -> Bool
$c> :: BloomFilterHash -> BloomFilterHash -> Bool
> :: BloomFilterHash -> BloomFilterHash -> Bool
$c>= :: BloomFilterHash -> BloomFilterHash -> Bool
>= :: BloomFilterHash -> BloomFilterHash -> Bool
$cmax :: BloomFilterHash -> BloomFilterHash -> BloomFilterHash
max :: BloomFilterHash -> BloomFilterHash -> BloomFilterHash
$cmin :: BloomFilterHash -> BloomFilterHash -> BloomFilterHash
min :: BloomFilterHash -> BloomFilterHash -> BloomFilterHash
Ord, ReadPrec [BloomFilterHash]
ReadPrec BloomFilterHash
Int -> ReadS BloomFilterHash
ReadS [BloomFilterHash]
(Int -> ReadS BloomFilterHash)
-> ReadS [BloomFilterHash]
-> ReadPrec BloomFilterHash
-> ReadPrec [BloomFilterHash]
-> Read BloomFilterHash
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BloomFilterHash
readsPrec :: Int -> ReadS BloomFilterHash
$creadList :: ReadS [BloomFilterHash]
readList :: ReadS [BloomFilterHash]
$creadPrec :: ReadPrec BloomFilterHash
readPrec :: ReadPrec BloomFilterHash
$creadListPrec :: ReadPrec [BloomFilterHash]
readListPrec :: ReadPrec [BloomFilterHash]
Read, Int -> BloomFilterHash -> ShowS
[BloomFilterHash] -> ShowS
BloomFilterHash -> String
(Int -> BloomFilterHash -> ShowS)
-> (BloomFilterHash -> String)
-> ([BloomFilterHash] -> ShowS)
-> Show BloomFilterHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BloomFilterHash -> ShowS
showsPrec :: Int -> BloomFilterHash -> ShowS
$cshow :: BloomFilterHash -> String
show :: BloomFilterHash -> String
$cshowList :: [BloomFilterHash] -> ShowS
showList :: [BloomFilterHash] -> ShowS
Show)
_BloomFilterHash :: Name
_BloomFilterHash = (String -> Name
Core.Name String
"hydra/langs/parquet/format.BloomFilterHash")
_BloomFilterHash_xxhash :: Name
_BloomFilterHash_xxhash = (String -> Name
Core.Name String
"xxhash")
data BloomFilterCompression =
BloomFilterCompressionUncompressed
deriving (BloomFilterCompression -> BloomFilterCompression -> Bool
(BloomFilterCompression -> BloomFilterCompression -> Bool)
-> (BloomFilterCompression -> BloomFilterCompression -> Bool)
-> Eq BloomFilterCompression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BloomFilterCompression -> BloomFilterCompression -> Bool
== :: BloomFilterCompression -> BloomFilterCompression -> Bool
$c/= :: BloomFilterCompression -> BloomFilterCompression -> Bool
/= :: BloomFilterCompression -> BloomFilterCompression -> Bool
Eq, Eq BloomFilterCompression
Eq BloomFilterCompression =>
(BloomFilterCompression -> BloomFilterCompression -> Ordering)
-> (BloomFilterCompression -> BloomFilterCompression -> Bool)
-> (BloomFilterCompression -> BloomFilterCompression -> Bool)
-> (BloomFilterCompression -> BloomFilterCompression -> Bool)
-> (BloomFilterCompression -> BloomFilterCompression -> Bool)
-> (BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression)
-> (BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression)
-> Ord BloomFilterCompression
BloomFilterCompression -> BloomFilterCompression -> Bool
BloomFilterCompression -> BloomFilterCompression -> Ordering
BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BloomFilterCompression -> BloomFilterCompression -> Ordering
compare :: BloomFilterCompression -> BloomFilterCompression -> Ordering
$c< :: BloomFilterCompression -> BloomFilterCompression -> Bool
< :: BloomFilterCompression -> BloomFilterCompression -> Bool
$c<= :: BloomFilterCompression -> BloomFilterCompression -> Bool
<= :: BloomFilterCompression -> BloomFilterCompression -> Bool
$c> :: BloomFilterCompression -> BloomFilterCompression -> Bool
> :: BloomFilterCompression -> BloomFilterCompression -> Bool
$c>= :: BloomFilterCompression -> BloomFilterCompression -> Bool
>= :: BloomFilterCompression -> BloomFilterCompression -> Bool
$cmax :: BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression
max :: BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression
$cmin :: BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression
min :: BloomFilterCompression
-> BloomFilterCompression -> BloomFilterCompression
Ord, ReadPrec [BloomFilterCompression]
ReadPrec BloomFilterCompression
Int -> ReadS BloomFilterCompression
ReadS [BloomFilterCompression]
(Int -> ReadS BloomFilterCompression)
-> ReadS [BloomFilterCompression]
-> ReadPrec BloomFilterCompression
-> ReadPrec [BloomFilterCompression]
-> Read BloomFilterCompression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BloomFilterCompression
readsPrec :: Int -> ReadS BloomFilterCompression
$creadList :: ReadS [BloomFilterCompression]
readList :: ReadS [BloomFilterCompression]
$creadPrec :: ReadPrec BloomFilterCompression
readPrec :: ReadPrec BloomFilterCompression
$creadListPrec :: ReadPrec [BloomFilterCompression]
readListPrec :: ReadPrec [BloomFilterCompression]
Read, Int -> BloomFilterCompression -> ShowS
[BloomFilterCompression] -> ShowS
BloomFilterCompression -> String
(Int -> BloomFilterCompression -> ShowS)
-> (BloomFilterCompression -> String)
-> ([BloomFilterCompression] -> ShowS)
-> Show BloomFilterCompression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BloomFilterCompression -> ShowS
showsPrec :: Int -> BloomFilterCompression -> ShowS
$cshow :: BloomFilterCompression -> String
show :: BloomFilterCompression -> String
$cshowList :: [BloomFilterCompression] -> ShowS
showList :: [BloomFilterCompression] -> ShowS
Show)
_BloomFilterCompression :: Name
_BloomFilterCompression = (String -> Name
Core.Name String
"hydra/langs/parquet/format.BloomFilterCompression")
_BloomFilterCompression_uncompressed :: Name
_BloomFilterCompression_uncompressed = (String -> Name
Core.Name String
"uncompressed")
data =
{
:: Int,
:: BloomFilterAlgorithm,
:: BloomFilterHash,
:: BloomFilterCompression}
deriving (BloomFilterHeader -> BloomFilterHeader -> Bool
(BloomFilterHeader -> BloomFilterHeader -> Bool)
-> (BloomFilterHeader -> BloomFilterHeader -> Bool)
-> Eq BloomFilterHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BloomFilterHeader -> BloomFilterHeader -> Bool
== :: BloomFilterHeader -> BloomFilterHeader -> Bool
$c/= :: BloomFilterHeader -> BloomFilterHeader -> Bool
/= :: BloomFilterHeader -> BloomFilterHeader -> Bool
Eq, Eq BloomFilterHeader
Eq BloomFilterHeader =>
(BloomFilterHeader -> BloomFilterHeader -> Ordering)
-> (BloomFilterHeader -> BloomFilterHeader -> Bool)
-> (BloomFilterHeader -> BloomFilterHeader -> Bool)
-> (BloomFilterHeader -> BloomFilterHeader -> Bool)
-> (BloomFilterHeader -> BloomFilterHeader -> Bool)
-> (BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader)
-> (BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader)
-> Ord BloomFilterHeader
BloomFilterHeader -> BloomFilterHeader -> Bool
BloomFilterHeader -> BloomFilterHeader -> Ordering
BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BloomFilterHeader -> BloomFilterHeader -> Ordering
compare :: BloomFilterHeader -> BloomFilterHeader -> Ordering
$c< :: BloomFilterHeader -> BloomFilterHeader -> Bool
< :: BloomFilterHeader -> BloomFilterHeader -> Bool
$c<= :: BloomFilterHeader -> BloomFilterHeader -> Bool
<= :: BloomFilterHeader -> BloomFilterHeader -> Bool
$c> :: BloomFilterHeader -> BloomFilterHeader -> Bool
> :: BloomFilterHeader -> BloomFilterHeader -> Bool
$c>= :: BloomFilterHeader -> BloomFilterHeader -> Bool
>= :: BloomFilterHeader -> BloomFilterHeader -> Bool
$cmax :: BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader
max :: BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader
$cmin :: BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader
min :: BloomFilterHeader -> BloomFilterHeader -> BloomFilterHeader
Ord, ReadPrec [BloomFilterHeader]
ReadPrec BloomFilterHeader
Int -> ReadS BloomFilterHeader
ReadS [BloomFilterHeader]
(Int -> ReadS BloomFilterHeader)
-> ReadS [BloomFilterHeader]
-> ReadPrec BloomFilterHeader
-> ReadPrec [BloomFilterHeader]
-> Read BloomFilterHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BloomFilterHeader
readsPrec :: Int -> ReadS BloomFilterHeader
$creadList :: ReadS [BloomFilterHeader]
readList :: ReadS [BloomFilterHeader]
$creadPrec :: ReadPrec BloomFilterHeader
readPrec :: ReadPrec BloomFilterHeader
$creadListPrec :: ReadPrec [BloomFilterHeader]
readListPrec :: ReadPrec [BloomFilterHeader]
Read, Int -> BloomFilterHeader -> ShowS
[BloomFilterHeader] -> ShowS
BloomFilterHeader -> String
(Int -> BloomFilterHeader -> ShowS)
-> (BloomFilterHeader -> String)
-> ([BloomFilterHeader] -> ShowS)
-> Show BloomFilterHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BloomFilterHeader -> ShowS
showsPrec :: Int -> BloomFilterHeader -> ShowS
$cshow :: BloomFilterHeader -> String
show :: BloomFilterHeader -> String
$cshowList :: [BloomFilterHeader] -> ShowS
showList :: [BloomFilterHeader] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.BloomFilterHeader")
= (String -> Name
Core.Name String
"numBytes")
= (String -> Name
Core.Name String
"algorithm")
= (String -> Name
Core.Name String
"hash")
= (String -> Name
Core.Name String
"compression")
data =
{
:: PageType,
:: Int,
:: Int,
:: (Maybe Int),
:: (Maybe DataPageHeader),
:: (Maybe IndexPageHeader),
:: (Maybe DictionaryPageHeader),
:: (Maybe DataPageHeaderV2)}
deriving (PageHeader -> PageHeader -> Bool
(PageHeader -> PageHeader -> Bool)
-> (PageHeader -> PageHeader -> Bool) -> Eq PageHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PageHeader -> PageHeader -> Bool
== :: PageHeader -> PageHeader -> Bool
$c/= :: PageHeader -> PageHeader -> Bool
/= :: PageHeader -> PageHeader -> Bool
Eq, Eq PageHeader
Eq PageHeader =>
(PageHeader -> PageHeader -> Ordering)
-> (PageHeader -> PageHeader -> Bool)
-> (PageHeader -> PageHeader -> Bool)
-> (PageHeader -> PageHeader -> Bool)
-> (PageHeader -> PageHeader -> Bool)
-> (PageHeader -> PageHeader -> PageHeader)
-> (PageHeader -> PageHeader -> PageHeader)
-> Ord PageHeader
PageHeader -> PageHeader -> Bool
PageHeader -> PageHeader -> Ordering
PageHeader -> PageHeader -> PageHeader
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PageHeader -> PageHeader -> Ordering
compare :: PageHeader -> PageHeader -> Ordering
$c< :: PageHeader -> PageHeader -> Bool
< :: PageHeader -> PageHeader -> Bool
$c<= :: PageHeader -> PageHeader -> Bool
<= :: PageHeader -> PageHeader -> Bool
$c> :: PageHeader -> PageHeader -> Bool
> :: PageHeader -> PageHeader -> Bool
$c>= :: PageHeader -> PageHeader -> Bool
>= :: PageHeader -> PageHeader -> Bool
$cmax :: PageHeader -> PageHeader -> PageHeader
max :: PageHeader -> PageHeader -> PageHeader
$cmin :: PageHeader -> PageHeader -> PageHeader
min :: PageHeader -> PageHeader -> PageHeader
Ord, ReadPrec [PageHeader]
ReadPrec PageHeader
Int -> ReadS PageHeader
ReadS [PageHeader]
(Int -> ReadS PageHeader)
-> ReadS [PageHeader]
-> ReadPrec PageHeader
-> ReadPrec [PageHeader]
-> Read PageHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PageHeader
readsPrec :: Int -> ReadS PageHeader
$creadList :: ReadS [PageHeader]
readList :: ReadS [PageHeader]
$creadPrec :: ReadPrec PageHeader
readPrec :: ReadPrec PageHeader
$creadListPrec :: ReadPrec [PageHeader]
readListPrec :: ReadPrec [PageHeader]
Read, Int -> PageHeader -> ShowS
[PageHeader] -> ShowS
PageHeader -> String
(Int -> PageHeader -> ShowS)
-> (PageHeader -> String)
-> ([PageHeader] -> ShowS)
-> Show PageHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PageHeader -> ShowS
showsPrec :: Int -> PageHeader -> ShowS
$cshow :: PageHeader -> String
show :: PageHeader -> String
$cshowList :: [PageHeader] -> ShowS
showList :: [PageHeader] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.PageHeader")
= (String -> Name
Core.Name String
"type")
= (String -> Name
Core.Name String
"uncompressedPageSize")
= (String -> Name
Core.Name String
"compressedPageSize")
= (String -> Name
Core.Name String
"crc")
= (String -> Name
Core.Name String
"dataPageHeader")
= (String -> Name
Core.Name String
"indexPageHeader")
= (String -> Name
Core.Name String
"dictionaryPageHeader")
= (String -> Name
Core.Name String
"dataPageHeaderV2")
data KeyValue =
KeyValue {
KeyValue -> String
keyValueKey :: String,
KeyValue -> Maybe String
keyValueValue :: (Maybe String)}
deriving (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, Eq KeyValue
Eq KeyValue =>
(KeyValue -> KeyValue -> Ordering)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> KeyValue)
-> (KeyValue -> KeyValue -> KeyValue)
-> Ord KeyValue
KeyValue -> KeyValue -> Bool
KeyValue -> KeyValue -> Ordering
KeyValue -> KeyValue -> KeyValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: KeyValue -> KeyValue -> Ordering
compare :: KeyValue -> KeyValue -> Ordering
$c< :: KeyValue -> KeyValue -> Bool
< :: KeyValue -> KeyValue -> Bool
$c<= :: KeyValue -> KeyValue -> Bool
<= :: KeyValue -> KeyValue -> Bool
$c> :: KeyValue -> KeyValue -> Bool
> :: KeyValue -> KeyValue -> Bool
$c>= :: KeyValue -> KeyValue -> Bool
>= :: KeyValue -> KeyValue -> Bool
$cmax :: KeyValue -> KeyValue -> KeyValue
max :: KeyValue -> KeyValue -> KeyValue
$cmin :: KeyValue -> KeyValue -> KeyValue
min :: KeyValue -> KeyValue -> KeyValue
Ord, ReadPrec [KeyValue]
ReadPrec KeyValue
Int -> ReadS KeyValue
ReadS [KeyValue]
(Int -> ReadS KeyValue)
-> ReadS [KeyValue]
-> ReadPrec KeyValue
-> ReadPrec [KeyValue]
-> Read KeyValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS KeyValue
readsPrec :: Int -> ReadS KeyValue
$creadList :: ReadS [KeyValue]
readList :: ReadS [KeyValue]
$creadPrec :: ReadPrec KeyValue
readPrec :: ReadPrec KeyValue
$creadListPrec :: ReadPrec [KeyValue]
readListPrec :: ReadPrec [KeyValue]
Read, Int -> KeyValue -> ShowS
[KeyValue] -> ShowS
KeyValue -> String
(Int -> KeyValue -> ShowS)
-> (KeyValue -> String) -> ([KeyValue] -> ShowS) -> Show KeyValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyValue -> ShowS
showsPrec :: Int -> KeyValue -> ShowS
$cshow :: KeyValue -> String
show :: KeyValue -> String
$cshowList :: [KeyValue] -> ShowS
showList :: [KeyValue] -> ShowS
Show)
_KeyValue :: Name
_KeyValue = (String -> Name
Core.Name String
"hydra/langs/parquet/format.KeyValue")
_KeyValue_key :: Name
_KeyValue_key = (String -> Name
Core.Name String
"key")
_KeyValue_value :: Name
_KeyValue_value = (String -> Name
Core.Name String
"value")
data SortingColumn =
SortingColumn {
SortingColumn -> Int
sortingColumnColumnIdx :: Int,
SortingColumn -> Bool
sortingColumnDescending :: Bool,
SortingColumn -> Bool
sortingColumnNullsFirst :: Bool}
deriving (SortingColumn -> SortingColumn -> Bool
(SortingColumn -> SortingColumn -> Bool)
-> (SortingColumn -> SortingColumn -> Bool) -> Eq SortingColumn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SortingColumn -> SortingColumn -> Bool
== :: SortingColumn -> SortingColumn -> Bool
$c/= :: SortingColumn -> SortingColumn -> Bool
/= :: SortingColumn -> SortingColumn -> Bool
Eq, Eq SortingColumn
Eq SortingColumn =>
(SortingColumn -> SortingColumn -> Ordering)
-> (SortingColumn -> SortingColumn -> Bool)
-> (SortingColumn -> SortingColumn -> Bool)
-> (SortingColumn -> SortingColumn -> Bool)
-> (SortingColumn -> SortingColumn -> Bool)
-> (SortingColumn -> SortingColumn -> SortingColumn)
-> (SortingColumn -> SortingColumn -> SortingColumn)
-> Ord SortingColumn
SortingColumn -> SortingColumn -> Bool
SortingColumn -> SortingColumn -> Ordering
SortingColumn -> SortingColumn -> SortingColumn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SortingColumn -> SortingColumn -> Ordering
compare :: SortingColumn -> SortingColumn -> Ordering
$c< :: SortingColumn -> SortingColumn -> Bool
< :: SortingColumn -> SortingColumn -> Bool
$c<= :: SortingColumn -> SortingColumn -> Bool
<= :: SortingColumn -> SortingColumn -> Bool
$c> :: SortingColumn -> SortingColumn -> Bool
> :: SortingColumn -> SortingColumn -> Bool
$c>= :: SortingColumn -> SortingColumn -> Bool
>= :: SortingColumn -> SortingColumn -> Bool
$cmax :: SortingColumn -> SortingColumn -> SortingColumn
max :: SortingColumn -> SortingColumn -> SortingColumn
$cmin :: SortingColumn -> SortingColumn -> SortingColumn
min :: SortingColumn -> SortingColumn -> SortingColumn
Ord, ReadPrec [SortingColumn]
ReadPrec SortingColumn
Int -> ReadS SortingColumn
ReadS [SortingColumn]
(Int -> ReadS SortingColumn)
-> ReadS [SortingColumn]
-> ReadPrec SortingColumn
-> ReadPrec [SortingColumn]
-> Read SortingColumn
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SortingColumn
readsPrec :: Int -> ReadS SortingColumn
$creadList :: ReadS [SortingColumn]
readList :: ReadS [SortingColumn]
$creadPrec :: ReadPrec SortingColumn
readPrec :: ReadPrec SortingColumn
$creadListPrec :: ReadPrec [SortingColumn]
readListPrec :: ReadPrec [SortingColumn]
Read, Int -> SortingColumn -> ShowS
[SortingColumn] -> ShowS
SortingColumn -> String
(Int -> SortingColumn -> ShowS)
-> (SortingColumn -> String)
-> ([SortingColumn] -> ShowS)
-> Show SortingColumn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SortingColumn -> ShowS
showsPrec :: Int -> SortingColumn -> ShowS
$cshow :: SortingColumn -> String
show :: SortingColumn -> String
$cshowList :: [SortingColumn] -> ShowS
showList :: [SortingColumn] -> ShowS
Show)
_SortingColumn :: Name
_SortingColumn = (String -> Name
Core.Name String
"hydra/langs/parquet/format.SortingColumn")
_SortingColumn_columnIdx :: Name
_SortingColumn_columnIdx = (String -> Name
Core.Name String
"columnIdx")
_SortingColumn_descending :: Name
_SortingColumn_descending = (String -> Name
Core.Name String
"descending")
_SortingColumn_nullsFirst :: Name
_SortingColumn_nullsFirst = (String -> Name
Core.Name String
"nullsFirst")
data PageEncodingStats =
PageEncodingStats {
PageEncodingStats -> PageType
pageEncodingStatsPageType :: PageType,
PageEncodingStats -> Encoding
pageEncodingStatsEncoding :: Encoding,
PageEncodingStats -> Int
pageEncodingStatsCount :: Int}
deriving (PageEncodingStats -> PageEncodingStats -> Bool
(PageEncodingStats -> PageEncodingStats -> Bool)
-> (PageEncodingStats -> PageEncodingStats -> Bool)
-> Eq PageEncodingStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PageEncodingStats -> PageEncodingStats -> Bool
== :: PageEncodingStats -> PageEncodingStats -> Bool
$c/= :: PageEncodingStats -> PageEncodingStats -> Bool
/= :: PageEncodingStats -> PageEncodingStats -> Bool
Eq, Eq PageEncodingStats
Eq PageEncodingStats =>
(PageEncodingStats -> PageEncodingStats -> Ordering)
-> (PageEncodingStats -> PageEncodingStats -> Bool)
-> (PageEncodingStats -> PageEncodingStats -> Bool)
-> (PageEncodingStats -> PageEncodingStats -> Bool)
-> (PageEncodingStats -> PageEncodingStats -> Bool)
-> (PageEncodingStats -> PageEncodingStats -> PageEncodingStats)
-> (PageEncodingStats -> PageEncodingStats -> PageEncodingStats)
-> Ord PageEncodingStats
PageEncodingStats -> PageEncodingStats -> Bool
PageEncodingStats -> PageEncodingStats -> Ordering
PageEncodingStats -> PageEncodingStats -> PageEncodingStats
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PageEncodingStats -> PageEncodingStats -> Ordering
compare :: PageEncodingStats -> PageEncodingStats -> Ordering
$c< :: PageEncodingStats -> PageEncodingStats -> Bool
< :: PageEncodingStats -> PageEncodingStats -> Bool
$c<= :: PageEncodingStats -> PageEncodingStats -> Bool
<= :: PageEncodingStats -> PageEncodingStats -> Bool
$c> :: PageEncodingStats -> PageEncodingStats -> Bool
> :: PageEncodingStats -> PageEncodingStats -> Bool
$c>= :: PageEncodingStats -> PageEncodingStats -> Bool
>= :: PageEncodingStats -> PageEncodingStats -> Bool
$cmax :: PageEncodingStats -> PageEncodingStats -> PageEncodingStats
max :: PageEncodingStats -> PageEncodingStats -> PageEncodingStats
$cmin :: PageEncodingStats -> PageEncodingStats -> PageEncodingStats
min :: PageEncodingStats -> PageEncodingStats -> PageEncodingStats
Ord, ReadPrec [PageEncodingStats]
ReadPrec PageEncodingStats
Int -> ReadS PageEncodingStats
ReadS [PageEncodingStats]
(Int -> ReadS PageEncodingStats)
-> ReadS [PageEncodingStats]
-> ReadPrec PageEncodingStats
-> ReadPrec [PageEncodingStats]
-> Read PageEncodingStats
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PageEncodingStats
readsPrec :: Int -> ReadS PageEncodingStats
$creadList :: ReadS [PageEncodingStats]
readList :: ReadS [PageEncodingStats]
$creadPrec :: ReadPrec PageEncodingStats
readPrec :: ReadPrec PageEncodingStats
$creadListPrec :: ReadPrec [PageEncodingStats]
readListPrec :: ReadPrec [PageEncodingStats]
Read, Int -> PageEncodingStats -> ShowS
[PageEncodingStats] -> ShowS
PageEncodingStats -> String
(Int -> PageEncodingStats -> ShowS)
-> (PageEncodingStats -> String)
-> ([PageEncodingStats] -> ShowS)
-> Show PageEncodingStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PageEncodingStats -> ShowS
showsPrec :: Int -> PageEncodingStats -> ShowS
$cshow :: PageEncodingStats -> String
show :: PageEncodingStats -> String
$cshowList :: [PageEncodingStats] -> ShowS
showList :: [PageEncodingStats] -> ShowS
Show)
_PageEncodingStats :: Name
_PageEncodingStats = (String -> Name
Core.Name String
"hydra/langs/parquet/format.PageEncodingStats")
_PageEncodingStats_pageType :: Name
_PageEncodingStats_pageType = (String -> Name
Core.Name String
"pageType")
_PageEncodingStats_encoding :: Name
_PageEncodingStats_encoding = (String -> Name
Core.Name String
"encoding")
_PageEncodingStats_count :: Name
_PageEncodingStats_count = (String -> Name
Core.Name String
"count")
data ColumnMetaData =
ColumnMetaData {
ColumnMetaData -> Type
columnMetaDataType :: Type,
ColumnMetaData -> [Encoding]
columnMetaDataEncodings :: [Encoding],
ColumnMetaData -> [String]
columnMetaDataPathInSchema :: [String],
ColumnMetaData -> CompressionCodec
columnMetaDataCodec :: CompressionCodec,
ColumnMetaData -> Int64
columnMetaDataNumValues :: Int64,
ColumnMetaData -> Int64
columnMetaDataTotalUncompressedSize :: Int64,
ColumnMetaData -> Int64
columnMetaDataTotalCompressedSize :: Int64,
ColumnMetaData -> Maybe [KeyValue]
columnMetaDataKeyValueMetadata :: (Maybe [KeyValue]),
ColumnMetaData -> Int64
columnMetaDataDataPageOffset :: Int64,
ColumnMetaData -> Maybe Int64
columnMetaDataIndexPageOffset :: (Maybe Int64),
ColumnMetaData -> Maybe Int64
columnMetaDataDictionaryPageOffset :: (Maybe Int64),
ColumnMetaData -> Maybe Statistics
columnMetaDataStatistics :: (Maybe Statistics),
ColumnMetaData -> Maybe [PageEncodingStats]
columnMetaDataEncodingStats :: (Maybe [PageEncodingStats]),
ColumnMetaData -> Maybe Int64
columnMetaDataBloomFilterOffset :: (Maybe Int64)}
deriving (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, Eq ColumnMetaData
Eq ColumnMetaData =>
(ColumnMetaData -> ColumnMetaData -> Ordering)
-> (ColumnMetaData -> ColumnMetaData -> Bool)
-> (ColumnMetaData -> ColumnMetaData -> Bool)
-> (ColumnMetaData -> ColumnMetaData -> Bool)
-> (ColumnMetaData -> ColumnMetaData -> Bool)
-> (ColumnMetaData -> ColumnMetaData -> ColumnMetaData)
-> (ColumnMetaData -> ColumnMetaData -> ColumnMetaData)
-> Ord ColumnMetaData
ColumnMetaData -> ColumnMetaData -> Bool
ColumnMetaData -> ColumnMetaData -> Ordering
ColumnMetaData -> ColumnMetaData -> ColumnMetaData
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnMetaData -> ColumnMetaData -> Ordering
compare :: ColumnMetaData -> ColumnMetaData -> Ordering
$c< :: ColumnMetaData -> ColumnMetaData -> Bool
< :: ColumnMetaData -> ColumnMetaData -> Bool
$c<= :: ColumnMetaData -> ColumnMetaData -> Bool
<= :: ColumnMetaData -> ColumnMetaData -> Bool
$c> :: ColumnMetaData -> ColumnMetaData -> Bool
> :: ColumnMetaData -> ColumnMetaData -> Bool
$c>= :: ColumnMetaData -> ColumnMetaData -> Bool
>= :: ColumnMetaData -> ColumnMetaData -> Bool
$cmax :: ColumnMetaData -> ColumnMetaData -> ColumnMetaData
max :: ColumnMetaData -> ColumnMetaData -> ColumnMetaData
$cmin :: ColumnMetaData -> ColumnMetaData -> ColumnMetaData
min :: ColumnMetaData -> ColumnMetaData -> ColumnMetaData
Ord, ReadPrec [ColumnMetaData]
ReadPrec ColumnMetaData
Int -> ReadS ColumnMetaData
ReadS [ColumnMetaData]
(Int -> ReadS ColumnMetaData)
-> ReadS [ColumnMetaData]
-> ReadPrec ColumnMetaData
-> ReadPrec [ColumnMetaData]
-> Read ColumnMetaData
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnMetaData
readsPrec :: Int -> ReadS ColumnMetaData
$creadList :: ReadS [ColumnMetaData]
readList :: ReadS [ColumnMetaData]
$creadPrec :: ReadPrec ColumnMetaData
readPrec :: ReadPrec ColumnMetaData
$creadListPrec :: ReadPrec [ColumnMetaData]
readListPrec :: ReadPrec [ColumnMetaData]
Read, Int -> ColumnMetaData -> ShowS
[ColumnMetaData] -> ShowS
ColumnMetaData -> String
(Int -> ColumnMetaData -> ShowS)
-> (ColumnMetaData -> String)
-> ([ColumnMetaData] -> ShowS)
-> Show ColumnMetaData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnMetaData -> ShowS
showsPrec :: Int -> ColumnMetaData -> ShowS
$cshow :: ColumnMetaData -> String
show :: ColumnMetaData -> String
$cshowList :: [ColumnMetaData] -> ShowS
showList :: [ColumnMetaData] -> ShowS
Show)
_ColumnMetaData :: Name
_ColumnMetaData = (String -> Name
Core.Name String
"hydra/langs/parquet/format.ColumnMetaData")
_ColumnMetaData_type :: Name
_ColumnMetaData_type = (String -> Name
Core.Name String
"type")
_ColumnMetaData_encodings :: Name
_ColumnMetaData_encodings = (String -> Name
Core.Name String
"encodings")
_ColumnMetaData_pathInSchema :: Name
_ColumnMetaData_pathInSchema = (String -> Name
Core.Name String
"pathInSchema")
_ColumnMetaData_codec :: Name
_ColumnMetaData_codec = (String -> Name
Core.Name String
"codec")
_ColumnMetaData_numValues :: Name
_ColumnMetaData_numValues = (String -> Name
Core.Name String
"numValues")
_ColumnMetaData_totalUncompressedSize :: Name
_ColumnMetaData_totalUncompressedSize = (String -> Name
Core.Name String
"totalUncompressedSize")
_ColumnMetaData_totalCompressedSize :: Name
_ColumnMetaData_totalCompressedSize = (String -> Name
Core.Name String
"totalCompressedSize")
_ColumnMetaData_keyValueMetadata :: Name
_ColumnMetaData_keyValueMetadata = (String -> Name
Core.Name String
"keyValueMetadata")
_ColumnMetaData_dataPageOffset :: Name
_ColumnMetaData_dataPageOffset = (String -> Name
Core.Name String
"dataPageOffset")
_ColumnMetaData_indexPageOffset :: Name
_ColumnMetaData_indexPageOffset = (String -> Name
Core.Name String
"indexPageOffset")
_ColumnMetaData_dictionaryPageOffset :: Name
_ColumnMetaData_dictionaryPageOffset = (String -> Name
Core.Name String
"dictionaryPageOffset")
_ColumnMetaData_statistics :: Name
_ColumnMetaData_statistics = (String -> Name
Core.Name String
"statistics")
_ColumnMetaData_encodingStats :: Name
_ColumnMetaData_encodingStats = (String -> Name
Core.Name String
"encodingStats")
_ColumnMetaData_bloomFilterOffset :: Name
_ColumnMetaData_bloomFilterOffset = (String -> Name
Core.Name String
"bloomFilterOffset")
data =
{}
deriving (EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
(EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool)
-> (EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool)
-> Eq EncryptionWithFooterKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
== :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
$c/= :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
/= :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
Eq, Eq EncryptionWithFooterKey
Eq EncryptionWithFooterKey =>
(EncryptionWithFooterKey -> EncryptionWithFooterKey -> Ordering)
-> (EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool)
-> (EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool)
-> (EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool)
-> (EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool)
-> (EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey)
-> (EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey)
-> Ord EncryptionWithFooterKey
EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
EncryptionWithFooterKey -> EncryptionWithFooterKey -> Ordering
EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Ordering
compare :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Ordering
$c< :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
< :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
$c<= :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
<= :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
$c> :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
> :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
$c>= :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
>= :: EncryptionWithFooterKey -> EncryptionWithFooterKey -> Bool
$cmax :: EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey
max :: EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey
$cmin :: EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey
min :: EncryptionWithFooterKey
-> EncryptionWithFooterKey -> EncryptionWithFooterKey
Ord, ReadPrec [EncryptionWithFooterKey]
ReadPrec EncryptionWithFooterKey
Int -> ReadS EncryptionWithFooterKey
ReadS [EncryptionWithFooterKey]
(Int -> ReadS EncryptionWithFooterKey)
-> ReadS [EncryptionWithFooterKey]
-> ReadPrec EncryptionWithFooterKey
-> ReadPrec [EncryptionWithFooterKey]
-> Read EncryptionWithFooterKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EncryptionWithFooterKey
readsPrec :: Int -> ReadS EncryptionWithFooterKey
$creadList :: ReadS [EncryptionWithFooterKey]
readList :: ReadS [EncryptionWithFooterKey]
$creadPrec :: ReadPrec EncryptionWithFooterKey
readPrec :: ReadPrec EncryptionWithFooterKey
$creadListPrec :: ReadPrec [EncryptionWithFooterKey]
readListPrec :: ReadPrec [EncryptionWithFooterKey]
Read, Int -> EncryptionWithFooterKey -> ShowS
[EncryptionWithFooterKey] -> ShowS
EncryptionWithFooterKey -> String
(Int -> EncryptionWithFooterKey -> ShowS)
-> (EncryptionWithFooterKey -> String)
-> ([EncryptionWithFooterKey] -> ShowS)
-> Show EncryptionWithFooterKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EncryptionWithFooterKey -> ShowS
showsPrec :: Int -> EncryptionWithFooterKey -> ShowS
$cshow :: EncryptionWithFooterKey -> String
show :: EncryptionWithFooterKey -> String
$cshowList :: [EncryptionWithFooterKey] -> ShowS
showList :: [EncryptionWithFooterKey] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/parquet/format.EncryptionWithFooterKey")
data EncryptionWithColumnKey =
EncryptionWithColumnKey {
EncryptionWithColumnKey -> [String]
encryptionWithColumnKeyPathInSchema :: [String],
EncryptionWithColumnKey -> Maybe String
encryptionWithColumnKeyKeyMetadata :: (Maybe String)}
deriving (EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
(EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool)
-> (EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool)
-> Eq EncryptionWithColumnKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
== :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
$c/= :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
/= :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
Eq, Eq EncryptionWithColumnKey
Eq EncryptionWithColumnKey =>
(EncryptionWithColumnKey -> EncryptionWithColumnKey -> Ordering)
-> (EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool)
-> (EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool)
-> (EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool)
-> (EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool)
-> (EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey)
-> (EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey)
-> Ord EncryptionWithColumnKey
EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
EncryptionWithColumnKey -> EncryptionWithColumnKey -> Ordering
EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Ordering
compare :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Ordering
$c< :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
< :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
$c<= :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
<= :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
$c> :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
> :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
$c>= :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
>= :: EncryptionWithColumnKey -> EncryptionWithColumnKey -> Bool
$cmax :: EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey
max :: EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey
$cmin :: EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey
min :: EncryptionWithColumnKey
-> EncryptionWithColumnKey -> EncryptionWithColumnKey
Ord, ReadPrec [EncryptionWithColumnKey]
ReadPrec EncryptionWithColumnKey
Int -> ReadS EncryptionWithColumnKey
ReadS [EncryptionWithColumnKey]
(Int -> ReadS EncryptionWithColumnKey)
-> ReadS [EncryptionWithColumnKey]
-> ReadPrec EncryptionWithColumnKey
-> ReadPrec [EncryptionWithColumnKey]
-> Read EncryptionWithColumnKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EncryptionWithColumnKey
readsPrec :: Int -> ReadS EncryptionWithColumnKey
$creadList :: ReadS [EncryptionWithColumnKey]
readList :: ReadS [EncryptionWithColumnKey]
$creadPrec :: ReadPrec EncryptionWithColumnKey
readPrec :: ReadPrec EncryptionWithColumnKey
$creadListPrec :: ReadPrec [EncryptionWithColumnKey]
readListPrec :: ReadPrec [EncryptionWithColumnKey]
Read, Int -> EncryptionWithColumnKey -> ShowS
[EncryptionWithColumnKey] -> ShowS
EncryptionWithColumnKey -> String
(Int -> EncryptionWithColumnKey -> ShowS)
-> (EncryptionWithColumnKey -> String)
-> ([EncryptionWithColumnKey] -> ShowS)
-> Show EncryptionWithColumnKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EncryptionWithColumnKey -> ShowS
showsPrec :: Int -> EncryptionWithColumnKey -> ShowS
$cshow :: EncryptionWithColumnKey -> String
show :: EncryptionWithColumnKey -> String
$cshowList :: [EncryptionWithColumnKey] -> ShowS
showList :: [EncryptionWithColumnKey] -> ShowS
Show)
_EncryptionWithColumnKey :: Name
_EncryptionWithColumnKey = (String -> Name
Core.Name String
"hydra/langs/parquet/format.EncryptionWithColumnKey")
_EncryptionWithColumnKey_pathInSchema :: Name
_EncryptionWithColumnKey_pathInSchema = (String -> Name
Core.Name String
"pathInSchema")
_EncryptionWithColumnKey_keyMetadata :: Name
_EncryptionWithColumnKey_keyMetadata = (String -> Name
Core.Name String
"keyMetadata")
data ColumnCryptoMetaData =
ColumnCryptoMetaDataEncryptionWithFooterKey EncryptionWithFooterKey |
ColumnCryptoMetaDataEncryptionWithColumnKey EncryptionWithColumnKey
deriving (ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
(ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool)
-> (ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool)
-> Eq ColumnCryptoMetaData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
== :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
$c/= :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
/= :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
Eq, Eq ColumnCryptoMetaData
Eq ColumnCryptoMetaData =>
(ColumnCryptoMetaData -> ColumnCryptoMetaData -> Ordering)
-> (ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool)
-> (ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool)
-> (ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool)
-> (ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool)
-> (ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData)
-> (ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData)
-> Ord ColumnCryptoMetaData
ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
ColumnCryptoMetaData -> ColumnCryptoMetaData -> Ordering
ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Ordering
compare :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Ordering
$c< :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
< :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
$c<= :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
<= :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
$c> :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
> :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
$c>= :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
>= :: ColumnCryptoMetaData -> ColumnCryptoMetaData -> Bool
$cmax :: ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData
max :: ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData
$cmin :: ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData
min :: ColumnCryptoMetaData
-> ColumnCryptoMetaData -> ColumnCryptoMetaData
Ord, ReadPrec [ColumnCryptoMetaData]
ReadPrec ColumnCryptoMetaData
Int -> ReadS ColumnCryptoMetaData
ReadS [ColumnCryptoMetaData]
(Int -> ReadS ColumnCryptoMetaData)
-> ReadS [ColumnCryptoMetaData]
-> ReadPrec ColumnCryptoMetaData
-> ReadPrec [ColumnCryptoMetaData]
-> Read ColumnCryptoMetaData
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnCryptoMetaData
readsPrec :: Int -> ReadS ColumnCryptoMetaData
$creadList :: ReadS [ColumnCryptoMetaData]
readList :: ReadS [ColumnCryptoMetaData]
$creadPrec :: ReadPrec ColumnCryptoMetaData
readPrec :: ReadPrec ColumnCryptoMetaData
$creadListPrec :: ReadPrec [ColumnCryptoMetaData]
readListPrec :: ReadPrec [ColumnCryptoMetaData]
Read, Int -> ColumnCryptoMetaData -> ShowS
[ColumnCryptoMetaData] -> ShowS
ColumnCryptoMetaData -> String
(Int -> ColumnCryptoMetaData -> ShowS)
-> (ColumnCryptoMetaData -> String)
-> ([ColumnCryptoMetaData] -> ShowS)
-> Show ColumnCryptoMetaData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnCryptoMetaData -> ShowS
showsPrec :: Int -> ColumnCryptoMetaData -> ShowS
$cshow :: ColumnCryptoMetaData -> String
show :: ColumnCryptoMetaData -> String
$cshowList :: [ColumnCryptoMetaData] -> ShowS
showList :: [ColumnCryptoMetaData] -> ShowS
Show)
_ColumnCryptoMetaData :: Name
_ColumnCryptoMetaData = (String -> Name
Core.Name String
"hydra/langs/parquet/format.ColumnCryptoMetaData")
_ColumnCryptoMetaData_encryptionWithFooterKey :: Name
_ColumnCryptoMetaData_encryptionWithFooterKey = (String -> Name
Core.Name String
"encryptionWithFooterKey")
_ColumnCryptoMetaData_encryptionWithColumnKey :: Name
_ColumnCryptoMetaData_encryptionWithColumnKey = (String -> Name
Core.Name String
"encryptionWithColumnKey")
data ColumnChunk =
ColumnChunk {
ColumnChunk -> Maybe String
columnChunkFilePath :: (Maybe String),
ColumnChunk -> Int64
columnChunkFileOffset :: Int64,
ColumnChunk -> Maybe ColumnMetaData
columnChunkMetaData :: (Maybe ColumnMetaData),
ColumnChunk -> Maybe Int64
columnChunkOffsetIndexOffset :: (Maybe Int64),
ColumnChunk -> Maybe Int
columnChunkOffsetIndexLength :: (Maybe Int),
ColumnChunk -> Maybe Int64
columnChunkColumnIndexOffset :: (Maybe Int64),
ColumnChunk -> Maybe Int
columnChunkColumnIndexLength :: (Maybe Int),
ColumnChunk -> Maybe ColumnCryptoMetaData
columnChunkCryptoMetadata :: (Maybe ColumnCryptoMetaData),
ColumnChunk -> Maybe String
columnChunkEncryptedColumnMetadata :: (Maybe String)}
deriving (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, Eq ColumnChunk
Eq ColumnChunk =>
(ColumnChunk -> ColumnChunk -> Ordering)
-> (ColumnChunk -> ColumnChunk -> Bool)
-> (ColumnChunk -> ColumnChunk -> Bool)
-> (ColumnChunk -> ColumnChunk -> Bool)
-> (ColumnChunk -> ColumnChunk -> Bool)
-> (ColumnChunk -> ColumnChunk -> ColumnChunk)
-> (ColumnChunk -> ColumnChunk -> ColumnChunk)
-> Ord ColumnChunk
ColumnChunk -> ColumnChunk -> Bool
ColumnChunk -> ColumnChunk -> Ordering
ColumnChunk -> ColumnChunk -> ColumnChunk
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnChunk -> ColumnChunk -> Ordering
compare :: ColumnChunk -> ColumnChunk -> Ordering
$c< :: ColumnChunk -> ColumnChunk -> Bool
< :: ColumnChunk -> ColumnChunk -> Bool
$c<= :: ColumnChunk -> ColumnChunk -> Bool
<= :: ColumnChunk -> ColumnChunk -> Bool
$c> :: ColumnChunk -> ColumnChunk -> Bool
> :: ColumnChunk -> ColumnChunk -> Bool
$c>= :: ColumnChunk -> ColumnChunk -> Bool
>= :: ColumnChunk -> ColumnChunk -> Bool
$cmax :: ColumnChunk -> ColumnChunk -> ColumnChunk
max :: ColumnChunk -> ColumnChunk -> ColumnChunk
$cmin :: ColumnChunk -> ColumnChunk -> ColumnChunk
min :: ColumnChunk -> ColumnChunk -> ColumnChunk
Ord, ReadPrec [ColumnChunk]
ReadPrec ColumnChunk
Int -> ReadS ColumnChunk
ReadS [ColumnChunk]
(Int -> ReadS ColumnChunk)
-> ReadS [ColumnChunk]
-> ReadPrec ColumnChunk
-> ReadPrec [ColumnChunk]
-> Read ColumnChunk
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnChunk
readsPrec :: Int -> ReadS ColumnChunk
$creadList :: ReadS [ColumnChunk]
readList :: ReadS [ColumnChunk]
$creadPrec :: ReadPrec ColumnChunk
readPrec :: ReadPrec ColumnChunk
$creadListPrec :: ReadPrec [ColumnChunk]
readListPrec :: ReadPrec [ColumnChunk]
Read, Int -> ColumnChunk -> ShowS
[ColumnChunk] -> ShowS
ColumnChunk -> String
(Int -> ColumnChunk -> ShowS)
-> (ColumnChunk -> String)
-> ([ColumnChunk] -> ShowS)
-> Show ColumnChunk
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnChunk -> ShowS
showsPrec :: Int -> ColumnChunk -> ShowS
$cshow :: ColumnChunk -> String
show :: ColumnChunk -> String
$cshowList :: [ColumnChunk] -> ShowS
showList :: [ColumnChunk] -> ShowS
Show)
_ColumnChunk :: Name
_ColumnChunk = (String -> Name
Core.Name String
"hydra/langs/parquet/format.ColumnChunk")
_ColumnChunk_filePath :: Name
_ColumnChunk_filePath = (String -> Name
Core.Name String
"filePath")
_ColumnChunk_fileOffset :: Name
_ColumnChunk_fileOffset = (String -> Name
Core.Name String
"fileOffset")
_ColumnChunk_metaData :: Name
_ColumnChunk_metaData = (String -> Name
Core.Name String
"metaData")
_ColumnChunk_offsetIndexOffset :: Name
_ColumnChunk_offsetIndexOffset = (String -> Name
Core.Name String
"offsetIndexOffset")
_ColumnChunk_offsetIndexLength :: Name
_ColumnChunk_offsetIndexLength = (String -> Name
Core.Name String
"offsetIndexLength")
_ColumnChunk_columnIndexOffset :: Name
_ColumnChunk_columnIndexOffset = (String -> Name
Core.Name String
"columnIndexOffset")
_ColumnChunk_columnIndexLength :: Name
_ColumnChunk_columnIndexLength = (String -> Name
Core.Name String
"columnIndexLength")
_ColumnChunk_cryptoMetadata :: Name
_ColumnChunk_cryptoMetadata = (String -> Name
Core.Name String
"cryptoMetadata")
_ColumnChunk_encryptedColumnMetadata :: Name
_ColumnChunk_encryptedColumnMetadata = (String -> Name
Core.Name String
"encryptedColumnMetadata")
data RowGroup =
RowGroup {
RowGroup -> [ColumnChunk]
rowGroupColumns :: [ColumnChunk],
RowGroup -> Int64
rowGroupTotalByteSize :: Int64,
RowGroup -> Int64
rowGroupNumRows :: Int64,
RowGroup -> Maybe [SortingColumn]
rowGroupSortingColumns :: (Maybe [SortingColumn]),
RowGroup -> Maybe Int64
rowGroupFileOffset :: (Maybe Int64),
RowGroup -> Maybe Int64
rowGroupTotalCompressedSize :: (Maybe Int64),
RowGroup -> Maybe Int16
rowGroupOrdinal :: (Maybe Int16)}
deriving (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, Eq RowGroup
Eq RowGroup =>
(RowGroup -> RowGroup -> Ordering)
-> (RowGroup -> RowGroup -> Bool)
-> (RowGroup -> RowGroup -> Bool)
-> (RowGroup -> RowGroup -> Bool)
-> (RowGroup -> RowGroup -> Bool)
-> (RowGroup -> RowGroup -> RowGroup)
-> (RowGroup -> RowGroup -> RowGroup)
-> Ord RowGroup
RowGroup -> RowGroup -> Bool
RowGroup -> RowGroup -> Ordering
RowGroup -> RowGroup -> RowGroup
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RowGroup -> RowGroup -> Ordering
compare :: RowGroup -> RowGroup -> Ordering
$c< :: RowGroup -> RowGroup -> Bool
< :: RowGroup -> RowGroup -> Bool
$c<= :: RowGroup -> RowGroup -> Bool
<= :: RowGroup -> RowGroup -> Bool
$c> :: RowGroup -> RowGroup -> Bool
> :: RowGroup -> RowGroup -> Bool
$c>= :: RowGroup -> RowGroup -> Bool
>= :: RowGroup -> RowGroup -> Bool
$cmax :: RowGroup -> RowGroup -> RowGroup
max :: RowGroup -> RowGroup -> RowGroup
$cmin :: RowGroup -> RowGroup -> RowGroup
min :: RowGroup -> RowGroup -> RowGroup
Ord, ReadPrec [RowGroup]
ReadPrec RowGroup
Int -> ReadS RowGroup
ReadS [RowGroup]
(Int -> ReadS RowGroup)
-> ReadS [RowGroup]
-> ReadPrec RowGroup
-> ReadPrec [RowGroup]
-> Read RowGroup
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RowGroup
readsPrec :: Int -> ReadS RowGroup
$creadList :: ReadS [RowGroup]
readList :: ReadS [RowGroup]
$creadPrec :: ReadPrec RowGroup
readPrec :: ReadPrec RowGroup
$creadListPrec :: ReadPrec [RowGroup]
readListPrec :: ReadPrec [RowGroup]
Read, Int -> RowGroup -> ShowS
[RowGroup] -> ShowS
RowGroup -> String
(Int -> RowGroup -> ShowS)
-> (RowGroup -> String) -> ([RowGroup] -> ShowS) -> Show RowGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RowGroup -> ShowS
showsPrec :: Int -> RowGroup -> ShowS
$cshow :: RowGroup -> String
show :: RowGroup -> String
$cshowList :: [RowGroup] -> ShowS
showList :: [RowGroup] -> ShowS
Show)
_RowGroup :: Name
_RowGroup = (String -> Name
Core.Name String
"hydra/langs/parquet/format.RowGroup")
_RowGroup_columns :: Name
_RowGroup_columns = (String -> Name
Core.Name String
"columns")
_RowGroup_totalByteSize :: Name
_RowGroup_totalByteSize = (String -> Name
Core.Name String
"totalByteSize")
_RowGroup_numRows :: Name
_RowGroup_numRows = (String -> Name
Core.Name String
"numRows")
_RowGroup_sortingColumns :: Name
_RowGroup_sortingColumns = (String -> Name
Core.Name String
"sortingColumns")
_RowGroup_fileOffset :: Name
_RowGroup_fileOffset = (String -> Name
Core.Name String
"fileOffset")
_RowGroup_totalCompressedSize :: Name
_RowGroup_totalCompressedSize = (String -> Name
Core.Name String
"totalCompressedSize")
_RowGroup_ordinal :: Name
_RowGroup_ordinal = (String -> Name
Core.Name String
"ordinal")
data ColumnOrder =
ColumnOrderTypeOrder
deriving (ColumnOrder -> ColumnOrder -> Bool
(ColumnOrder -> ColumnOrder -> Bool)
-> (ColumnOrder -> ColumnOrder -> Bool) -> Eq ColumnOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnOrder -> ColumnOrder -> Bool
== :: ColumnOrder -> ColumnOrder -> Bool
$c/= :: ColumnOrder -> ColumnOrder -> Bool
/= :: ColumnOrder -> ColumnOrder -> Bool
Eq, Eq ColumnOrder
Eq ColumnOrder =>
(ColumnOrder -> ColumnOrder -> Ordering)
-> (ColumnOrder -> ColumnOrder -> Bool)
-> (ColumnOrder -> ColumnOrder -> Bool)
-> (ColumnOrder -> ColumnOrder -> Bool)
-> (ColumnOrder -> ColumnOrder -> Bool)
-> (ColumnOrder -> ColumnOrder -> ColumnOrder)
-> (ColumnOrder -> ColumnOrder -> ColumnOrder)
-> Ord ColumnOrder
ColumnOrder -> ColumnOrder -> Bool
ColumnOrder -> ColumnOrder -> Ordering
ColumnOrder -> ColumnOrder -> ColumnOrder
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnOrder -> ColumnOrder -> Ordering
compare :: ColumnOrder -> ColumnOrder -> Ordering
$c< :: ColumnOrder -> ColumnOrder -> Bool
< :: ColumnOrder -> ColumnOrder -> Bool
$c<= :: ColumnOrder -> ColumnOrder -> Bool
<= :: ColumnOrder -> ColumnOrder -> Bool
$c> :: ColumnOrder -> ColumnOrder -> Bool
> :: ColumnOrder -> ColumnOrder -> Bool
$c>= :: ColumnOrder -> ColumnOrder -> Bool
>= :: ColumnOrder -> ColumnOrder -> Bool
$cmax :: ColumnOrder -> ColumnOrder -> ColumnOrder
max :: ColumnOrder -> ColumnOrder -> ColumnOrder
$cmin :: ColumnOrder -> ColumnOrder -> ColumnOrder
min :: ColumnOrder -> ColumnOrder -> ColumnOrder
Ord, ReadPrec [ColumnOrder]
ReadPrec ColumnOrder
Int -> ReadS ColumnOrder
ReadS [ColumnOrder]
(Int -> ReadS ColumnOrder)
-> ReadS [ColumnOrder]
-> ReadPrec ColumnOrder
-> ReadPrec [ColumnOrder]
-> Read ColumnOrder
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnOrder
readsPrec :: Int -> ReadS ColumnOrder
$creadList :: ReadS [ColumnOrder]
readList :: ReadS [ColumnOrder]
$creadPrec :: ReadPrec ColumnOrder
readPrec :: ReadPrec ColumnOrder
$creadListPrec :: ReadPrec [ColumnOrder]
readListPrec :: ReadPrec [ColumnOrder]
Read, Int -> ColumnOrder -> ShowS
[ColumnOrder] -> ShowS
ColumnOrder -> String
(Int -> ColumnOrder -> ShowS)
-> (ColumnOrder -> String)
-> ([ColumnOrder] -> ShowS)
-> Show ColumnOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnOrder -> ShowS
showsPrec :: Int -> ColumnOrder -> ShowS
$cshow :: ColumnOrder -> String
show :: ColumnOrder -> String
$cshowList :: [ColumnOrder] -> ShowS
showList :: [ColumnOrder] -> ShowS
Show)
_ColumnOrder :: Name
_ColumnOrder = (String -> Name
Core.Name String
"hydra/langs/parquet/format.ColumnOrder")
_ColumnOrder_typeOrder :: Name
_ColumnOrder_typeOrder = (String -> Name
Core.Name String
"typeOrder")
data PageLocation =
PageLocation {
PageLocation -> Int64
pageLocationOffset :: Int64,
PageLocation -> Int
pageLocationCompressedPageSize :: Int,
PageLocation -> Int64
pageLocationFirstRowIndex :: Int64}
deriving (PageLocation -> PageLocation -> Bool
(PageLocation -> PageLocation -> Bool)
-> (PageLocation -> PageLocation -> Bool) -> Eq PageLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PageLocation -> PageLocation -> Bool
== :: PageLocation -> PageLocation -> Bool
$c/= :: PageLocation -> PageLocation -> Bool
/= :: PageLocation -> PageLocation -> Bool
Eq, Eq PageLocation
Eq PageLocation =>
(PageLocation -> PageLocation -> Ordering)
-> (PageLocation -> PageLocation -> Bool)
-> (PageLocation -> PageLocation -> Bool)
-> (PageLocation -> PageLocation -> Bool)
-> (PageLocation -> PageLocation -> Bool)
-> (PageLocation -> PageLocation -> PageLocation)
-> (PageLocation -> PageLocation -> PageLocation)
-> Ord PageLocation
PageLocation -> PageLocation -> Bool
PageLocation -> PageLocation -> Ordering
PageLocation -> PageLocation -> PageLocation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PageLocation -> PageLocation -> Ordering
compare :: PageLocation -> PageLocation -> Ordering
$c< :: PageLocation -> PageLocation -> Bool
< :: PageLocation -> PageLocation -> Bool
$c<= :: PageLocation -> PageLocation -> Bool
<= :: PageLocation -> PageLocation -> Bool
$c> :: PageLocation -> PageLocation -> Bool
> :: PageLocation -> PageLocation -> Bool
$c>= :: PageLocation -> PageLocation -> Bool
>= :: PageLocation -> PageLocation -> Bool
$cmax :: PageLocation -> PageLocation -> PageLocation
max :: PageLocation -> PageLocation -> PageLocation
$cmin :: PageLocation -> PageLocation -> PageLocation
min :: PageLocation -> PageLocation -> PageLocation
Ord, ReadPrec [PageLocation]
ReadPrec PageLocation
Int -> ReadS PageLocation
ReadS [PageLocation]
(Int -> ReadS PageLocation)
-> ReadS [PageLocation]
-> ReadPrec PageLocation
-> ReadPrec [PageLocation]
-> Read PageLocation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PageLocation
readsPrec :: Int -> ReadS PageLocation
$creadList :: ReadS [PageLocation]
readList :: ReadS [PageLocation]
$creadPrec :: ReadPrec PageLocation
readPrec :: ReadPrec PageLocation
$creadListPrec :: ReadPrec [PageLocation]
readListPrec :: ReadPrec [PageLocation]
Read, Int -> PageLocation -> ShowS
[PageLocation] -> ShowS
PageLocation -> String
(Int -> PageLocation -> ShowS)
-> (PageLocation -> String)
-> ([PageLocation] -> ShowS)
-> Show PageLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PageLocation -> ShowS
showsPrec :: Int -> PageLocation -> ShowS
$cshow :: PageLocation -> String
show :: PageLocation -> String
$cshowList :: [PageLocation] -> ShowS
showList :: [PageLocation] -> ShowS
Show)
_PageLocation :: Name
_PageLocation = (String -> Name
Core.Name String
"hydra/langs/parquet/format.PageLocation")
_PageLocation_offset :: Name
_PageLocation_offset = (String -> Name
Core.Name String
"offset")
_PageLocation_compressedPageSize :: Name
_PageLocation_compressedPageSize = (String -> Name
Core.Name String
"compressedPageSize")
_PageLocation_firstRowIndex :: Name
_PageLocation_firstRowIndex = (String -> Name
Core.Name String
"firstRowIndex")
data OffsetIndex =
OffsetIndex {
OffsetIndex -> [PageLocation]
offsetIndexPageLocations :: [PageLocation]}
deriving (OffsetIndex -> OffsetIndex -> Bool
(OffsetIndex -> OffsetIndex -> Bool)
-> (OffsetIndex -> OffsetIndex -> Bool) -> Eq OffsetIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OffsetIndex -> OffsetIndex -> Bool
== :: OffsetIndex -> OffsetIndex -> Bool
$c/= :: OffsetIndex -> OffsetIndex -> Bool
/= :: OffsetIndex -> OffsetIndex -> Bool
Eq, Eq OffsetIndex
Eq OffsetIndex =>
(OffsetIndex -> OffsetIndex -> Ordering)
-> (OffsetIndex -> OffsetIndex -> Bool)
-> (OffsetIndex -> OffsetIndex -> Bool)
-> (OffsetIndex -> OffsetIndex -> Bool)
-> (OffsetIndex -> OffsetIndex -> Bool)
-> (OffsetIndex -> OffsetIndex -> OffsetIndex)
-> (OffsetIndex -> OffsetIndex -> OffsetIndex)
-> Ord OffsetIndex
OffsetIndex -> OffsetIndex -> Bool
OffsetIndex -> OffsetIndex -> Ordering
OffsetIndex -> OffsetIndex -> OffsetIndex
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OffsetIndex -> OffsetIndex -> Ordering
compare :: OffsetIndex -> OffsetIndex -> Ordering
$c< :: OffsetIndex -> OffsetIndex -> Bool
< :: OffsetIndex -> OffsetIndex -> Bool
$c<= :: OffsetIndex -> OffsetIndex -> Bool
<= :: OffsetIndex -> OffsetIndex -> Bool
$c> :: OffsetIndex -> OffsetIndex -> Bool
> :: OffsetIndex -> OffsetIndex -> Bool
$c>= :: OffsetIndex -> OffsetIndex -> Bool
>= :: OffsetIndex -> OffsetIndex -> Bool
$cmax :: OffsetIndex -> OffsetIndex -> OffsetIndex
max :: OffsetIndex -> OffsetIndex -> OffsetIndex
$cmin :: OffsetIndex -> OffsetIndex -> OffsetIndex
min :: OffsetIndex -> OffsetIndex -> OffsetIndex
Ord, ReadPrec [OffsetIndex]
ReadPrec OffsetIndex
Int -> ReadS OffsetIndex
ReadS [OffsetIndex]
(Int -> ReadS OffsetIndex)
-> ReadS [OffsetIndex]
-> ReadPrec OffsetIndex
-> ReadPrec [OffsetIndex]
-> Read OffsetIndex
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OffsetIndex
readsPrec :: Int -> ReadS OffsetIndex
$creadList :: ReadS [OffsetIndex]
readList :: ReadS [OffsetIndex]
$creadPrec :: ReadPrec OffsetIndex
readPrec :: ReadPrec OffsetIndex
$creadListPrec :: ReadPrec [OffsetIndex]
readListPrec :: ReadPrec [OffsetIndex]
Read, Int -> OffsetIndex -> ShowS
[OffsetIndex] -> ShowS
OffsetIndex -> String
(Int -> OffsetIndex -> ShowS)
-> (OffsetIndex -> String)
-> ([OffsetIndex] -> ShowS)
-> Show OffsetIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OffsetIndex -> ShowS
showsPrec :: Int -> OffsetIndex -> ShowS
$cshow :: OffsetIndex -> String
show :: OffsetIndex -> String
$cshowList :: [OffsetIndex] -> ShowS
showList :: [OffsetIndex] -> ShowS
Show)
_OffsetIndex :: Name
_OffsetIndex = (String -> Name
Core.Name String
"hydra/langs/parquet/format.OffsetIndex")
_OffsetIndex_pageLocations :: Name
_OffsetIndex_pageLocations = (String -> Name
Core.Name String
"pageLocations")
data ColumnIndex =
ColumnIndex {
ColumnIndex -> [Bool]
columnIndexNullPages :: [Bool],
ColumnIndex -> [String]
columnIndexMinValues :: [String],
ColumnIndex -> [String]
columnIndexMaxValues :: [String],
ColumnIndex -> BoundaryOrder
columnIndexBoundaryOrder :: BoundaryOrder,
ColumnIndex -> Maybe [Int64]
columnIndexNullCounts :: (Maybe [Int64])}
deriving (ColumnIndex -> ColumnIndex -> Bool
(ColumnIndex -> ColumnIndex -> Bool)
-> (ColumnIndex -> ColumnIndex -> Bool) -> Eq ColumnIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnIndex -> ColumnIndex -> Bool
== :: ColumnIndex -> ColumnIndex -> Bool
$c/= :: ColumnIndex -> ColumnIndex -> Bool
/= :: ColumnIndex -> ColumnIndex -> Bool
Eq, Eq ColumnIndex
Eq ColumnIndex =>
(ColumnIndex -> ColumnIndex -> Ordering)
-> (ColumnIndex -> ColumnIndex -> Bool)
-> (ColumnIndex -> ColumnIndex -> Bool)
-> (ColumnIndex -> ColumnIndex -> Bool)
-> (ColumnIndex -> ColumnIndex -> Bool)
-> (ColumnIndex -> ColumnIndex -> ColumnIndex)
-> (ColumnIndex -> ColumnIndex -> ColumnIndex)
-> Ord ColumnIndex
ColumnIndex -> ColumnIndex -> Bool
ColumnIndex -> ColumnIndex -> Ordering
ColumnIndex -> ColumnIndex -> ColumnIndex
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnIndex -> ColumnIndex -> Ordering
compare :: ColumnIndex -> ColumnIndex -> Ordering
$c< :: ColumnIndex -> ColumnIndex -> Bool
< :: ColumnIndex -> ColumnIndex -> Bool
$c<= :: ColumnIndex -> ColumnIndex -> Bool
<= :: ColumnIndex -> ColumnIndex -> Bool
$c> :: ColumnIndex -> ColumnIndex -> Bool
> :: ColumnIndex -> ColumnIndex -> Bool
$c>= :: ColumnIndex -> ColumnIndex -> Bool
>= :: ColumnIndex -> ColumnIndex -> Bool
$cmax :: ColumnIndex -> ColumnIndex -> ColumnIndex
max :: ColumnIndex -> ColumnIndex -> ColumnIndex
$cmin :: ColumnIndex -> ColumnIndex -> ColumnIndex
min :: ColumnIndex -> ColumnIndex -> ColumnIndex
Ord, ReadPrec [ColumnIndex]
ReadPrec ColumnIndex
Int -> ReadS ColumnIndex
ReadS [ColumnIndex]
(Int -> ReadS ColumnIndex)
-> ReadS [ColumnIndex]
-> ReadPrec ColumnIndex
-> ReadPrec [ColumnIndex]
-> Read ColumnIndex
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnIndex
readsPrec :: Int -> ReadS ColumnIndex
$creadList :: ReadS [ColumnIndex]
readList :: ReadS [ColumnIndex]
$creadPrec :: ReadPrec ColumnIndex
readPrec :: ReadPrec ColumnIndex
$creadListPrec :: ReadPrec [ColumnIndex]
readListPrec :: ReadPrec [ColumnIndex]
Read, Int -> ColumnIndex -> ShowS
[ColumnIndex] -> ShowS
ColumnIndex -> String
(Int -> ColumnIndex -> ShowS)
-> (ColumnIndex -> String)
-> ([ColumnIndex] -> ShowS)
-> Show ColumnIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnIndex -> ShowS
showsPrec :: Int -> ColumnIndex -> ShowS
$cshow :: ColumnIndex -> String
show :: ColumnIndex -> String
$cshowList :: [ColumnIndex] -> ShowS
showList :: [ColumnIndex] -> ShowS
Show)
_ColumnIndex :: Name
_ColumnIndex = (String -> Name
Core.Name String
"hydra/langs/parquet/format.ColumnIndex")
_ColumnIndex_nullPages :: Name
_ColumnIndex_nullPages = (String -> Name
Core.Name String
"nullPages")
_ColumnIndex_minValues :: Name
_ColumnIndex_minValues = (String -> Name
Core.Name String
"minValues")
_ColumnIndex_maxValues :: Name
_ColumnIndex_maxValues = (String -> Name
Core.Name String
"maxValues")
_ColumnIndex_boundaryOrder :: Name
_ColumnIndex_boundaryOrder = (String -> Name
Core.Name String
"boundaryOrder")
_ColumnIndex_nullCounts :: Name
_ColumnIndex_nullCounts = (String -> Name
Core.Name String
"nullCounts")
data AesGcmV1 =
AesGcmV1 {
AesGcmV1 -> Maybe String
aesGcmV1AadPrefix :: (Maybe String),
AesGcmV1 -> Maybe String
aesGcmV1AadFileUnique :: (Maybe String),
AesGcmV1 -> Maybe Bool
aesGcmV1SupplyAadPrefix :: (Maybe Bool)}
deriving (AesGcmV1 -> AesGcmV1 -> Bool
(AesGcmV1 -> AesGcmV1 -> Bool)
-> (AesGcmV1 -> AesGcmV1 -> Bool) -> Eq AesGcmV1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AesGcmV1 -> AesGcmV1 -> Bool
== :: AesGcmV1 -> AesGcmV1 -> Bool
$c/= :: AesGcmV1 -> AesGcmV1 -> Bool
/= :: AesGcmV1 -> AesGcmV1 -> Bool
Eq, Eq AesGcmV1
Eq AesGcmV1 =>
(AesGcmV1 -> AesGcmV1 -> Ordering)
-> (AesGcmV1 -> AesGcmV1 -> Bool)
-> (AesGcmV1 -> AesGcmV1 -> Bool)
-> (AesGcmV1 -> AesGcmV1 -> Bool)
-> (AesGcmV1 -> AesGcmV1 -> Bool)
-> (AesGcmV1 -> AesGcmV1 -> AesGcmV1)
-> (AesGcmV1 -> AesGcmV1 -> AesGcmV1)
-> Ord AesGcmV1
AesGcmV1 -> AesGcmV1 -> Bool
AesGcmV1 -> AesGcmV1 -> Ordering
AesGcmV1 -> AesGcmV1 -> AesGcmV1
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AesGcmV1 -> AesGcmV1 -> Ordering
compare :: AesGcmV1 -> AesGcmV1 -> Ordering
$c< :: AesGcmV1 -> AesGcmV1 -> Bool
< :: AesGcmV1 -> AesGcmV1 -> Bool
$c<= :: AesGcmV1 -> AesGcmV1 -> Bool
<= :: AesGcmV1 -> AesGcmV1 -> Bool
$c> :: AesGcmV1 -> AesGcmV1 -> Bool
> :: AesGcmV1 -> AesGcmV1 -> Bool
$c>= :: AesGcmV1 -> AesGcmV1 -> Bool
>= :: AesGcmV1 -> AesGcmV1 -> Bool
$cmax :: AesGcmV1 -> AesGcmV1 -> AesGcmV1
max :: AesGcmV1 -> AesGcmV1 -> AesGcmV1
$cmin :: AesGcmV1 -> AesGcmV1 -> AesGcmV1
min :: AesGcmV1 -> AesGcmV1 -> AesGcmV1
Ord, ReadPrec [AesGcmV1]
ReadPrec AesGcmV1
Int -> ReadS AesGcmV1
ReadS [AesGcmV1]
(Int -> ReadS AesGcmV1)
-> ReadS [AesGcmV1]
-> ReadPrec AesGcmV1
-> ReadPrec [AesGcmV1]
-> Read AesGcmV1
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AesGcmV1
readsPrec :: Int -> ReadS AesGcmV1
$creadList :: ReadS [AesGcmV1]
readList :: ReadS [AesGcmV1]
$creadPrec :: ReadPrec AesGcmV1
readPrec :: ReadPrec AesGcmV1
$creadListPrec :: ReadPrec [AesGcmV1]
readListPrec :: ReadPrec [AesGcmV1]
Read, Int -> AesGcmV1 -> ShowS
[AesGcmV1] -> ShowS
AesGcmV1 -> String
(Int -> AesGcmV1 -> ShowS)
-> (AesGcmV1 -> String) -> ([AesGcmV1] -> ShowS) -> Show AesGcmV1
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AesGcmV1 -> ShowS
showsPrec :: Int -> AesGcmV1 -> ShowS
$cshow :: AesGcmV1 -> String
show :: AesGcmV1 -> String
$cshowList :: [AesGcmV1] -> ShowS
showList :: [AesGcmV1] -> ShowS
Show)
_AesGcmV1 :: Name
_AesGcmV1 = (String -> Name
Core.Name String
"hydra/langs/parquet/format.AesGcmV1")
_AesGcmV1_aadPrefix :: Name
_AesGcmV1_aadPrefix = (String -> Name
Core.Name String
"aadPrefix")
_AesGcmV1_aadFileUnique :: Name
_AesGcmV1_aadFileUnique = (String -> Name
Core.Name String
"aadFileUnique")
_AesGcmV1_supplyAadPrefix :: Name
_AesGcmV1_supplyAadPrefix = (String -> Name
Core.Name String
"supplyAadPrefix")
data AesGcmCtrV1 =
AesGcmCtrV1 {
AesGcmCtrV1 -> Maybe String
aesGcmCtrV1AadPrefix :: (Maybe String),
AesGcmCtrV1 -> Maybe String
aesGcmCtrV1AadFileUnique :: (Maybe String),
AesGcmCtrV1 -> Maybe Bool
aesGcmCtrV1SupplyAadPrefix :: (Maybe Bool)}
deriving (AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
(AesGcmCtrV1 -> AesGcmCtrV1 -> Bool)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> Bool) -> Eq AesGcmCtrV1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
== :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
$c/= :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
/= :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
Eq, Eq AesGcmCtrV1
Eq AesGcmCtrV1 =>
(AesGcmCtrV1 -> AesGcmCtrV1 -> Ordering)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> Bool)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> Bool)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> Bool)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> Bool)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1)
-> (AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1)
-> Ord AesGcmCtrV1
AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
AesGcmCtrV1 -> AesGcmCtrV1 -> Ordering
AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AesGcmCtrV1 -> AesGcmCtrV1 -> Ordering
compare :: AesGcmCtrV1 -> AesGcmCtrV1 -> Ordering
$c< :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
< :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
$c<= :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
<= :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
$c> :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
> :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
$c>= :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
>= :: AesGcmCtrV1 -> AesGcmCtrV1 -> Bool
$cmax :: AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1
max :: AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1
$cmin :: AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1
min :: AesGcmCtrV1 -> AesGcmCtrV1 -> AesGcmCtrV1
Ord, ReadPrec [AesGcmCtrV1]
ReadPrec AesGcmCtrV1
Int -> ReadS AesGcmCtrV1
ReadS [AesGcmCtrV1]
(Int -> ReadS AesGcmCtrV1)
-> ReadS [AesGcmCtrV1]
-> ReadPrec AesGcmCtrV1
-> ReadPrec [AesGcmCtrV1]
-> Read AesGcmCtrV1
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AesGcmCtrV1
readsPrec :: Int -> ReadS AesGcmCtrV1
$creadList :: ReadS [AesGcmCtrV1]
readList :: ReadS [AesGcmCtrV1]
$creadPrec :: ReadPrec AesGcmCtrV1
readPrec :: ReadPrec AesGcmCtrV1
$creadListPrec :: ReadPrec [AesGcmCtrV1]
readListPrec :: ReadPrec [AesGcmCtrV1]
Read, Int -> AesGcmCtrV1 -> ShowS
[AesGcmCtrV1] -> ShowS
AesGcmCtrV1 -> String
(Int -> AesGcmCtrV1 -> ShowS)
-> (AesGcmCtrV1 -> String)
-> ([AesGcmCtrV1] -> ShowS)
-> Show AesGcmCtrV1
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AesGcmCtrV1 -> ShowS
showsPrec :: Int -> AesGcmCtrV1 -> ShowS
$cshow :: AesGcmCtrV1 -> String
show :: AesGcmCtrV1 -> String
$cshowList :: [AesGcmCtrV1] -> ShowS
showList :: [AesGcmCtrV1] -> ShowS
Show)
_AesGcmCtrV1 :: Name
_AesGcmCtrV1 = (String -> Name
Core.Name String
"hydra/langs/parquet/format.AesGcmCtrV1")
_AesGcmCtrV1_aadPrefix :: Name
_AesGcmCtrV1_aadPrefix = (String -> Name
Core.Name String
"aadPrefix")
_AesGcmCtrV1_aadFileUnique :: Name
_AesGcmCtrV1_aadFileUnique = (String -> Name
Core.Name String
"aadFileUnique")
_AesGcmCtrV1_supplyAadPrefix :: Name
_AesGcmCtrV1_supplyAadPrefix = (String -> Name
Core.Name String
"supplyAadPrefix")
data EncryptionAlgorithm =
EncryptionAlgorithmAesGcmV1 AesGcmV1 |
EncryptionAlgorithmAesGcmCtrV1 AesGcmCtrV1
deriving (EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
(EncryptionAlgorithm -> EncryptionAlgorithm -> Bool)
-> (EncryptionAlgorithm -> EncryptionAlgorithm -> Bool)
-> Eq EncryptionAlgorithm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
== :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
$c/= :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
/= :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
Eq, Eq EncryptionAlgorithm
Eq EncryptionAlgorithm =>
(EncryptionAlgorithm -> EncryptionAlgorithm -> Ordering)
-> (EncryptionAlgorithm -> EncryptionAlgorithm -> Bool)
-> (EncryptionAlgorithm -> EncryptionAlgorithm -> Bool)
-> (EncryptionAlgorithm -> EncryptionAlgorithm -> Bool)
-> (EncryptionAlgorithm -> EncryptionAlgorithm -> Bool)
-> (EncryptionAlgorithm
-> EncryptionAlgorithm -> EncryptionAlgorithm)
-> (EncryptionAlgorithm
-> EncryptionAlgorithm -> EncryptionAlgorithm)
-> Ord EncryptionAlgorithm
EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
EncryptionAlgorithm -> EncryptionAlgorithm -> Ordering
EncryptionAlgorithm -> EncryptionAlgorithm -> EncryptionAlgorithm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EncryptionAlgorithm -> EncryptionAlgorithm -> Ordering
compare :: EncryptionAlgorithm -> EncryptionAlgorithm -> Ordering
$c< :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
< :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
$c<= :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
<= :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
$c> :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
> :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
$c>= :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
>= :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool
$cmax :: EncryptionAlgorithm -> EncryptionAlgorithm -> EncryptionAlgorithm
max :: EncryptionAlgorithm -> EncryptionAlgorithm -> EncryptionAlgorithm
$cmin :: EncryptionAlgorithm -> EncryptionAlgorithm -> EncryptionAlgorithm
min :: EncryptionAlgorithm -> EncryptionAlgorithm -> EncryptionAlgorithm
Ord, ReadPrec [EncryptionAlgorithm]
ReadPrec EncryptionAlgorithm
Int -> ReadS EncryptionAlgorithm
ReadS [EncryptionAlgorithm]
(Int -> ReadS EncryptionAlgorithm)
-> ReadS [EncryptionAlgorithm]
-> ReadPrec EncryptionAlgorithm
-> ReadPrec [EncryptionAlgorithm]
-> Read EncryptionAlgorithm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EncryptionAlgorithm
readsPrec :: Int -> ReadS EncryptionAlgorithm
$creadList :: ReadS [EncryptionAlgorithm]
readList :: ReadS [EncryptionAlgorithm]
$creadPrec :: ReadPrec EncryptionAlgorithm
readPrec :: ReadPrec EncryptionAlgorithm
$creadListPrec :: ReadPrec [EncryptionAlgorithm]
readListPrec :: ReadPrec [EncryptionAlgorithm]
Read, Int -> EncryptionAlgorithm -> ShowS
[EncryptionAlgorithm] -> ShowS
EncryptionAlgorithm -> String
(Int -> EncryptionAlgorithm -> ShowS)
-> (EncryptionAlgorithm -> String)
-> ([EncryptionAlgorithm] -> ShowS)
-> Show EncryptionAlgorithm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EncryptionAlgorithm -> ShowS
showsPrec :: Int -> EncryptionAlgorithm -> ShowS
$cshow :: EncryptionAlgorithm -> String
show :: EncryptionAlgorithm -> String
$cshowList :: [EncryptionAlgorithm] -> ShowS
showList :: [EncryptionAlgorithm] -> ShowS
Show)
_EncryptionAlgorithm :: Name
_EncryptionAlgorithm = (String -> Name
Core.Name String
"hydra/langs/parquet/format.EncryptionAlgorithm")
_EncryptionAlgorithm_aesGcmV1 :: Name
_EncryptionAlgorithm_aesGcmV1 = (String -> Name
Core.Name String
"aesGcmV1")
_EncryptionAlgorithm_aesGcmCtrV1 :: Name
_EncryptionAlgorithm_aesGcmCtrV1 = (String -> Name
Core.Name String
"aesGcmCtrV1")
data FileMetaData =
FileMetaData {
FileMetaData -> Int
fileMetaDataVersion :: Int,
FileMetaData -> [SchemaElement]
fileMetaDataSchema :: [SchemaElement],
FileMetaData -> Int64
fileMetaDataNumRows :: Int64,
FileMetaData -> [RowGroup]
fileMetaDataRowGroups :: [RowGroup],
FileMetaData -> Maybe [KeyValue]
fileMetaDataKeyValueMetadata :: (Maybe [KeyValue]),
FileMetaData -> Maybe String
fileMetaDataCreatedBy :: (Maybe String),
FileMetaData -> Maybe [ColumnOrder]
fileMetaDataColumnOrders :: (Maybe [ColumnOrder]),
FileMetaData -> Maybe EncryptionAlgorithm
fileMetaDataEncryptionAlgorithm :: (Maybe EncryptionAlgorithm),
:: (Maybe String)}
deriving (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, Eq FileMetaData
Eq FileMetaData =>
(FileMetaData -> FileMetaData -> Ordering)
-> (FileMetaData -> FileMetaData -> Bool)
-> (FileMetaData -> FileMetaData -> Bool)
-> (FileMetaData -> FileMetaData -> Bool)
-> (FileMetaData -> FileMetaData -> Bool)
-> (FileMetaData -> FileMetaData -> FileMetaData)
-> (FileMetaData -> FileMetaData -> FileMetaData)
-> Ord FileMetaData
FileMetaData -> FileMetaData -> Bool
FileMetaData -> FileMetaData -> Ordering
FileMetaData -> FileMetaData -> FileMetaData
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileMetaData -> FileMetaData -> Ordering
compare :: FileMetaData -> FileMetaData -> Ordering
$c< :: FileMetaData -> FileMetaData -> Bool
< :: FileMetaData -> FileMetaData -> Bool
$c<= :: FileMetaData -> FileMetaData -> Bool
<= :: FileMetaData -> FileMetaData -> Bool
$c> :: FileMetaData -> FileMetaData -> Bool
> :: FileMetaData -> FileMetaData -> Bool
$c>= :: FileMetaData -> FileMetaData -> Bool
>= :: FileMetaData -> FileMetaData -> Bool
$cmax :: FileMetaData -> FileMetaData -> FileMetaData
max :: FileMetaData -> FileMetaData -> FileMetaData
$cmin :: FileMetaData -> FileMetaData -> FileMetaData
min :: FileMetaData -> FileMetaData -> FileMetaData
Ord, ReadPrec [FileMetaData]
ReadPrec FileMetaData
Int -> ReadS FileMetaData
ReadS [FileMetaData]
(Int -> ReadS FileMetaData)
-> ReadS [FileMetaData]
-> ReadPrec FileMetaData
-> ReadPrec [FileMetaData]
-> Read FileMetaData
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FileMetaData
readsPrec :: Int -> ReadS FileMetaData
$creadList :: ReadS [FileMetaData]
readList :: ReadS [FileMetaData]
$creadPrec :: ReadPrec FileMetaData
readPrec :: ReadPrec FileMetaData
$creadListPrec :: ReadPrec [FileMetaData]
readListPrec :: ReadPrec [FileMetaData]
Read, Int -> FileMetaData -> ShowS
[FileMetaData] -> ShowS
FileMetaData -> String
(Int -> FileMetaData -> ShowS)
-> (FileMetaData -> String)
-> ([FileMetaData] -> ShowS)
-> Show FileMetaData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileMetaData -> ShowS
showsPrec :: Int -> FileMetaData -> ShowS
$cshow :: FileMetaData -> String
show :: FileMetaData -> String
$cshowList :: [FileMetaData] -> ShowS
showList :: [FileMetaData] -> ShowS
Show)
_FileMetaData :: Name
_FileMetaData = (String -> Name
Core.Name String
"hydra/langs/parquet/format.FileMetaData")
_FileMetaData_version :: Name
_FileMetaData_version = (String -> Name
Core.Name String
"version")
_FileMetaData_schema :: Name
_FileMetaData_schema = (String -> Name
Core.Name String
"schema")
_FileMetaData_numRows :: Name
_FileMetaData_numRows = (String -> Name
Core.Name String
"numRows")
_FileMetaData_rowGroups :: Name
_FileMetaData_rowGroups = (String -> Name
Core.Name String
"rowGroups")
_FileMetaData_keyValueMetadata :: Name
_FileMetaData_keyValueMetadata = (String -> Name
Core.Name String
"keyValueMetadata")
_FileMetaData_createdBy :: Name
_FileMetaData_createdBy = (String -> Name
Core.Name String
"createdBy")
_FileMetaData_columnOrders :: Name
_FileMetaData_columnOrders = (String -> Name
Core.Name String
"columnOrders")
_FileMetaData_encryptionAlgorithm :: Name
_FileMetaData_encryptionAlgorithm = (String -> Name
Core.Name String
"encryptionAlgorithm")
= (String -> Name
Core.Name String
"footerSigningKeyMetadata")
data FileCryptoMetaData =
FileCryptoMetaData {
FileCryptoMetaData -> EncryptionAlgorithm
fileCryptoMetaDataEncryptionAlgorithm :: EncryptionAlgorithm,
FileCryptoMetaData -> Maybe String
fileCryptoMetaDataKeyMetadata :: (Maybe String)}
deriving (FileCryptoMetaData -> FileCryptoMetaData -> Bool
(FileCryptoMetaData -> FileCryptoMetaData -> Bool)
-> (FileCryptoMetaData -> FileCryptoMetaData -> Bool)
-> Eq FileCryptoMetaData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
== :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
$c/= :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
/= :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
Eq, Eq FileCryptoMetaData
Eq FileCryptoMetaData =>
(FileCryptoMetaData -> FileCryptoMetaData -> Ordering)
-> (FileCryptoMetaData -> FileCryptoMetaData -> Bool)
-> (FileCryptoMetaData -> FileCryptoMetaData -> Bool)
-> (FileCryptoMetaData -> FileCryptoMetaData -> Bool)
-> (FileCryptoMetaData -> FileCryptoMetaData -> Bool)
-> (FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData)
-> (FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData)
-> Ord FileCryptoMetaData
FileCryptoMetaData -> FileCryptoMetaData -> Bool
FileCryptoMetaData -> FileCryptoMetaData -> Ordering
FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileCryptoMetaData -> FileCryptoMetaData -> Ordering
compare :: FileCryptoMetaData -> FileCryptoMetaData -> Ordering
$c< :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
< :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
$c<= :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
<= :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
$c> :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
> :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
$c>= :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
>= :: FileCryptoMetaData -> FileCryptoMetaData -> Bool
$cmax :: FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData
max :: FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData
$cmin :: FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData
min :: FileCryptoMetaData -> FileCryptoMetaData -> FileCryptoMetaData
Ord, ReadPrec [FileCryptoMetaData]
ReadPrec FileCryptoMetaData
Int -> ReadS FileCryptoMetaData
ReadS [FileCryptoMetaData]
(Int -> ReadS FileCryptoMetaData)
-> ReadS [FileCryptoMetaData]
-> ReadPrec FileCryptoMetaData
-> ReadPrec [FileCryptoMetaData]
-> Read FileCryptoMetaData
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FileCryptoMetaData
readsPrec :: Int -> ReadS FileCryptoMetaData
$creadList :: ReadS [FileCryptoMetaData]
readList :: ReadS [FileCryptoMetaData]
$creadPrec :: ReadPrec FileCryptoMetaData
readPrec :: ReadPrec FileCryptoMetaData
$creadListPrec :: ReadPrec [FileCryptoMetaData]
readListPrec :: ReadPrec [FileCryptoMetaData]
Read, Int -> FileCryptoMetaData -> ShowS
[FileCryptoMetaData] -> ShowS
FileCryptoMetaData -> String
(Int -> FileCryptoMetaData -> ShowS)
-> (FileCryptoMetaData -> String)
-> ([FileCryptoMetaData] -> ShowS)
-> Show FileCryptoMetaData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileCryptoMetaData -> ShowS
showsPrec :: Int -> FileCryptoMetaData -> ShowS
$cshow :: FileCryptoMetaData -> String
show :: FileCryptoMetaData -> String
$cshowList :: [FileCryptoMetaData] -> ShowS
showList :: [FileCryptoMetaData] -> ShowS
Show)
_FileCryptoMetaData :: Name
_FileCryptoMetaData = (String -> Name
Core.Name String
"hydra/langs/parquet/format.FileCryptoMetaData")
_FileCryptoMetaData_encryptionAlgorithm :: Name
_FileCryptoMetaData_encryptionAlgorithm = (String -> Name
Core.Name String
"encryptionAlgorithm")
_FileCryptoMetaData_keyMetadata :: Name
_FileCryptoMetaData_keyMetadata = (String -> Name
Core.Name String
"keyMetadata")