{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Bindings.HDF5.Datatype.Internal where
import Data.Int
import Data.Word
import Foreign.C.Types
import Bindings.HDF5.Core
import Bindings.HDF5.Object
import Bindings.HDF5.Raw
import Data.Tagged
import Foreign.Storable
newtype Datatype = Datatype HId_t
    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, Datatype -> HId_t
(Datatype -> HId_t) -> HId Datatype
forall t. (t -> HId_t) -> HId t
$chid :: Datatype -> HId_t
hid :: Datatype -> HId_t
HId, HId_t -> Datatype
(HId_t -> Datatype) -> FromHId Datatype
forall t. (HId_t -> t) -> FromHId t
$cuncheckedFromHId :: HId_t -> Datatype
uncheckedFromHId :: HId_t -> Datatype
FromHId, Datatype -> Bool
(Datatype -> Bool) -> HDFResultType Datatype
forall t. (t -> Bool) -> HDFResultType t
$cisError :: Datatype -> Bool
isError :: Datatype -> Bool
HDFResultType)
instance Object Datatype where
    staticObjectType :: Tagged Datatype (Maybe ObjectType)
staticObjectType = Maybe ObjectType -> Tagged Datatype (Maybe ObjectType)
forall {k} (s :: k) b. b -> Tagged s b
Tagged (ObjectType -> Maybe ObjectType
forall a. a -> Maybe a
Just ObjectType
DatatypeObj)
class Storable t => NativeType t where
    nativeTypeId :: Tagged t Datatype
instance NativeType CChar where
    nativeTypeId :: Tagged CChar Datatype
nativeTypeId = Datatype -> Tagged CChar Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_CHAR)
instance NativeType CSChar where
    nativeTypeId :: Tagged CSChar Datatype
nativeTypeId = Datatype -> Tagged CSChar Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_SCHAR)
instance NativeType CUChar where
    nativeTypeId :: Tagged CUChar Datatype
nativeTypeId = Datatype -> Tagged CUChar Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_UCHAR)
instance NativeType CShort where
    nativeTypeId :: Tagged CShort Datatype
nativeTypeId = Datatype -> Tagged CShort Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_SHORT)
instance NativeType CUShort where
    nativeTypeId :: Tagged CUShort Datatype
nativeTypeId = Datatype -> Tagged CUShort Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_USHORT)
instance NativeType CInt where
    nativeTypeId :: Tagged CInt Datatype
nativeTypeId = Datatype -> Tagged CInt Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_INT)
instance NativeType CUInt where
    nativeTypeId :: Tagged CUInt Datatype
nativeTypeId = Datatype -> Tagged CUInt Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_UINT)
instance NativeType CLong where
    nativeTypeId :: Tagged CLong Datatype
nativeTypeId = Datatype -> Tagged CLong Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_LONG)
instance NativeType CULong where
    nativeTypeId :: Tagged CULong Datatype
nativeTypeId = Datatype -> Tagged CULong Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_ULONG)
instance NativeType CLLong where
    nativeTypeId :: Tagged CLLong Datatype
nativeTypeId = Datatype -> Tagged CLLong Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_LLONG)
instance NativeType CULLong where
    nativeTypeId :: Tagged CULLong Datatype
nativeTypeId = Datatype -> Tagged CULLong Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_ULLONG)
instance NativeType CFloat where
    nativeTypeId :: Tagged CFloat Datatype
nativeTypeId = Datatype -> Tagged CFloat Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_FLOAT)
instance NativeType CDouble where
    nativeTypeId :: Tagged CDouble Datatype
nativeTypeId = Datatype -> Tagged CDouble Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_DOUBLE)
instance NativeType HAddr where
    nativeTypeId :: Tagged HAddr Datatype
nativeTypeId = Datatype -> Tagged HAddr Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_HADDR)
instance NativeType HSize where
    nativeTypeId :: Tagged HSize Datatype
nativeTypeId = Datatype -> Tagged HSize Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_HSIZE)
instance NativeType HSSize where
    nativeTypeId :: Tagged HSSize Datatype
nativeTypeId = Datatype -> Tagged HSSize Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_HSSIZE)
instance NativeType HErr_t where
    nativeTypeId :: Tagged HErr_t Datatype
nativeTypeId = Datatype -> Tagged HErr_t Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_HERR)
instance NativeType HBool_t where
    nativeTypeId :: Tagged HBool_t Datatype
nativeTypeId = Datatype -> Tagged HBool_t Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_HBOOL)
instance NativeType Int8 where
    nativeTypeId :: Tagged Int8 Datatype
nativeTypeId = Datatype -> Tagged Int8 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_INT8)
instance NativeType Int16 where
    nativeTypeId :: Tagged Int16 Datatype
nativeTypeId = Datatype -> Tagged Int16 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_INT16)
instance NativeType Int32 where
    nativeTypeId :: Tagged Int32 Datatype
nativeTypeId = Datatype -> Tagged Int32 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_INT32)
instance NativeType Int64 where
    nativeTypeId :: Tagged Int64 Datatype
nativeTypeId = Datatype -> Tagged Int64 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_INT64)
instance NativeType Word8 where
    nativeTypeId :: Tagged Word8 Datatype
nativeTypeId = Datatype -> Tagged Word8 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_UINT8)
instance NativeType Word16 where
    nativeTypeId :: Tagged Word16 Datatype
nativeTypeId = Datatype -> Tagged Word16 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_UINT16)
instance NativeType Word32 where
    nativeTypeId :: Tagged Word32 Datatype
nativeTypeId = Datatype -> Tagged Word32 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_UINT32)
instance NativeType Word64 where
    nativeTypeId :: Tagged Word64 Datatype
nativeTypeId = Datatype -> Tagged Word64 Datatype
forall {k} (s :: k) b. b -> Tagged s b
Tagged (HId_t -> Datatype
Datatype HId_t
h5t_NATIVE_UINT64)
if  isIEEE (0 :: Float)
    && floatRadix  (0 :: Float) == 2
    && floatDigits (0 :: Float) == 24
    && floatRange  (0 :: Float) == (-125,128)
    then [d| instance NativeType Float where nativeTypeId = Tagged (Datatype h5t_NATIVE_FLOAT) |]
    else [d| |]
