module Hydra.Langs.Parquet.Delta 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 ArrayType =
ArrayType {
ArrayType -> DataType
arrayTypeElementType :: DataType,
ArrayType -> Bool
arrayTypeContainsNull :: Bool}
deriving (ArrayType -> ArrayType -> Bool
(ArrayType -> ArrayType -> Bool)
-> (ArrayType -> ArrayType -> Bool) -> Eq ArrayType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArrayType -> ArrayType -> Bool
== :: ArrayType -> ArrayType -> Bool
$c/= :: ArrayType -> ArrayType -> Bool
/= :: ArrayType -> ArrayType -> Bool
Eq, Eq ArrayType
Eq ArrayType =>
(ArrayType -> ArrayType -> Ordering)
-> (ArrayType -> ArrayType -> Bool)
-> (ArrayType -> ArrayType -> Bool)
-> (ArrayType -> ArrayType -> Bool)
-> (ArrayType -> ArrayType -> Bool)
-> (ArrayType -> ArrayType -> ArrayType)
-> (ArrayType -> ArrayType -> ArrayType)
-> Ord ArrayType
ArrayType -> ArrayType -> Bool
ArrayType -> ArrayType -> Ordering
ArrayType -> ArrayType -> ArrayType
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 :: ArrayType -> ArrayType -> Ordering
compare :: ArrayType -> ArrayType -> Ordering
$c< :: ArrayType -> ArrayType -> Bool
< :: ArrayType -> ArrayType -> Bool
$c<= :: ArrayType -> ArrayType -> Bool
<= :: ArrayType -> ArrayType -> Bool
$c> :: ArrayType -> ArrayType -> Bool
> :: ArrayType -> ArrayType -> Bool
$c>= :: ArrayType -> ArrayType -> Bool
>= :: ArrayType -> ArrayType -> Bool
$cmax :: ArrayType -> ArrayType -> ArrayType
max :: ArrayType -> ArrayType -> ArrayType
$cmin :: ArrayType -> ArrayType -> ArrayType
min :: ArrayType -> ArrayType -> ArrayType
Ord, ReadPrec [ArrayType]
ReadPrec ArrayType
Int -> ReadS ArrayType
ReadS [ArrayType]
(Int -> ReadS ArrayType)
-> ReadS [ArrayType]
-> ReadPrec ArrayType
-> ReadPrec [ArrayType]
-> Read ArrayType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ArrayType
readsPrec :: Int -> ReadS ArrayType
$creadList :: ReadS [ArrayType]
readList :: ReadS [ArrayType]
$creadPrec :: ReadPrec ArrayType
readPrec :: ReadPrec ArrayType
$creadListPrec :: ReadPrec [ArrayType]
readListPrec :: ReadPrec [ArrayType]
Read, Int -> ArrayType -> ShowS
[ArrayType] -> ShowS
ArrayType -> String
(Int -> ArrayType -> ShowS)
-> (ArrayType -> String)
-> ([ArrayType] -> ShowS)
-> Show ArrayType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ArrayType -> ShowS
showsPrec :: Int -> ArrayType -> ShowS
$cshow :: ArrayType -> String
show :: ArrayType -> String
$cshowList :: [ArrayType] -> ShowS
showList :: [ArrayType] -> ShowS
Show)
_ArrayType :: Name
_ArrayType = (String -> Name
Core.Name String
"hydra/langs/parquet/delta.ArrayType")
_ArrayType_elementType :: Name
_ArrayType_elementType = (String -> Name
Core.Name String
"elementType")
_ArrayType_containsNull :: Name
_ArrayType_containsNull = (String -> Name
Core.Name String
"containsNull")
data DataType =
DataTypeArray ArrayType |
DataTypeBinary |
DataTypeBoolean |
DataTypeByte |
DataTypeDate |
DataTypeDecimal DecimalType |
DataTypeDouble |
DataTypeFloat |
DataTypeInteger |
DataTypeLong |
DataTypeMap MapType |
DataTypeNull |
DataTypeShort |
DataTypeString |
DataTypeStruct StructType
deriving (DataType -> DataType -> Bool
(DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool) -> Eq DataType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataType -> DataType -> Bool
== :: DataType -> DataType -> Bool
$c/= :: DataType -> DataType -> Bool
/= :: DataType -> DataType -> Bool
Eq, Eq DataType
Eq DataType =>
(DataType -> DataType -> Ordering)
-> (DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool)
-> (DataType -> DataType -> DataType)
-> (DataType -> DataType -> DataType)
-> Ord DataType
DataType -> DataType -> Bool
DataType -> DataType -> Ordering
DataType -> DataType -> DataType
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 :: DataType -> DataType -> Ordering
compare :: DataType -> DataType -> Ordering
$c< :: DataType -> DataType -> Bool
< :: DataType -> DataType -> Bool
$c<= :: DataType -> DataType -> Bool
<= :: DataType -> DataType -> Bool
$c> :: DataType -> DataType -> Bool
> :: DataType -> DataType -> Bool
$c>= :: DataType -> DataType -> Bool
>= :: DataType -> DataType -> Bool
$cmax :: DataType -> DataType -> DataType
max :: DataType -> DataType -> DataType
$cmin :: DataType -> DataType -> DataType
min :: DataType -> DataType -> DataType
Ord, ReadPrec [DataType]
ReadPrec DataType
Int -> ReadS DataType
ReadS [DataType]
(Int -> ReadS DataType)
-> ReadS [DataType]
-> ReadPrec DataType
-> ReadPrec [DataType]
-> Read DataType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataType
readsPrec :: Int -> ReadS DataType
$creadList :: ReadS [DataType]
readList :: ReadS [DataType]
$creadPrec :: ReadPrec DataType
readPrec :: ReadPrec DataType
$creadListPrec :: ReadPrec [DataType]
readListPrec :: ReadPrec [DataType]
Read, Int -> DataType -> ShowS
[DataType] -> ShowS
DataType -> String
(Int -> DataType -> ShowS)
-> (DataType -> String) -> ([DataType] -> ShowS) -> Show DataType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataType -> ShowS
showsPrec :: Int -> DataType -> ShowS
$cshow :: DataType -> String
show :: DataType -> String
$cshowList :: [DataType] -> ShowS
showList :: [DataType] -> ShowS
Show)
_DataType :: Name
_DataType = (String -> Name
Core.Name String
"hydra/langs/parquet/delta.DataType")
_DataType_array :: Name
_DataType_array = (String -> Name
Core.Name String
"array")
_DataType_binary :: Name
_DataType_binary = (String -> Name
Core.Name String
"binary")
_DataType_boolean :: Name
_DataType_boolean = (String -> Name
Core.Name String
"boolean")
_DataType_byte :: Name
_DataType_byte = (String -> Name
Core.Name String
"byte")
_DataType_date :: Name
_DataType_date = (String -> Name
Core.Name String
"date")
_DataType_decimal :: Name
_DataType_decimal = (String -> Name
Core.Name String
"decimal")
_DataType_double :: Name
_DataType_double = (String -> Name
Core.Name String
"double")
_DataType_float :: Name
_DataType_float = (String -> Name
Core.Name String
"float")
_DataType_integer :: Name
_DataType_integer = (String -> Name
Core.Name String
"integer")
_DataType_long :: Name
_DataType_long = (String -> Name
Core.Name String
"long")
_DataType_map :: Name
_DataType_map = (String -> Name
Core.Name String
"map")
_DataType_null :: Name
_DataType_null = (String -> Name
Core.Name String
"null")
_DataType_short :: Name
_DataType_short = (String -> Name
Core.Name String
"short")
_DataType_string :: Name
_DataType_string = (String -> Name
Core.Name String
"string")
_DataType_struct :: Name
_DataType_struct = (String -> Name
Core.Name String
"struct")
data DecimalType =
DecimalType {
DecimalType -> Int
decimalTypePrecision :: Int,
DecimalType -> Int
decimalTypeScale :: 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/delta.DecimalType")
_DecimalType_precision :: Name
_DecimalType_precision = (String -> Name
Core.Name String
"precision")
_DecimalType_scale :: Name
_DecimalType_scale = (String -> Name
Core.Name String
"scale")
data MapType =
MapType {
MapType -> DataType
mapTypeKeyType :: DataType,
MapType -> DataType
mapTypeValueType :: DataType,
MapType -> Bool
mapTypeValueContainsNull :: Bool}
deriving (MapType -> MapType -> Bool
(MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool) -> Eq MapType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MapType -> MapType -> Bool
== :: MapType -> MapType -> Bool
$c/= :: MapType -> MapType -> Bool
/= :: MapType -> MapType -> Bool
Eq, Eq MapType
Eq MapType =>
(MapType -> MapType -> Ordering)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> MapType)
-> (MapType -> MapType -> MapType)
-> Ord MapType
MapType -> MapType -> Bool
MapType -> MapType -> Ordering
MapType -> MapType -> MapType
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 :: MapType -> MapType -> Ordering
compare :: MapType -> MapType -> Ordering
$c< :: MapType -> MapType -> Bool
< :: MapType -> MapType -> Bool
$c<= :: MapType -> MapType -> Bool
<= :: MapType -> MapType -> Bool
$c> :: MapType -> MapType -> Bool
> :: MapType -> MapType -> Bool
$c>= :: MapType -> MapType -> Bool
>= :: MapType -> MapType -> Bool
$cmax :: MapType -> MapType -> MapType
max :: MapType -> MapType -> MapType
$cmin :: MapType -> MapType -> MapType
min :: MapType -> MapType -> MapType
Ord, ReadPrec [MapType]
ReadPrec MapType
Int -> ReadS MapType
ReadS [MapType]
(Int -> ReadS MapType)
-> ReadS [MapType]
-> ReadPrec MapType
-> ReadPrec [MapType]
-> Read MapType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MapType
readsPrec :: Int -> ReadS MapType
$creadList :: ReadS [MapType]
readList :: ReadS [MapType]
$creadPrec :: ReadPrec MapType
readPrec :: ReadPrec MapType
$creadListPrec :: ReadPrec [MapType]
readListPrec :: ReadPrec [MapType]
Read, Int -> MapType -> ShowS
[MapType] -> ShowS
MapType -> String
(Int -> MapType -> ShowS)
-> (MapType -> String) -> ([MapType] -> ShowS) -> Show MapType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MapType -> ShowS
showsPrec :: Int -> MapType -> ShowS
$cshow :: MapType -> String
show :: MapType -> String
$cshowList :: [MapType] -> ShowS
showList :: [MapType] -> ShowS
Show)
_MapType :: Name
_MapType = (String -> Name
Core.Name String
"hydra/langs/parquet/delta.MapType")
_MapType_keyType :: Name
_MapType_keyType = (String -> Name
Core.Name String
"keyType")
_MapType_valueType :: Name
_MapType_valueType = (String -> Name
Core.Name String
"valueType")
_MapType_valueContainsNull :: Name
_MapType_valueContainsNull = (String -> Name
Core.Name String
"valueContainsNull")
data StructField =
StructField {
StructField -> String
structFieldName :: String,
StructField -> DataType
structFieldDataType :: DataType,
StructField -> Bool
structFieldNullable :: Bool}
deriving (StructField -> StructField -> Bool
(StructField -> StructField -> Bool)
-> (StructField -> StructField -> Bool) -> Eq StructField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StructField -> StructField -> Bool
== :: StructField -> StructField -> Bool
$c/= :: StructField -> StructField -> Bool
/= :: StructField -> StructField -> Bool
Eq, Eq StructField
Eq StructField =>
(StructField -> StructField -> Ordering)
-> (StructField -> StructField -> Bool)
-> (StructField -> StructField -> Bool)
-> (StructField -> StructField -> Bool)
-> (StructField -> StructField -> Bool)
-> (StructField -> StructField -> StructField)
-> (StructField -> StructField -> StructField)
-> Ord StructField
StructField -> StructField -> Bool
StructField -> StructField -> Ordering
StructField -> StructField -> StructField
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 :: StructField -> StructField -> Ordering
compare :: StructField -> StructField -> Ordering
$c< :: StructField -> StructField -> Bool
< :: StructField -> StructField -> Bool
$c<= :: StructField -> StructField -> Bool
<= :: StructField -> StructField -> Bool
$c> :: StructField -> StructField -> Bool
> :: StructField -> StructField -> Bool
$c>= :: StructField -> StructField -> Bool
>= :: StructField -> StructField -> Bool
$cmax :: StructField -> StructField -> StructField
max :: StructField -> StructField -> StructField
$cmin :: StructField -> StructField -> StructField
min :: StructField -> StructField -> StructField
Ord, ReadPrec [StructField]
ReadPrec StructField
Int -> ReadS StructField
ReadS [StructField]
(Int -> ReadS StructField)
-> ReadS [StructField]
-> ReadPrec StructField
-> ReadPrec [StructField]
-> Read StructField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StructField
readsPrec :: Int -> ReadS StructField
$creadList :: ReadS [StructField]
readList :: ReadS [StructField]
$creadPrec :: ReadPrec StructField
readPrec :: ReadPrec StructField
$creadListPrec :: ReadPrec [StructField]
readListPrec :: ReadPrec [StructField]
Read, Int -> StructField -> ShowS
[StructField] -> ShowS
StructField -> String
(Int -> StructField -> ShowS)
-> (StructField -> String)
-> ([StructField] -> ShowS)
-> Show StructField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StructField -> ShowS
showsPrec :: Int -> StructField -> ShowS
$cshow :: StructField -> String
show :: StructField -> String
$cshowList :: [StructField] -> ShowS
showList :: [StructField] -> ShowS
Show)
_StructField :: Name
_StructField = (String -> Name
Core.Name String
"hydra/langs/parquet/delta.StructField")
_StructField_name :: Name
_StructField_name = (String -> Name
Core.Name String
"name")
_StructField_dataType :: Name
_StructField_dataType = (String -> Name
Core.Name String
"dataType")
_StructField_nullable :: Name
_StructField_nullable = (String -> Name
Core.Name String
"nullable")
data StructType =
StructType {
StructType -> [StructField]
structTypeFields :: [StructField]}
deriving (StructType -> StructType -> Bool
(StructType -> StructType -> Bool)
-> (StructType -> StructType -> Bool) -> Eq StructType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StructType -> StructType -> Bool
== :: StructType -> StructType -> Bool
$c/= :: StructType -> StructType -> Bool
/= :: StructType -> StructType -> Bool
Eq, Eq StructType
Eq StructType =>
(StructType -> StructType -> Ordering)
-> (StructType -> StructType -> Bool)
-> (StructType -> StructType -> Bool)
-> (StructType -> StructType -> Bool)
-> (StructType -> StructType -> Bool)
-> (StructType -> StructType -> StructType)
-> (StructType -> StructType -> StructType)
-> Ord StructType
StructType -> StructType -> Bool
StructType -> StructType -> Ordering
StructType -> StructType -> StructType
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 :: StructType -> StructType -> Ordering
compare :: StructType -> StructType -> Ordering
$c< :: StructType -> StructType -> Bool
< :: StructType -> StructType -> Bool
$c<= :: StructType -> StructType -> Bool
<= :: StructType -> StructType -> Bool
$c> :: StructType -> StructType -> Bool
> :: StructType -> StructType -> Bool
$c>= :: StructType -> StructType -> Bool
>= :: StructType -> StructType -> Bool
$cmax :: StructType -> StructType -> StructType
max :: StructType -> StructType -> StructType
$cmin :: StructType -> StructType -> StructType
min :: StructType -> StructType -> StructType
Ord, ReadPrec [StructType]
ReadPrec StructType
Int -> ReadS StructType
ReadS [StructType]
(Int -> ReadS StructType)
-> ReadS [StructType]
-> ReadPrec StructType
-> ReadPrec [StructType]
-> Read StructType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StructType
readsPrec :: Int -> ReadS StructType
$creadList :: ReadS [StructType]
readList :: ReadS [StructType]
$creadPrec :: ReadPrec StructType
readPrec :: ReadPrec StructType
$creadListPrec :: ReadPrec [StructType]
readListPrec :: ReadPrec [StructType]
Read, Int -> StructType -> ShowS
[StructType] -> ShowS
StructType -> String
(Int -> StructType -> ShowS)
-> (StructType -> String)
-> ([StructType] -> ShowS)
-> Show StructType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StructType -> ShowS
showsPrec :: Int -> StructType -> ShowS
$cshow :: StructType -> String
show :: StructType -> String
$cshowList :: [StructType] -> ShowS
showList :: [StructType] -> ShowS
Show)
_StructType :: Name
_StructType = (String -> Name
Core.Name String
"hydra/langs/parquet/delta.StructType")
_StructType_fields :: Name
_StructType_fields = (String -> Name
Core.Name String
"fields")