module DataFrame.IO.Parquet.ColumnStatistics where import Data.Int import Data.Word data ColumnStatistics = ColumnStatistics { ColumnStatistics -> [Word8] columnMin :: [Word8] , ColumnStatistics -> [Word8] columnMax :: [Word8] , ColumnStatistics -> Int64 columnNullCount :: Int64 , ColumnStatistics -> Int64 columnDistictCount :: Int64 , ColumnStatistics -> [Word8] columnMinValue :: [Word8] , ColumnStatistics -> [Word8] columnMaxValue :: [Word8] , ColumnStatistics -> Bool isColumnMaxValueExact :: Bool , ColumnStatistics -> Bool isColumnMinValueExact :: Bool } deriving (Int -> ColumnStatistics -> ShowS [ColumnStatistics] -> ShowS ColumnStatistics -> String (Int -> ColumnStatistics -> ShowS) -> (ColumnStatistics -> String) -> ([ColumnStatistics] -> ShowS) -> Show ColumnStatistics forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> ColumnStatistics -> ShowS showsPrec :: Int -> ColumnStatistics -> ShowS $cshow :: ColumnStatistics -> String show :: ColumnStatistics -> String $cshowList :: [ColumnStatistics] -> ShowS showList :: [ColumnStatistics] -> ShowS Show, ColumnStatistics -> ColumnStatistics -> Bool (ColumnStatistics -> ColumnStatistics -> Bool) -> (ColumnStatistics -> ColumnStatistics -> Bool) -> Eq ColumnStatistics forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: ColumnStatistics -> ColumnStatistics -> Bool == :: ColumnStatistics -> ColumnStatistics -> Bool $c/= :: ColumnStatistics -> ColumnStatistics -> Bool /= :: ColumnStatistics -> ColumnStatistics -> Bool Eq) emptyColumnStatistics :: ColumnStatistics emptyColumnStatistics :: ColumnStatistics emptyColumnStatistics = [Word8] -> [Word8] -> Int64 -> Int64 -> [Word8] -> [Word8] -> Bool -> Bool -> ColumnStatistics ColumnStatistics [] [] Int64 0 Int64 0 [] [] Bool False Bool False