if  isIEEE (0 :: Double)
    && floatRadix  (0 :: Double) == 2
    && floatDigits (0 :: Double) == 53
    && floatRange  (0 :: Double) == (-1021,1024)
    then [d| instance NativeType Double where nativeTypeId = Tagged (Datatype h5t_NATIVE_DOUBLE) |]
    else [d| |]
case sizeOf (0 :: Int) of
    1   -> [d| instance NativeType Int where nativeTypeId = Tagged (Datatype h5t_NATIVE_INT8) |]
    2   -> [d| instance NativeType Int where nativeTypeId = Tagged (Datatype h5t_NATIVE_INT16) |]
    4   -> [d| instance NativeType Int where nativeTypeId = Tagged (Datatype h5t_NATIVE_INT32) |]
    8   -> [d| instance NativeType Int where nativeTypeId = Tagged (Datatype h5t_NATIVE_INT64) |]
    _   -> [d| |]
case sizeOf (0 :: Word) of
    1   -> [d| instance NativeType Word where nativeTypeId = Tagged (Datatype h5t_NATIVE_UINT8) |]
    2   -> [d| instance NativeType Word where nativeTypeId = Tagged (Datatype h5t_NATIVE_UINT16) |]
    4   -> [d| instance NativeType Word where nativeTypeId = Tagged (Datatype h5t_NATIVE_UINT32) |]
    8   -> [d| instance NativeType Word where nativeTypeId = Tagged (Datatype h5t_NATIVE_UINT64) |]
    _   -> [d| |]
nativeTypeOf :: NativeType t => t -> Datatype
nativeTypeOf :: forall t. NativeType t => t -> Datatype
nativeTypeOf t
it = t -> Tagged t Datatype -> Datatype
forall t a. t -> Tagged t a -> a
untagAs t
it Tagged t Datatype
forall t. NativeType t => Tagged t Datatype
nativeTypeId
    where
        untagAs :: t -> Tagged t a -> a
        untagAs :: forall t a. t -> Tagged t a -> a
untagAs t
_ = Tagged t a -> a
forall {k} (s :: k) b. Tagged s b -> b
untag
nativeTypeOf1 :: NativeType t => f t -> Datatype
nativeTypeOf1 :: forall t (f :: * -> *). NativeType t => f t -> Datatype
nativeTypeOf1 f t
it = f t -> Tagged t Datatype -> Datatype
forall (f :: * -> *) t a. f t -> Tagged t a -> a
untagAs1 f t
it Tagged t Datatype
forall t. NativeType t => Tagged t Datatype
nativeTypeId
    where
        untagAs1 :: f t -> Tagged t a -> a
        untagAs1 :: forall (f :: * -> *) t a. f t -> Tagged t a -> a
untagAs1 f t
_ = Tagged t a -> a
forall {k} (s :: k) b. Tagged s b -> b
untag
hdfTypeOf :: NativeType t => t -> HId_t
hdfTypeOf :: forall t. NativeType t => t -> HId_t
hdfTypeOf = Datatype -> HId_t
forall t. HId t => t -> HId_t
hid (Datatype -> HId_t) -> (t -> Datatype) -> t -> HId_t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Datatype
forall t. NativeType t => t -> Datatype
nativeTypeOf
hdfTypeOf1 :: NativeType t => f t -> HId_t
hdfTypeOf1 :: forall t (f :: * -> *). NativeType t => f t -> HId_t
hdfTypeOf1 = Datatype -> HId_t
forall t. HId t => t -> HId_t
hid (Datatype -> HId_t) -> (f t -> Datatype) -> f t -> HId_t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f t -> Datatype
forall t (f :: * -> *). NativeType t => f t -> Datatype
nativeTypeOf1
data Class
    = Integer
    | Float
    | Time
    | String
    | BitField
    | Opaque
    | Compound
    | Reference
    | Enum
    | VLen
    | Array
    deriving (Class -> Class -> Bool
(Class -> Class -> Bool) -> (Class -> Class -> Bool) -> Eq Class
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Class -> Class -> Bool
== :: Class -> Class -> Bool
$c/= :: Class -> Class -> Bool
/= :: Class -> Class -> Bool
Eq, Eq Class
Eq Class =>
(Class -> Class -> Ordering)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Class)
-> (Class -> Class -> Class)
-> Ord Class
Class -> Class -> Bool
Class -> Class -> Ordering
Class -> Class -> Class
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 :: Class -> Class -> Ordering
compare :: Class -> Class -> Ordering
$c< :: Class -> Class -> Bool
< :: Class -> Class -> Bool
$c<= :: Class -> Class -> Bool
<= :: Class -> Class -> Bool
$c> :: Class -> Class -> Bool
> :: Class -> Class -> Bool
$c>= :: Class -> Class -> Bool
>= :: Class -> Class -> Bool
$cmax :: Class -> Class -> Class
max :: Class -> Class -> Class
$cmin :: Class -> Class -> Class
min :: Class -> Class -> Class
Ord, Int -> Class
Class -> Int
Class -> [Class]
Class -> Class
Class -> Class -> [Class]
Class -> Class -> Class -> [Class]
(Class -> Class)
-> (Class -> Class)
-> (Int -> Class)
-> (Class -> Int)
-> (Class -> [Class])
-> (Class -> Class -> [Class])
-> (Class -> Class -> [Class])
-> (Class -> Class -> Class -> [Class])
-> Enum Class
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Class -> Class
succ :: Class -> Class
$cpred :: Class -> Class
pred :: Class -> Class
$ctoEnum :: Int -> Class
toEnum :: Int -> Class
$cfromEnum :: Class -> Int
fromEnum :: Class -> Int
$cenumFrom :: Class -> [Class]
enumFrom :: Class -> [Class]
$cenumFromThen :: Class -> Class -> [Class]
enumFromThen :: Class -> Class -> [Class]
$cenumFromTo :: Class -> Class -> [Class]
enumFromTo :: Class -> Class -> [Class]
$cenumFromThenTo :: Class -> Class -> Class -> [Class]
enumFromThenTo :: Class -> Class -> Class -> [Class]
Enum, Class
Class -> Class -> Bounded Class
forall a. a -> a -> Bounded a
$cminBound :: Class
minBound :: Class
$cmaxBound :: Class
maxBound :: Class
Bounded, ReadPrec [Class]
ReadPrec Class
Int -> ReadS Class
ReadS [Class]
(Int -> ReadS Class)
-> ReadS [Class]
-> ReadPrec Class
-> ReadPrec [Class]
-> Read Class
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Class
readsPrec :: Int -> ReadS Class
$creadList :: ReadS [Class]
readList :: ReadS [Class]
$creadPrec :: ReadPrec Class
readPrec :: ReadPrec Class
$creadListPrec :: ReadPrec [Class]
readListPrec :: ReadPrec [Class]
Read, Int -> Class -> ShowS
[Class] -> ShowS
Class -> String
(Int -> Class -> ShowS)
-> (Class -> String) -> ([Class] -> ShowS) -> Show Class
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Class -> ShowS
showsPrec :: Int -> Class -> ShowS
$cshow :: Class -> String
show :: Class -> String
$cshowList :: [Class] -> ShowS
showList :: [Class] -> ShowS
Show)
classCode :: Class -> H5T_class_t
classCode :: Class -> H5T_class_t
classCode Class
Integer   = H5T_class_t
h5t_INTEGER
classCode Class
Float     = H5T_class_t
h5t_FLOAT
classCode Class
Time      = H5T_class_t
h5t_TIME
classCode Class
String    = H5T_class_t
h5t_STRING
classCode Class
BitField  = H5T_class_t
h5t_BITFIELD
classCode Class
Opaque    = H5T_class_t
h5t_OPAQUE
classCode Class
Compound  = H5T_class_t
h5t_COMPOUND
classCode Class
Reference = H5T_class_t
h5t_REFERENCE
classCode Class
Enum      = H5T_class_t
h5t_ENUM
classCode Class
VLen      = H5T_class_t
h5t_VLEN
classCode Class
Array     = H5T_class_t
h5t_ARRAY
classFromCode :: H5T_class_t -> Class
classFromCode :: H5T_class_t -> Class
classFromCode H5T_class_t
c
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_INTEGER      = Class
Integer
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_FLOAT        = Class
Float
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_TIME         = Class
Time
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_STRING       = Class
String
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_BITFIELD     = Class
BitField
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_OPAQUE       = Class
Opaque
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_COMPOUND     = Class
Compound
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_REFERENCE    = Class
Reference
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_ENUM         = Class
Enum
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_VLEN         = Class
VLen
    | H5T_class_t
c H5T_class_t -> H5T_class_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_class_t
h5t_ARRAY        = Class
Array
    | Bool
otherwise = String -> Class
forall a. HasCallStack => String -> a
error (String
"Unknown H5T_class_t " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5T_class_t -> String
forall a. Show a => a -> String
show H5T_class_t
c)
data CSet
    = ASCII
    | Reserved2
    | Reserved3
    | Reserved4
    | Reserved5
    | Reserved6
    | Reserved7
    | Reserved8
    | Reserved9
    | Reserved10
    | Reserved11
    | Reserved12
    | Reserved13
    | Reserved14
    | Reserved15
    | UTF8
    deriving (CSet -> CSet -> Bool
(CSet -> CSet -> Bool) -> (CSet -> CSet -> Bool) -> Eq CSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CSet -> CSet -> Bool
== :: CSet -> CSet -> Bool
$c/= :: CSet -> CSet -> Bool
/= :: CSet -> CSet -> Bool
Eq, Eq CSet
Eq CSet =>
(CSet -> CSet -> Ordering)
-> (CSet -> CSet -> Bool)
-> (CSet -> CSet -> Bool)
-> (CSet -> CSet -> Bool)
-> (CSet -> CSet -> Bool)
-> (CSet -> CSet -> CSet)
-> (CSet -> CSet -> CSet)
-> Ord CSet
CSet -> CSet -> Bool
CSet -> CSet -> Ordering
CSet -> CSet -> CSet
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 :: CSet -> CSet -> Ordering
compare :: CSet -> CSet -> Ordering
$c< :: CSet -> CSet -> Bool
< :: CSet -> CSet -> Bool
$c<= :: CSet -> CSet -> Bool
<= :: CSet -> CSet -> Bool
$c> :: CSet -> CSet -> Bool
> :: CSet -> CSet -> Bool
$c>= :: CSet -> CSet -> Bool
>= :: CSet -> CSet -> Bool
$cmax :: CSet -> CSet -> CSet
max :: CSet -> CSet -> CSet
$cmin :: CSet -> CSet -> CSet
min :: CSet -> CSet -> CSet
Ord, ReadPrec [CSet]
ReadPrec CSet
Int -> ReadS CSet
ReadS [CSet]
(Int -> ReadS CSet)
-> ReadS [CSet] -> ReadPrec CSet -> ReadPrec [CSet] -> Read CSet
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CSet
readsPrec :: Int -> ReadS CSet
$creadList :: ReadS [CSet]
readList :: ReadS [CSet]
$creadPrec :: ReadPrec CSet
readPrec :: ReadPrec CSet
$creadListPrec :: ReadPrec [CSet]
readListPrec :: ReadPrec [CSet]
Read, Int -> CSet -> ShowS
[CSet] -> ShowS
CSet -> String
(Int -> CSet -> ShowS)
-> (CSet -> String) -> ([CSet] -> ShowS) -> Show CSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CSet -> ShowS
showsPrec :: Int -> CSet -> ShowS
$cshow :: CSet -> String
show :: CSet -> String
$cshowList :: [CSet] -> ShowS
showList :: [CSet] -> ShowS
Show, Int -> CSet
CSet -> Int
CSet -> [CSet]
CSet -> CSet
CSet -> CSet -> [CSet]
CSet -> CSet -> CSet -> [CSet]
(CSet -> CSet)
-> (CSet -> CSet)
-> (Int -> CSet)
-> (CSet -> Int)
-> (CSet -> [CSet])
-> (CSet -> CSet -> [CSet])
-> (CSet -> CSet -> [CSet])
-> (CSet -> CSet -> CSet -> [CSet])
-> Enum CSet
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: CSet -> CSet
succ :: CSet -> CSet
$cpred :: CSet -> CSet
pred :: CSet -> CSet
$ctoEnum :: Int -> CSet
toEnum :: Int -> CSet
$cfromEnum :: CSet -> Int
fromEnum :: CSet -> Int
$cenumFrom :: CSet -> [CSet]
enumFrom :: CSet -> [CSet]
$cenumFromThen :: CSet -> CSet -> [CSet]
enumFromThen :: CSet -> CSet -> [CSet]
$cenumFromTo :: CSet -> CSet -> [CSet]
enumFromTo :: CSet -> CSet -> [CSet]
$cenumFromThenTo :: CSet -> CSet -> CSet -> [CSet]
enumFromThenTo :: CSet -> CSet -> CSet -> [CSet]
Enum, CSet
CSet -> CSet -> Bounded CSet
forall a. a -> a -> Bounded a
$cminBound :: CSet
minBound :: CSet
$cmaxBound :: CSet
maxBound :: CSet
Bounded)
cSetCode :: CSet -> H5T_cset_t
cSetCode :: CSet -> H5T_cset_t
cSetCode CSet
ASCII          = H5T_cset_t
h5t_CSET_ASCII
cSetCode CSet
Reserved2      = H5T_cset_t
h5t_CSET_RESERVED_2
cSetCode CSet
Reserved3      = H5T_cset_t
h5t_CSET_RESERVED_3
cSetCode CSet
Reserved4      = H5T_cset_t
h5t_CSET_RESERVED_4
cSetCode CSet
Reserved5      = H5T_cset_t
h5t_CSET_RESERVED_5
cSetCode CSet
Reserved6      = H5T_cset_t
h5t_CSET_RESERVED_6
cSetCode CSet
Reserved7      = H5T_cset_t
h5t_CSET_RESERVED_7
cSetCode CSet
Reserved8      = H5T_cset_t
h5t_CSET_RESERVED_8
cSetCode CSet
Reserved9      = H5T_cset_t
h5t_CSET_RESERVED_9
cSetCode CSet
Reserved10     = H5T_cset_t
h5t_CSET_RESERVED_10
cSetCode CSet
Reserved11     = H5T_cset_t
h5t_CSET_RESERVED_11
cSetCode CSet
Reserved12     = H5T_cset_t
h5t_CSET_RESERVED_12
cSetCode CSet
Reserved13     = H5T_cset_t
h5t_CSET_RESERVED_13
cSetCode CSet
Reserved14     = H5T_cset_t
h5t_CSET_RESERVED_14
cSetCode CSet
Reserved15     = H5T_cset_t
h5t_CSET_RESERVED_15
cSetCode CSet
UTF8           = H5T_cset_t
h5t_CSET_UTF8
cSetFromCode :: H5T_cset_t -> CSet
cSetFromCode :: H5T_cset_t -> CSet
cSetFromCode H5T_cset_t
c = case H5T_cset_t -> [(H5T_cset_t, CSet)] -> Maybe CSet
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup H5T_cset_t
c [(H5T_cset_t, CSet)]
cSets of
    Just CSet
cset -> CSet
cset
    Maybe CSet
Nothing   -> String -> CSet
forall a. HasCallStack => String -> a
error (String
"Unknown charset code: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5T_cset_t -> String
forall a. Show a => a -> String
show H5T_cset_t
c)
    where cSets :: [(H5T_cset_t, CSet)]
cSets = [ (CSet -> H5T_cset_t
cSetCode CSet
x, CSet
x) | CSet
x <- [CSet
forall a. Bounded a => a
minBound .. CSet
forall a. Bounded a => a
maxBound]]
data ByteOrder
    = LE
    | BE
    | VAX
    | Mixed
    deriving (ByteOrder -> ByteOrder -> Bool
(ByteOrder -> ByteOrder -> Bool)
-> (ByteOrder -> ByteOrder -> Bool) -> Eq ByteOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ByteOrder -> ByteOrder -> Bool
== :: ByteOrder -> ByteOrder -> Bool
$c/= :: ByteOrder -> ByteOrder -> Bool
/= :: ByteOrder -> ByteOrder -> Bool
Eq, Eq ByteOrder
Eq ByteOrder =>
(ByteOrder -> ByteOrder -> Ordering)
-> (ByteOrder -> ByteOrder -> Bool)
-> (ByteOrder -> ByteOrder -> Bool)
-> (ByteOrder -> ByteOrder -> Bool)
-> (ByteOrder -> ByteOrder -> Bool)
-> (ByteOrder -> ByteOrder -> ByteOrder)
-> (ByteOrder -> ByteOrder -> ByteOrder)
-> Ord ByteOrder
ByteOrder -> ByteOrder -> Bool
ByteOrder -> ByteOrder -> Ordering
ByteOrder -> ByteOrder -> ByteOrder
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 :: ByteOrder -> ByteOrder -> Ordering
compare :: ByteOrder -> ByteOrder -> Ordering
$c< :: ByteOrder -> ByteOrder -> Bool
< :: ByteOrder -> ByteOrder -> Bool
$c<= :: ByteOrder -> ByteOrder -> Bool
<= :: ByteOrder -> ByteOrder -> Bool
$c> :: ByteOrder -> ByteOrder -> Bool
> :: ByteOrder -> ByteOrder -> Bool
$c>= :: ByteOrder -> ByteOrder -> Bool
>= :: ByteOrder -> ByteOrder -> Bool
$cmax :: ByteOrder -> ByteOrder -> ByteOrder
max :: ByteOrder -> ByteOrder -> ByteOrder
$cmin :: ByteOrder -> ByteOrder -> ByteOrder
min :: ByteOrder -> ByteOrder -> ByteOrder
Ord, ByteOrder
ByteOrder -> ByteOrder -> Bounded ByteOrder
forall a. a -> a -> Bounded a
$cminBound :: ByteOrder
minBound :: ByteOrder
$cmaxBound :: ByteOrder
maxBound :: ByteOrder
Bounded, Int -> ByteOrder
ByteOrder -> Int
ByteOrder -> [ByteOrder]
ByteOrder -> ByteOrder
ByteOrder -> ByteOrder -> [ByteOrder]
ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder]
(ByteOrder -> ByteOrder)
-> (ByteOrder -> ByteOrder)
-> (Int -> ByteOrder)
-> (ByteOrder -> Int)
-> (ByteOrder -> [ByteOrder])
-> (ByteOrder -> ByteOrder -> [ByteOrder])
-> (ByteOrder -> ByteOrder -> [ByteOrder])
-> (ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder])
-> Enum ByteOrder
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ByteOrder -> ByteOrder
succ :: ByteOrder -> ByteOrder
$cpred :: ByteOrder -> ByteOrder
pred :: ByteOrder -> ByteOrder
$ctoEnum :: Int -> ByteOrder
toEnum :: Int -> ByteOrder
$cfromEnum :: ByteOrder -> Int
fromEnum :: ByteOrder -> Int
$cenumFrom :: ByteOrder -> [ByteOrder]
enumFrom :: ByteOrder -> [ByteOrder]
$cenumFromThen :: ByteOrder -> ByteOrder -> [ByteOrder]
enumFromThen :: ByteOrder -> ByteOrder -> [ByteOrder]
$cenumFromTo :: ByteOrder -> ByteOrder -> [ByteOrder]
enumFromTo :: ByteOrder -> ByteOrder -> [ByteOrder]
$cenumFromThenTo :: ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder]
enumFromThenTo :: ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder]
Enum, ReadPrec [ByteOrder]
ReadPrec ByteOrder
Int -> ReadS ByteOrder
ReadS [ByteOrder]
(Int -> ReadS ByteOrder)
-> ReadS [ByteOrder]
-> ReadPrec ByteOrder
-> ReadPrec [ByteOrder]
-> Read ByteOrder
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ByteOrder
readsPrec :: Int -> ReadS ByteOrder
$creadList :: ReadS [ByteOrder]
readList :: ReadS [ByteOrder]
$creadPrec :: ReadPrec ByteOrder
readPrec :: ReadPrec ByteOrder
$creadListPrec :: ReadPrec [ByteOrder]
readListPrec :: ReadPrec [ByteOrder]
Read, Int -> ByteOrder -> ShowS
[ByteOrder] -> ShowS
ByteOrder -> String
(Int -> ByteOrder -> ShowS)
-> (ByteOrder -> String)
-> ([ByteOrder] -> ShowS)
-> Show ByteOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ByteOrder -> ShowS
showsPrec :: Int -> ByteOrder -> ShowS
$cshow :: ByteOrder -> String
show :: ByteOrder -> String
$cshowList :: [ByteOrder] -> ShowS
showList :: [ByteOrder] -> ShowS
Show)
byteOrderCode :: Maybe ByteOrder -> H5T_order_t
byteOrderCode :: Maybe ByteOrder -> H5T_order_t
byteOrderCode (Just ByteOrder
LE)     = H5T_order_t
h5t_ORDER_LE
byteOrderCode (Just ByteOrder
BE)     = H5T_order_t
h5t_ORDER_BE
byteOrderCode (Just ByteOrder
VAX)    = H5T_order_t
h5t_ORDER_VAX
byteOrderCode (Just ByteOrder
Mixed)  = H5T_order_t
h5t_ORDER_MIXED
byteOrderCode Maybe ByteOrder
Nothing       = H5T_order_t
h5t_ORDER_NONE
byteOrder :: H5T_order_t -> Maybe ByteOrder
byteOrder :: H5T_order_t -> Maybe ByteOrder
byteOrder H5T_order_t
c
    | H5T_order_t
c H5T_order_t -> H5T_order_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_order_t
h5t_ORDER_LE     = ByteOrder -> Maybe ByteOrder
forall a. a -> Maybe a
Just ByteOrder
LE
    | H5T_order_t
c H5T_order_t -> H5T_order_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_order_t
h5t_ORDER_BE     = ByteOrder -> Maybe ByteOrder
forall a. a -> Maybe a
Just ByteOrder
BE
    | H5T_order_t
c H5T_order_t -> H5T_order_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_order_t
h5t_ORDER_VAX    = ByteOrder -> Maybe ByteOrder
forall a. a -> Maybe a
Just ByteOrder
VAX
    | H5T_order_t
c H5T_order_t -> H5T_order_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_order_t
h5t_ORDER_MIXED  = ByteOrder -> Maybe ByteOrder
forall a. a -> Maybe a
Just ByteOrder
Mixed
    | H5T_order_t
c H5T_order_t -> H5T_order_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_order_t
h5t_ORDER_NONE   = Maybe ByteOrder
forall a. Maybe a
Nothing
    | Bool
otherwise             = Maybe ByteOrder
forall a. Maybe a
Nothing
data Pad
    = Zero
    | One
    | Background
    deriving (Pad -> Pad -> Bool
(Pad -> Pad -> Bool) -> (Pad -> Pad -> Bool) -> Eq Pad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pad -> Pad -> Bool
== :: Pad -> Pad -> Bool
$c/= :: Pad -> Pad -> Bool
/= :: Pad -> Pad -> Bool
Eq, Eq Pad
Eq Pad =>
(Pad -> Pad -> Ordering)
-> (Pad -> Pad -> Bool)
-> (Pad -> Pad -> Bool)
-> (Pad -> Pad -> Bool)
-> (Pad -> Pad -> Bool)
-> (Pad -> Pad -> Pad)
-> (Pad -> Pad -> Pad)
-> Ord Pad
Pad -> Pad -> Bool
Pad -> Pad -> Ordering
Pad -> Pad -> Pad
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 :: Pad -> Pad -> Ordering
compare :: Pad -> Pad -> Ordering
$c< :: Pad -> Pad -> Bool
< :: Pad -> Pad -> Bool
$c<= :: Pad -> Pad -> Bool
<= :: Pad -> Pad -> Bool
$c> :: Pad -> Pad -> Bool
> :: Pad -> Pad -> Bool
$c>= :: Pad -> Pad -> Bool
>= :: Pad -> Pad -> Bool
$cmax :: Pad -> Pad -> Pad
max :: Pad -> Pad -> Pad
$cmin :: Pad -> Pad -> Pad
min :: Pad -> Pad -> Pad
Ord, Int -> Pad
Pad -> Int
Pad -> [Pad]
Pad -> Pad
Pad -> Pad -> [Pad]
Pad -> Pad -> Pad -> [Pad]
(Pad -> Pad)
-> (Pad -> Pad)
-> (Int -> Pad)
-> (Pad -> Int)
-> (Pad -> [Pad])
-> (Pad -> Pad -> [Pad])
-> (Pad -> Pad -> [Pad])
-> (Pad -> Pad -> Pad -> [Pad])
-> Enum Pad
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Pad -> Pad
succ :: Pad -> Pad
$cpred :: Pad -> Pad
pred :: Pad -> Pad
$ctoEnum :: Int -> Pad
toEnum :: Int -> Pad
$cfromEnum :: Pad -> Int
fromEnum :: Pad -> Int
$cenumFrom :: Pad -> [Pad]
enumFrom :: Pad -> [Pad]
$cenumFromThen :: Pad -> Pad -> [Pad]
enumFromThen :: Pad -> Pad -> [Pad]
$cenumFromTo :: Pad -> Pad -> [Pad]
enumFromTo :: Pad -> Pad -> [Pad]
$cenumFromThenTo :: Pad -> Pad -> Pad -> [Pad]
enumFromThenTo :: Pad -> Pad -> Pad -> [Pad]
Enum, Pad
Pad -> Pad -> Bounded Pad
forall a. a -> a -> Bounded a
$cminBound :: Pad
minBound :: Pad
$cmaxBound :: Pad
maxBound :: Pad
Bounded, ReadPrec [Pad]
ReadPrec Pad
Int -> ReadS Pad
ReadS [Pad]
(Int -> ReadS Pad)
-> ReadS [Pad] -> ReadPrec Pad -> ReadPrec [Pad] -> Read Pad
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pad
readsPrec :: Int -> ReadS Pad
$creadList :: ReadS [Pad]
readList :: ReadS [Pad]
$creadPrec :: ReadPrec Pad
readPrec :: ReadPrec Pad
$creadListPrec :: ReadPrec [Pad]
readListPrec :: ReadPrec [Pad]
Read, Int -> Pad -> ShowS
[Pad] -> ShowS
Pad -> String
(Int -> Pad -> ShowS)
-> (Pad -> String) -> ([Pad] -> ShowS) -> Show Pad
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pad -> ShowS
showsPrec :: Int -> Pad -> ShowS
$cshow :: Pad -> String
show :: Pad -> String
$cshowList :: [Pad] -> ShowS
showList :: [Pad] -> ShowS
Show)
padCode     :: Pad -> H5T_pad_t
padCode :: Pad -> H5T_pad_t
padCode Pad
Zero        = H5T_pad_t
h5t_PAD_ZERO
padCode Pad
One         = H5T_pad_t
h5t_PAD_ONE
padCode Pad
Background  = H5T_pad_t
h5t_PAD_BACKGROUND
padFromCode :: H5T_pad_t -> Pad
padFromCode :: H5T_pad_t -> Pad
padFromCode H5T_pad_t
c
    | H5T_pad_t
c H5T_pad_t -> H5T_pad_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_pad_t
h5t_PAD_ZERO         = Pad
Zero
    | H5T_pad_t
c H5T_pad_t -> H5T_pad_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_pad_t
h5t_PAD_ONE          = Pad
One
    | H5T_pad_t
c H5T_pad_t -> H5T_pad_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_pad_t
h5t_PAD_BACKGROUND   = Pad
Background
    | Bool
otherwise = String -> Pad
forall a. HasCallStack => String -> a
error (String
"Unknown Pad code " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5T_pad_t -> String
forall a. Show a => a -> String
show H5T_pad_t
c)
data Normalization
    = Implied
    | MSBSet
    deriving (Normalization -> Normalization -> Bool
(Normalization -> Normalization -> Bool)
-> (Normalization -> Normalization -> Bool) -> Eq Normalization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Normalization -> Normalization -> Bool
== :: Normalization -> Normalization -> Bool
$c/= :: Normalization -> Normalization -> Bool
/= :: Normalization -> Normalization -> Bool
Eq, Eq Normalization
Eq Normalization =>
(Normalization -> Normalization -> Ordering)
-> (Normalization -> Normalization -> Bool)
-> (Normalization -> Normalization -> Bool)
-> (Normalization -> Normalization -> Bool)
-> (Normalization -> Normalization -> Bool)
-> (Normalization -> Normalization -> Normalization)
-> (Normalization -> Normalization -> Normalization)
-> Ord Normalization
Normalization -> Normalization -> Bool
Normalization -> Normalization -> Ordering
Normalization -> Normalization -> Normalization
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 :: Normalization -> Normalization -> Ordering
compare :: Normalization -> Normalization -> Ordering
$c< :: Normalization -> Normalization -> Bool
< :: Normalization -> Normalization -> Bool
$c<= :: Normalization -> Normalization -> Bool
<= :: Normalization -> Normalization -> Bool
$c> :: Normalization -> Normalization -> Bool
> :: Normalization -> Normalization -> Bool
$c>= :: Normalization -> Normalization -> Bool
>= :: Normalization -> Normalization -> Bool
$cmax :: Normalization -> Normalization -> Normalization
max :: Normalization -> Normalization -> Normalization
$cmin :: Normalization -> Normalization -> Normalization
min :: Normalization -> Normalization -> Normalization
Ord, Int -> Normalization
Normalization -> Int
Normalization -> [Normalization]
Normalization -> Normalization
Normalization -> Normalization -> [Normalization]
Normalization -> Normalization -> Normalization -> [Normalization]
(Normalization -> Normalization)
-> (Normalization -> Normalization)
-> (Int -> Normalization)
-> (Normalization -> Int)
-> (Normalization -> [Normalization])
-> (Normalization -> Normalization -> [Normalization])
-> (Normalization -> Normalization -> [Normalization])
-> (Normalization
    -> Normalization -> Normalization -> [Normalization])
-> Enum Normalization
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Normalization -> Normalization
succ :: Normalization -> Normalization
$cpred :: Normalization -> Normalization
pred :: Normalization -> Normalization
$ctoEnum :: Int -> Normalization
toEnum :: Int -> Normalization
$cfromEnum :: Normalization -> Int
fromEnum :: Normalization -> Int
$cenumFrom :: Normalization -> [Normalization]
enumFrom :: Normalization -> [Normalization]
$cenumFromThen :: Normalization -> Normalization -> [Normalization]
enumFromThen :: Normalization -> Normalization -> [Normalization]
$cenumFromTo :: Normalization -> Normalization -> [Normalization]
enumFromTo :: Normalization -> Normalization -> [Normalization]
$cenumFromThenTo :: Normalization -> Normalization -> Normalization -> [Normalization]
enumFromThenTo :: Normalization -> Normalization -> Normalization -> [Normalization]
Enum, Normalization
Normalization -> Normalization -> Bounded Normalization
forall a. a -> a -> Bounded a
$cminBound :: Normalization
minBound :: Normalization
$cmaxBound :: Normalization
maxBound :: Normalization
Bounded, ReadPrec [Normalization]
ReadPrec Normalization
Int -> ReadS Normalization
ReadS [Normalization]
(Int -> ReadS Normalization)
-> ReadS [Normalization]
-> ReadPrec Normalization
-> ReadPrec [Normalization]
-> Read Normalization
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Normalization
readsPrec :: Int -> ReadS Normalization
$creadList :: ReadS [Normalization]
readList :: ReadS [Normalization]
$creadPrec :: ReadPrec Normalization
readPrec :: ReadPrec Normalization
$creadListPrec :: ReadPrec [Normalization]
readListPrec :: ReadPrec [Normalization]
Read, Int -> Normalization -> ShowS
[Normalization] -> ShowS
Normalization -> String
(Int -> Normalization -> ShowS)
-> (Normalization -> String)
-> ([Normalization] -> ShowS)
-> Show Normalization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Normalization -> ShowS
showsPrec :: Int -> Normalization -> ShowS
$cshow :: Normalization -> String
show :: Normalization -> String
$cshowList :: [Normalization] -> ShowS
showList :: [Normalization] -> ShowS
Show)
normalization :: H5T_norm_t -> Maybe Normalization
normalization :: H5T_norm_t -> Maybe Normalization
normalization H5T_norm_t
c
    | H5T_norm_t
c H5T_norm_t -> H5T_norm_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_norm_t
h5t_NORM_IMPLIED = Normalization -> Maybe Normalization
forall a. a -> Maybe a
Just Normalization
Implied
    | H5T_norm_t
c H5T_norm_t -> H5T_norm_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_norm_t
h5t_NORM_MSBSET  = Normalization -> Maybe Normalization
forall a. a -> Maybe a
Just Normalization
MSBSet
    | H5T_norm_t
c H5T_norm_t -> H5T_norm_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_norm_t
h5t_NORM_NONE    = Maybe Normalization
forall a. Maybe a
Nothing
    | Bool
otherwise = String -> Maybe Normalization
forall a. HasCallStack => String -> a
error String
"Unknown H5T_norm_t value"
data StringPad
    = NullTerm
    | NullPad
    | SpacePad
    | StringPad_Reserved3
    | StringPad_Reserved4
    | StringPad_Reserved5
    | StringPad_Reserved6
    | StringPad_Reserved7
    | StringPad_Reserved8
    | StringPad_Reserved9
    | StringPad_Reserved10
    | StringPad_Reserved11
    | StringPad_Reserved12
    | StringPad_Reserved13
    | StringPad_Reserved14
    | StringPad_Reserved15
    deriving (StringPad -> StringPad -> Bool
(StringPad -> StringPad -> Bool)
-> (StringPad -> StringPad -> Bool) -> Eq StringPad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StringPad -> StringPad -> Bool
== :: StringPad -> StringPad -> Bool
$c/= :: StringPad -> StringPad -> Bool
/= :: StringPad -> StringPad -> Bool
Eq, Eq StringPad
Eq StringPad =>
(StringPad -> StringPad -> Ordering)
-> (StringPad -> StringPad -> Bool)
-> (StringPad -> StringPad -> Bool)
-> (StringPad -> StringPad -> Bool)
-> (StringPad -> StringPad -> Bool)
-> (StringPad -> StringPad -> StringPad)
-> (StringPad -> StringPad -> StringPad)
-> Ord StringPad
StringPad -> StringPad -> Bool
StringPad -> StringPad -> Ordering
StringPad -> StringPad -> StringPad
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 :: StringPad -> StringPad -> Ordering
compare :: StringPad -> StringPad -> Ordering
$c< :: StringPad -> StringPad -> Bool
< :: StringPad -> StringPad -> Bool
$c<= :: StringPad -> StringPad -> Bool
<= :: StringPad -> StringPad -> Bool
$c> :: StringPad -> StringPad -> Bool
> :: StringPad -> StringPad -> Bool
$c>= :: StringPad -> StringPad -> Bool
>= :: StringPad -> StringPad -> Bool
$cmax :: StringPad -> StringPad -> StringPad
max :: StringPad -> StringPad -> StringPad
$cmin :: StringPad -> StringPad -> StringPad
min :: StringPad -> StringPad -> StringPad
Ord, Int -> StringPad
StringPad -> Int
StringPad -> [StringPad]
StringPad -> StringPad
StringPad -> StringPad -> [StringPad]
StringPad -> StringPad -> StringPad -> [StringPad]
(StringPad -> StringPad)
-> (StringPad -> StringPad)
-> (Int -> StringPad)
-> (StringPad -> Int)
-> (StringPad -> [StringPad])
-> (StringPad -> StringPad -> [StringPad])
-> (StringPad -> StringPad -> [StringPad])
-> (StringPad -> StringPad -> StringPad -> [StringPad])
-> Enum StringPad
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: StringPad -> StringPad
succ :: StringPad -> StringPad
$cpred :: StringPad -> StringPad
pred :: StringPad -> StringPad
$ctoEnum :: Int -> StringPad
toEnum :: Int -> StringPad
$cfromEnum :: StringPad -> Int
fromEnum :: StringPad -> Int
$cenumFrom :: StringPad -> [StringPad]
enumFrom :: StringPad -> [StringPad]
$cenumFromThen :: StringPad -> StringPad -> [StringPad]
enumFromThen :: StringPad -> StringPad -> [StringPad]
$cenumFromTo :: StringPad -> StringPad -> [StringPad]
enumFromTo :: StringPad -> StringPad -> [StringPad]
$cenumFromThenTo :: StringPad -> StringPad -> StringPad -> [StringPad]
enumFromThenTo :: StringPad -> StringPad -> StringPad -> [StringPad]
Enum, StringPad
StringPad -> StringPad -> Bounded StringPad
forall a. a -> a -> Bounded a
$cminBound :: StringPad
minBound :: StringPad
$cmaxBound :: StringPad
maxBound :: StringPad
Bounded, ReadPrec [StringPad]
ReadPrec StringPad
Int -> ReadS StringPad
ReadS [StringPad]
(Int -> ReadS StringPad)
-> ReadS [StringPad]
-> ReadPrec StringPad
-> ReadPrec [StringPad]
-> Read StringPad
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StringPad
readsPrec :: Int -> ReadS StringPad
$creadList :: ReadS [StringPad]
readList :: ReadS [StringPad]
$creadPrec :: ReadPrec StringPad
readPrec :: ReadPrec StringPad
$creadListPrec :: ReadPrec [StringPad]
readListPrec :: ReadPrec [StringPad]
Read, Int -> StringPad -> ShowS
[StringPad] -> ShowS
StringPad -> String
(Int -> StringPad -> ShowS)
-> (StringPad -> String)
-> ([StringPad] -> ShowS)
-> Show StringPad
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StringPad -> ShowS
showsPrec :: Int -> StringPad -> ShowS
$cshow :: StringPad -> String
show :: StringPad -> String
$cshowList :: [StringPad] -> ShowS
showList :: [StringPad] -> ShowS
Show)
stringPadCode :: StringPad -> H5T_str_t
stringPadCode :: StringPad -> H5T_str_t
stringPadCode StringPad
NullTerm              = H5T_str_t
h5t_STR_NULLTERM
stringPadCode StringPad
NullPad               = H5T_str_t
h5t_STR_NULLPAD
stringPadCode StringPad
SpacePad              = H5T_str_t
h5t_STR_SPACEPAD
stringPadCode StringPad
StringPad_Reserved3   = H5T_str_t
h5t_STR_RESERVED_3
stringPadCode StringPad
StringPad_Reserved4   = H5T_str_t
h5t_STR_RESERVED_4
stringPadCode StringPad
StringPad_Reserved5   = H5T_str_t
h5t_STR_RESERVED_5
stringPadCode StringPad
StringPad_Reserved6   = H5T_str_t
h5t_STR_RESERVED_6
stringPadCode StringPad
StringPad_Reserved7   = H5T_str_t
h5t_STR_RESERVED_7
stringPadCode StringPad
StringPad_Reserved8   = H5T_str_t
h5t_STR_RESERVED_8
stringPadCode StringPad
StringPad_Reserved9   = H5T_str_t
h5t_STR_RESERVED_9
stringPadCode StringPad
StringPad_Reserved10  = H5T_str_t
h5t_STR_RESERVED_10
stringPadCode StringPad
StringPad_Reserved11  = H5T_str_t
h5t_STR_RESERVED_11
stringPadCode StringPad
StringPad_Reserved12  = H5T_str_t
h5t_STR_RESERVED_12
stringPadCode StringPad
StringPad_Reserved13  = H5T_str_t
h5t_STR_RESERVED_13
stringPadCode StringPad
StringPad_Reserved14  = H5T_str_t
h5t_STR_RESERVED_14
stringPadCode StringPad
StringPad_Reserved15  = H5T_str_t
h5t_STR_RESERVED_15
stringPadFromCode :: H5T_str_t -> StringPad
stringPadFromCode :: H5T_str_t -> StringPad
stringPadFromCode H5T_str_t
c
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_NULLTERM     = StringPad
NullTerm
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_NULLPAD      = StringPad
NullPad
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_SPACEPAD     = StringPad
SpacePad
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_3   = StringPad
StringPad_Reserved3
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_4   = StringPad
StringPad_Reserved4
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_5   = StringPad
StringPad_Reserved5
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_6   = StringPad
StringPad_Reserved6
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_7   = StringPad
StringPad_Reserved7
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_8   = StringPad
StringPad_Reserved8
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_9   = StringPad
StringPad_Reserved9
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_10  = StringPad
StringPad_Reserved10
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_11  = StringPad
StringPad_Reserved11
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_12  = StringPad
StringPad_Reserved12
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_13  = StringPad
StringPad_Reserved13
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_14  = StringPad
StringPad_Reserved14
    | H5T_str_t
c H5T_str_t -> H5T_str_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5T_str_t
h5t_STR_RESERVED_15  = StringPad
StringPad_Reserved15
    | Bool
otherwise = String -> StringPad
forall a. HasCallStack => String -> a
error (String
"Unknown StringPad code " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5T_str_t -> String
forall a. Show a => a -> String
show H5T_str_t
c)