{-# LINE 1 "src/Bindings/HDF5/Raw/H5T.hsc" #-}




{-# LINE 5 "src/Bindings/HDF5/Raw/H5T.hsc" #-}


{-# LINE 7 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

module Bindings.HDF5.Raw.H5T where

import Data.Int
import Data.Word
import Foreign.C.String
import Foreign.C.Types
import Foreign.Ptr
import Foreign.Storable

import Bindings.HDF5.Raw.H5
import Bindings.HDF5.Raw.H5I
import Foreign.Ptr.Conventions

-- |These are the various classes of datatypes
--
-- If this goes over 16 types (0-15), the file format will need to change)
newtype H5T_class_t = H5T_class_t Int32 deriving (Ptr H5T_class_t -> IO H5T_class_t
Ptr H5T_class_t -> Int -> IO H5T_class_t
Ptr H5T_class_t -> Int -> H5T_class_t -> IO ()
Ptr H5T_class_t -> H5T_class_t -> IO ()
H5T_class_t -> Int
(H5T_class_t -> Int)
-> (H5T_class_t -> Int)
-> (Ptr H5T_class_t -> Int -> IO H5T_class_t)
-> (Ptr H5T_class_t -> Int -> H5T_class_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5T_class_t)
-> (forall b. Ptr b -> Int -> H5T_class_t -> IO ())
-> (Ptr H5T_class_t -> IO H5T_class_t)
-> (Ptr H5T_class_t -> H5T_class_t -> IO ())
-> Storable H5T_class_t
forall b. Ptr b -> Int -> IO H5T_class_t
forall b. Ptr b -> Int -> H5T_class_t -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: H5T_class_t -> Int
sizeOf :: H5T_class_t -> Int
$calignment :: H5T_class_t -> Int
alignment :: H5T_class_t -> Int
$cpeekElemOff :: Ptr H5T_class_t -> Int -> IO H5T_class_t
peekElemOff :: Ptr H5T_class_t -> Int -> IO H5T_class_t
$cpokeElemOff :: Ptr H5T_class_t -> Int -> H5T_class_t -> IO ()
pokeElemOff :: Ptr H5T_class_t -> Int -> H5T_class_t -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5T_class_t
peekByteOff :: forall b. Ptr b -> Int -> IO H5T_class_t
$cpokeByteOff :: forall b. Ptr b -> Int -> H5T_class_t -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5T_class_t -> IO ()
$cpeek :: Ptr H5T_class_t -> IO H5T_class_t
peek :: Ptr H5T_class_t -> IO H5T_class_t
$cpoke :: Ptr H5T_class_t -> H5T_class_t -> IO ()
poke :: Ptr H5T_class_t -> H5T_class_t -> IO ()
Storable, Int -> H5T_class_t -> ShowS
[H5T_class_t] -> ShowS
H5T_class_t -> String
(Int -> H5T_class_t -> ShowS)
-> (H5T_class_t -> String)
-> ([H5T_class_t] -> ShowS)
-> Show H5T_class_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5T_class_t -> ShowS
showsPrec :: Int -> H5T_class_t -> ShowS
$cshow :: H5T_class_t -> String
show :: H5T_class_t -> String
$cshowList :: [H5T_class_t] -> ShowS
showList :: [H5T_class_t] -> ShowS
Show, H5T_class_t -> H5T_class_t -> Bool
(H5T_class_t -> H5T_class_t -> Bool)
-> (H5T_class_t -> H5T_class_t -> Bool) -> Eq H5T_class_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5T_class_t -> H5T_class_t -> Bool
== :: H5T_class_t -> H5T_class_t -> Bool
$c/= :: H5T_class_t -> H5T_class_t -> Bool
/= :: H5T_class_t -> H5T_class_t -> Bool
Eq)

{-# LINE 25 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_NO_CLASS :: H5T_class_t
h5t_NO_CLASS :: H5T_class_t
h5t_NO_CLASS = Int32 -> H5T_class_t
H5T_class_t (-Int32
1)

{-# LINE 28 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |integer types
h5t_INTEGER :: H5T_class_t
h5t_INTEGER :: H5T_class_t
h5t_INTEGER = Int32 -> H5T_class_t
H5T_class_t (Int32
0)

{-# LINE 31 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |floating-point types
h5t_FLOAT :: H5T_class_t
h5t_FLOAT :: H5T_class_t
h5t_FLOAT = Int32 -> H5T_class_t
H5T_class_t (Int32
1)

{-# LINE 34 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |date and time types
h5t_TIME :: H5T_class_t
h5t_TIME :: H5T_class_t
h5t_TIME = Int32 -> H5T_class_t
H5T_class_t (Int32
2)

{-# LINE 37 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |character string types
h5t_STRING :: H5T_class_t
h5t_STRING :: H5T_class_t
h5t_STRING = Int32 -> H5T_class_t
H5T_class_t (Int32
3)

{-# LINE 40 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |bit field types
h5t_BITFIELD :: H5T_class_t
h5t_BITFIELD :: H5T_class_t
h5t_BITFIELD = Int32 -> H5T_class_t
H5T_class_t (Int32
4)

{-# LINE 43 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |opaque types
h5t_OPAQUE :: H5T_class_t
h5t_OPAQUE :: H5T_class_t
h5t_OPAQUE = Int32 -> H5T_class_t
H5T_class_t (Int32
5)

{-# LINE 46 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |compound types
h5t_COMPOUND :: H5T_class_t
h5t_COMPOUND :: H5T_class_t
h5t_COMPOUND = Int32 -> H5T_class_t
H5T_class_t (Int32
6)

{-# LINE 49 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reference types
h5t_REFERENCE :: H5T_class_t
h5t_REFERENCE :: H5T_class_t
h5t_REFERENCE = Int32 -> H5T_class_t
H5T_class_t (Int32
7)

{-# LINE 52 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |enumeration types
h5t_ENUM :: H5T_class_t
h5t_ENUM :: H5T_class_t
h5t_ENUM = Int32 -> H5T_class_t
H5T_class_t (Int32
8)

{-# LINE 55 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Variable-Length types
h5t_VLEN :: H5T_class_t
h5t_VLEN :: H5T_class_t
h5t_VLEN = Int32 -> H5T_class_t
H5T_class_t (Int32
9)

{-# LINE 58 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Array types
h5t_ARRAY :: H5T_class_t
h5t_ARRAY :: H5T_class_t
h5t_ARRAY = Int32 -> H5T_class_t
H5T_class_t (Int32
10)

{-# LINE 61 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The number of basic datatypes
h5t_NCLASSES = 11
h5t_NCLASSES :: (Num a) => a

{-# LINE 64 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Byte orders
newtype H5T_order_t = H5T_order_t Int32 deriving (Storable, Show, Eq)

{-# LINE 67 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_ORDER_ERROR :: H5T_order_t
h5t_ORDER_ERROR :: H5T_order_t
h5t_ORDER_ERROR = Int32 -> H5T_order_t
H5T_order_t (-Int32
1)

{-# LINE 70 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |little endian
h5t_ORDER_LE :: H5T_order_t
h5t_ORDER_LE :: H5T_order_t
h5t_ORDER_LE = Int32 -> H5T_order_t
H5T_order_t (Int32
0)

{-# LINE 73 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |bit endian
h5t_ORDER_BE :: H5T_order_t
h5t_ORDER_BE :: H5T_order_t
h5t_ORDER_BE = Int32 -> H5T_order_t
H5T_order_t (Int32
1)

{-# LINE 76 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |VAX mixed endian
h5t_ORDER_VAX :: H5T_order_t
h5t_ORDER_VAX :: H5T_order_t
h5t_ORDER_VAX = Int32 -> H5T_order_t
H5T_order_t (Int32
2)

{-# LINE 79 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Compound type with mixed member orders
h5t_ORDER_MIXED :: H5T_order_t
h5t_ORDER_MIXED :: H5T_order_t
h5t_ORDER_MIXED = Int32 -> H5T_order_t
H5T_order_t (Int32
3)

{-# LINE 82 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |no particular order (strings, bits,..)
h5t_ORDER_NONE :: H5T_order_t
h5t_ORDER_NONE :: H5T_order_t
h5t_ORDER_NONE = Int32 -> H5T_order_t
H5T_order_t (Int32
4)

{-# LINE 85 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Types of integer sign schemes
newtype H5T_sign_t = H5T_sign_t Int32 deriving (Storable, Show, Eq)

{-# LINE 88 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_SGN_ERROR :: H5T_sign_t
h5t_SGN_ERROR :: H5T_sign_t
h5t_SGN_ERROR = Int32 -> H5T_sign_t
H5T_sign_t (-Int32
1)

{-# LINE 91 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |this is an unsigned type
h5t_SGN_NONE :: H5T_sign_t
h5t_SGN_NONE :: H5T_sign_t
h5t_SGN_NONE = Int32 -> H5T_sign_t
H5T_sign_t (Int32
0)

{-# LINE 94 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |two's complement
h5t_SGN_2 :: H5T_sign_t
h5t_SGN_2 :: H5T_sign_t
h5t_SGN_2 = Int32 -> H5T_sign_t
H5T_sign_t (Int32
1)

h5t_NSGN :: forall a. Num a => a
{-# LINE 97 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The number of recognized integer sign schemes
h5t_NSGN = 2
h5t_NSGN :: (Num a) => a

{-# LINE 100 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Floating-point normalization schemes
newtype H5T_norm_t = H5T_norm_t Int32 deriving (Storable, Show, Eq)

{-# LINE 103 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_NORM_ERROR :: H5T_norm_t
h5t_NORM_ERROR :: H5T_norm_t
h5t_NORM_ERROR = Int32 -> H5T_norm_t
H5T_norm_t (-Int32
1)

{-# LINE 106 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |msb of mantissa isn't stored, always 1
h5t_NORM_IMPLIED :: H5T_norm_t
h5t_NORM_IMPLIED :: H5T_norm_t
h5t_NORM_IMPLIED = Int32 -> H5T_norm_t
H5T_norm_t (Int32
0)

{-# LINE 109 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |msb of mantissa is always 1
h5t_NORM_MSBSET :: H5T_norm_t
h5t_NORM_MSBSET :: H5T_norm_t
h5t_NORM_MSBSET = Int32 -> H5T_norm_t
H5T_norm_t (Int32
1)

{-# LINE 112 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |not normalized
h5t_NORM_NONE :: H5T_norm_t
h5t_NORM_NONE :: H5T_norm_t
h5t_NORM_NONE = Int32 -> H5T_norm_t
H5T_norm_t (Int32
2)

{-# LINE 115 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Character set to use for text strings.  Do not change these values since
-- they appear in HDF5 files!
newtype H5T_cset_t = H5T_cset_t Int32 deriving (Ptr H5T_cset_t -> IO H5T_cset_t
Ptr H5T_cset_t -> Int -> IO H5T_cset_t
Ptr H5T_cset_t -> Int -> H5T_cset_t -> IO ()
Ptr H5T_cset_t -> H5T_cset_t -> IO ()
H5T_cset_t -> Int
(H5T_cset_t -> Int)
-> (H5T_cset_t -> Int)
-> (Ptr H5T_cset_t -> Int -> IO H5T_cset_t)
-> (Ptr H5T_cset_t -> Int -> H5T_cset_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5T_cset_t)
-> (forall b. Ptr b -> Int -> H5T_cset_t -> IO ())
-> (Ptr H5T_cset_t -> IO H5T_cset_t)
-> (Ptr H5T_cset_t -> H5T_cset_t -> IO ())
-> Storable H5T_cset_t
forall b. Ptr b -> Int -> IO H5T_cset_t
forall b. Ptr b -> Int -> H5T_cset_t -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: H5T_cset_t -> Int
sizeOf :: H5T_cset_t -> Int
$calignment :: H5T_cset_t -> Int
alignment :: H5T_cset_t -> Int
$cpeekElemOff :: Ptr H5T_cset_t -> Int -> IO H5T_cset_t
peekElemOff :: Ptr H5T_cset_t -> Int -> IO H5T_cset_t
$cpokeElemOff :: Ptr H5T_cset_t -> Int -> H5T_cset_t -> IO ()
pokeElemOff :: Ptr H5T_cset_t -> Int -> H5T_cset_t -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5T_cset_t
peekByteOff :: forall b. Ptr b -> Int -> IO H5T_cset_t
$cpokeByteOff :: forall b. Ptr b -> Int -> H5T_cset_t -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5T_cset_t -> IO ()
$cpeek :: Ptr H5T_cset_t -> IO H5T_cset_t
peek :: Ptr H5T_cset_t -> IO H5T_cset_t
$cpoke :: Ptr H5T_cset_t -> H5T_cset_t -> IO ()
poke :: Ptr H5T_cset_t -> H5T_cset_t -> IO ()
Storable, Int -> H5T_cset_t -> ShowS
[H5T_cset_t] -> ShowS
H5T_cset_t -> String
(Int -> H5T_cset_t -> ShowS)
-> (H5T_cset_t -> String)
-> ([H5T_cset_t] -> ShowS)
-> Show H5T_cset_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5T_cset_t -> ShowS
showsPrec :: Int -> H5T_cset_t -> ShowS
$cshow :: H5T_cset_t -> String
show :: H5T_cset_t -> String
$cshowList :: [H5T_cset_t] -> ShowS
showList :: [H5T_cset_t] -> ShowS
Show, H5T_cset_t -> H5T_cset_t -> Bool
(H5T_cset_t -> H5T_cset_t -> Bool)
-> (H5T_cset_t -> H5T_cset_t -> Bool) -> Eq H5T_cset_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5T_cset_t -> H5T_cset_t -> Bool
== :: H5T_cset_t -> H5T_cset_t -> Bool
$c/= :: H5T_cset_t -> H5T_cset_t -> Bool
/= :: H5T_cset_t -> H5T_cset_t -> Bool
Eq, Eq H5T_cset_t
Eq H5T_cset_t =>
(H5T_cset_t -> H5T_cset_t -> Ordering)
-> (H5T_cset_t -> H5T_cset_t -> Bool)
-> (H5T_cset_t -> H5T_cset_t -> Bool)
-> (H5T_cset_t -> H5T_cset_t -> Bool)
-> (H5T_cset_t -> H5T_cset_t -> Bool)
-> (H5T_cset_t -> H5T_cset_t -> H5T_cset_t)
-> (H5T_cset_t -> H5T_cset_t -> H5T_cset_t)
-> Ord H5T_cset_t
H5T_cset_t -> H5T_cset_t -> Bool
H5T_cset_t -> H5T_cset_t -> Ordering
H5T_cset_t -> H5T_cset_t -> H5T_cset_t
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 :: H5T_cset_t -> H5T_cset_t -> Ordering
compare :: H5T_cset_t -> H5T_cset_t -> Ordering
$c< :: H5T_cset_t -> H5T_cset_t -> Bool
< :: H5T_cset_t -> H5T_cset_t -> Bool
$c<= :: H5T_cset_t -> H5T_cset_t -> Bool
<= :: H5T_cset_t -> H5T_cset_t -> Bool
$c> :: H5T_cset_t -> H5T_cset_t -> Bool
> :: H5T_cset_t -> H5T_cset_t -> Bool
$c>= :: H5T_cset_t -> H5T_cset_t -> Bool
>= :: H5T_cset_t -> H5T_cset_t -> Bool
$cmax :: H5T_cset_t -> H5T_cset_t -> H5T_cset_t
max :: H5T_cset_t -> H5T_cset_t -> H5T_cset_t
$cmin :: H5T_cset_t -> H5T_cset_t -> H5T_cset_t
min :: H5T_cset_t -> H5T_cset_t -> H5T_cset_t
Ord, ReadPrec [H5T_cset_t]
ReadPrec H5T_cset_t
Int -> ReadS H5T_cset_t
ReadS [H5T_cset_t]
(Int -> ReadS H5T_cset_t)
-> ReadS [H5T_cset_t]
-> ReadPrec H5T_cset_t
-> ReadPrec [H5T_cset_t]
-> Read H5T_cset_t
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS H5T_cset_t
readsPrec :: Int -> ReadS H5T_cset_t
$creadList :: ReadS [H5T_cset_t]
readList :: ReadS [H5T_cset_t]
$creadPrec :: ReadPrec H5T_cset_t
readPrec :: ReadPrec H5T_cset_t
$creadListPrec :: ReadPrec [H5T_cset_t]
readListPrec :: ReadPrec [H5T_cset_t]
Read)

{-# LINE 119 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_CSET_ERROR :: H5T_cset_t
h5t_CSET_ERROR :: H5T_cset_t
h5t_CSET_ERROR = Int32 -> H5T_cset_t
H5T_cset_t (-Int32
1)

{-# LINE 122 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |US ASCII
h5t_CSET_ASCII :: H5T_cset_t
h5t_CSET_ASCII :: H5T_cset_t
h5t_CSET_ASCII = Int32 -> H5T_cset_t
H5T_cset_t (Int32
0)

{-# LINE 125 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |UTF-8 Unicode encoding
h5t_CSET_UTF8 :: H5T_cset_t
h5t_CSET_UTF8 :: H5T_cset_t
h5t_CSET_UTF8 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
1)

{-# LINE 128 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_2 :: H5T_cset_t
h5t_CSET_RESERVED_2 :: H5T_cset_t
h5t_CSET_RESERVED_2 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
2)

{-# LINE 131 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_3 :: H5T_cset_t
h5t_CSET_RESERVED_3 :: H5T_cset_t
h5t_CSET_RESERVED_3 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
3)

{-# LINE 134 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_4 :: H5T_cset_t
h5t_CSET_RESERVED_4 :: H5T_cset_t
h5t_CSET_RESERVED_4 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
4)

{-# LINE 137 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_5 :: H5T_cset_t
h5t_CSET_RESERVED_5 :: H5T_cset_t
h5t_CSET_RESERVED_5 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
5)

{-# LINE 140 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_6 :: H5T_cset_t
h5t_CSET_RESERVED_6 :: H5T_cset_t
h5t_CSET_RESERVED_6 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
6)

{-# LINE 143 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_7 :: H5T_cset_t
h5t_CSET_RESERVED_7 :: H5T_cset_t
h5t_CSET_RESERVED_7 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
7)

{-# LINE 146 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_8 :: H5T_cset_t
h5t_CSET_RESERVED_8 :: H5T_cset_t
h5t_CSET_RESERVED_8 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
8)

{-# LINE 149 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_9 :: H5T_cset_t
h5t_CSET_RESERVED_9 :: H5T_cset_t
h5t_CSET_RESERVED_9 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
9)

{-# LINE 152 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_10 :: H5T_cset_t
h5t_CSET_RESERVED_10 :: H5T_cset_t
h5t_CSET_RESERVED_10 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
10)

{-# LINE 155 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_11 :: H5T_cset_t
h5t_CSET_RESERVED_11 :: H5T_cset_t
h5t_CSET_RESERVED_11 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
11)

{-# LINE 158 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_12 :: H5T_cset_t
h5t_CSET_RESERVED_12 :: H5T_cset_t
h5t_CSET_RESERVED_12 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
12)

{-# LINE 161 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_13 :: H5T_cset_t
h5t_CSET_RESERVED_13 :: H5T_cset_t
h5t_CSET_RESERVED_13 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
13)

{-# LINE 164 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_14 :: H5T_cset_t
h5t_CSET_RESERVED_14 :: H5T_cset_t
h5t_CSET_RESERVED_14 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
14)

{-# LINE 167 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_CSET_RESERVED_15 :: H5T_cset_t
h5t_CSET_RESERVED_15 :: H5T_cset_t
h5t_CSET_RESERVED_15 = Int32 -> H5T_cset_t
H5T_cset_t (Int32
15)

{-# LINE 170 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Number of character sets actually defined
h5t_NCSET = 2
h5t_NCSET :: (Num a) => a

{-# LINE 173 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Type of padding to use in character strings.  Do not change these values
-- since they appear in HDF5 files!
newtype H5T_str_t = H5T_str_t Int32 deriving (Ptr H5T_str_t -> IO H5T_str_t
Ptr H5T_str_t -> Int -> IO H5T_str_t
Ptr H5T_str_t -> Int -> H5T_str_t -> IO ()
Ptr H5T_str_t -> H5T_str_t -> IO ()
H5T_str_t -> Int
(H5T_str_t -> Int)
-> (H5T_str_t -> Int)
-> (Ptr H5T_str_t -> Int -> IO H5T_str_t)
-> (Ptr H5T_str_t -> Int -> H5T_str_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5T_str_t)
-> (forall b. Ptr b -> Int -> H5T_str_t -> IO ())
-> (Ptr H5T_str_t -> IO H5T_str_t)
-> (Ptr H5T_str_t -> H5T_str_t -> IO ())
-> Storable H5T_str_t
forall b. Ptr b -> Int -> IO H5T_str_t
forall b. Ptr b -> Int -> H5T_str_t -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: H5T_str_t -> Int
sizeOf :: H5T_str_t -> Int
$calignment :: H5T_str_t -> Int
alignment :: H5T_str_t -> Int
$cpeekElemOff :: Ptr H5T_str_t -> Int -> IO H5T_str_t
peekElemOff :: Ptr H5T_str_t -> Int -> IO H5T_str_t
$cpokeElemOff :: Ptr H5T_str_t -> Int -> H5T_str_t -> IO ()
pokeElemOff :: Ptr H5T_str_t -> Int -> H5T_str_t -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5T_str_t
peekByteOff :: forall b. Ptr b -> Int -> IO H5T_str_t
$cpokeByteOff :: forall b. Ptr b -> Int -> H5T_str_t -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5T_str_t -> IO ()
$cpeek :: Ptr H5T_str_t -> IO H5T_str_t
peek :: Ptr H5T_str_t -> IO H5T_str_t
$cpoke :: Ptr H5T_str_t -> H5T_str_t -> IO ()
poke :: Ptr H5T_str_t -> H5T_str_t -> IO ()
Storable, Int -> H5T_str_t -> ShowS
[H5T_str_t] -> ShowS
H5T_str_t -> String
(Int -> H5T_str_t -> ShowS)
-> (H5T_str_t -> String)
-> ([H5T_str_t] -> ShowS)
-> Show H5T_str_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5T_str_t -> ShowS
showsPrec :: Int -> H5T_str_t -> ShowS
$cshow :: H5T_str_t -> String
show :: H5T_str_t -> String
$cshowList :: [H5T_str_t] -> ShowS
showList :: [H5T_str_t] -> ShowS
Show, H5T_str_t -> H5T_str_t -> Bool
(H5T_str_t -> H5T_str_t -> Bool)
-> (H5T_str_t -> H5T_str_t -> Bool) -> Eq H5T_str_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5T_str_t -> H5T_str_t -> Bool
== :: H5T_str_t -> H5T_str_t -> Bool
$c/= :: H5T_str_t -> H5T_str_t -> Bool
/= :: H5T_str_t -> H5T_str_t -> Bool
Eq)

{-# LINE 177 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_STR_ERROR :: H5T_str_t
h5t_STR_ERROR :: H5T_str_t
h5t_STR_ERROR = Int32 -> H5T_str_t
H5T_str_t (-Int32
1)

{-# LINE 180 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |null terminate like in C
h5t_STR_NULLTERM :: H5T_str_t
h5t_STR_NULLTERM :: H5T_str_t
h5t_STR_NULLTERM = Int32 -> H5T_str_t
H5T_str_t (Int32
0)

{-# LINE 183 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |pad with nulls
h5t_STR_NULLPAD :: H5T_str_t
h5t_STR_NULLPAD :: H5T_str_t
h5t_STR_NULLPAD = Int32 -> H5T_str_t
H5T_str_t (Int32
1)

{-# LINE 186 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |pad with spaces like in Fortran
h5t_STR_SPACEPAD :: H5T_str_t
h5t_STR_SPACEPAD :: H5T_str_t
h5t_STR_SPACEPAD = Int32 -> H5T_str_t
H5T_str_t (Int32
2)

{-# LINE 189 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_3 :: H5T_str_t
h5t_STR_RESERVED_3 :: H5T_str_t
h5t_STR_RESERVED_3 = Int32 -> H5T_str_t
H5T_str_t (Int32
3)

{-# LINE 192 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_4 :: H5T_str_t
h5t_STR_RESERVED_4 :: H5T_str_t
h5t_STR_RESERVED_4 = Int32 -> H5T_str_t
H5T_str_t (Int32
4)

{-# LINE 195 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_5 :: H5T_str_t
h5t_STR_RESERVED_5 :: H5T_str_t
h5t_STR_RESERVED_5 = Int32 -> H5T_str_t
H5T_str_t (Int32
5)

{-# LINE 198 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_6 :: H5T_str_t
h5t_STR_RESERVED_6 :: H5T_str_t
h5t_STR_RESERVED_6 = Int32 -> H5T_str_t
H5T_str_t (Int32
6)

{-# LINE 201 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_7 :: H5T_str_t
h5t_STR_RESERVED_7 :: H5T_str_t
h5t_STR_RESERVED_7 = Int32 -> H5T_str_t
H5T_str_t (Int32
7)

{-# LINE 204 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_8 :: H5T_str_t
h5t_STR_RESERVED_8 :: H5T_str_t
h5t_STR_RESERVED_8 = Int32 -> H5T_str_t
H5T_str_t (Int32
8)

{-# LINE 207 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_9 :: H5T_str_t
h5t_STR_RESERVED_9 :: H5T_str_t
h5t_STR_RESERVED_9 = Int32 -> H5T_str_t
H5T_str_t (Int32
9)

{-# LINE 210 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_10 :: H5T_str_t
h5t_STR_RESERVED_10 :: H5T_str_t
h5t_STR_RESERVED_10 = Int32 -> H5T_str_t
H5T_str_t (Int32
10)

{-# LINE 213 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_11 :: H5T_str_t
h5t_STR_RESERVED_11 :: H5T_str_t
h5t_STR_RESERVED_11 = Int32 -> H5T_str_t
H5T_str_t (Int32
11)

{-# LINE 216 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_12 :: H5T_str_t
h5t_STR_RESERVED_12 :: H5T_str_t
h5t_STR_RESERVED_12 = Int32 -> H5T_str_t
H5T_str_t (Int32
12)

{-# LINE 219 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_13 :: H5T_str_t
h5t_STR_RESERVED_13 :: H5T_str_t
h5t_STR_RESERVED_13 = Int32 -> H5T_str_t
H5T_str_t (Int32
13)

{-# LINE 222 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_14 :: H5T_str_t
h5t_STR_RESERVED_14 :: H5T_str_t
h5t_STR_RESERVED_14 = Int32 -> H5T_str_t
H5T_str_t (Int32
14)

{-# LINE 225 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |reserved for later use
h5t_STR_RESERVED_15 :: H5T_str_t
h5t_STR_RESERVED_15 :: H5T_str_t
h5t_STR_RESERVED_15 = Int32 -> H5T_str_t
H5T_str_t (Int32
15)

h5t_NSTR :: forall a. Num a => a
{-# LINE 228 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |num 'H5T_str_t' types actually defined
h5t_NSTR = 3
h5t_NSTR :: (Num a) => a

{-# LINE 231 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Type of padding to use in other atomic types
newtype H5T_pad_t = H5T_pad_t Int32 deriving (Storable, Show, Eq)

{-# LINE 234 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |error
h5t_PAD_ERROR :: H5T_pad_t
h5t_PAD_ERROR :: H5T_pad_t
h5t_PAD_ERROR = Int32 -> H5T_pad_t
H5T_pad_t (-Int32
1)

{-# LINE 237 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |always set to zero
h5t_PAD_ZERO :: H5T_pad_t
h5t_PAD_ZERO :: H5T_pad_t
h5t_PAD_ZERO = Int32 -> H5T_pad_t
H5T_pad_t (Int32
0)

{-# LINE 240 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |always set to one
h5t_PAD_ONE :: H5T_pad_t
h5t_PAD_ONE :: H5T_pad_t
h5t_PAD_ONE = Int32 -> H5T_pad_t
H5T_pad_t (Int32
1)

{-# LINE 243 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |set to background value
h5t_PAD_BACKGROUND :: H5T_pad_t
h5t_PAD_BACKGROUND :: H5T_pad_t
h5t_PAD_BACKGROUND = Int32 -> H5T_pad_t
H5T_pad_t (Int32
2)

h5t_NPAD :: forall a. Num a => a
{-# LINE 246 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Number of valid 'H5T_pad_t' values.
h5t_NPAD = 3
h5t_NPAD :: (Num a) => a

{-# LINE 249 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Commands sent to conversion functions
newtype H5T_cmd_t = H5T_cmd_t Word32 deriving (Storable, Show, Eq)

{-# LINE 252 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |query and/or initialize private data
h5t_CONV_INIT :: H5T_cmd_t
h5t_CONV_INIT :: H5T_cmd_t
h5t_CONV_INIT = Word32 -> H5T_cmd_t
H5T_cmd_t (Word32
0)

{-# LINE 255 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |convert data from source to dest datatype
h5t_CONV_CONV :: H5T_cmd_t
h5t_CONV_CONV :: H5T_cmd_t
h5t_CONV_CONV = Word32 -> H5T_cmd_t
H5T_cmd_t (Word32
1)

{-# LINE 258 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |function is being removed from path
h5t_CONV_FREE :: H5T_cmd_t
h5t_CONV_FREE :: H5T_cmd_t
h5t_CONV_FREE = Word32 -> H5T_cmd_t
H5T_cmd_t (Word32
2)

{-# LINE 261 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |How is the 'bkg' buffer used by the conversion function?
newtype H5T_bkg_t = H5T_bkg_t Word32 deriving (Storable, Show, Eq)

{-# LINE 264 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |background buffer is not needed, send NULL
h5t_BKG_NO :: H5T_bkg_t
h5t_BKG_NO :: H5T_bkg_t
h5t_BKG_NO = Word32 -> H5T_bkg_t
H5T_bkg_t (Word32
0)

{-# LINE 267 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |bkg buffer used as temp storage only
h5t_BKG_TEMP :: H5T_bkg_t
h5t_BKG_TEMP :: H5T_bkg_t
h5t_BKG_TEMP = Word32 -> H5T_bkg_t
H5T_bkg_t (Word32
1)

{-# LINE 270 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |init bkg buf with data before conversion
h5t_BKG_YES :: H5T_bkg_t
h5t_BKG_YES :: H5T_bkg_t
h5t_BKG_YES = Word32 -> H5T_bkg_t
H5T_bkg_t (Word32
2)

{-# LINE 273 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Type conversion client data
data H5T_cdata_t a = H5T_cdata_t {

    -- |what should the conversion function do?
    h5t_cdata_t'command   :: H5T_cmd_t,

    -- |is the background buffer needed?
    h5t_cdata_t'need_bkg  :: H5T_bkg_t,

    -- |recalculate private data
    h5t_cdata_t'recalc    :: HBool_t,

    -- |private data
    h5t_cdata_t'priv      :: Ptr a}

    deriving (Eq,Show)

instance Storable (H5T_cdata_t a) where
  sizeOf :: H5T_cdata_t a -> Int
sizeOf H5T_cdata_t a
_ = (Int
24)
{-# LINE 293 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
  alignment = sizeOf
  peek :: Ptr (H5T_cdata_t a) -> IO (H5T_cdata_t a)
peek Ptr (H5T_cdata_t a)
p = do
    H5T_cmd_t
v0 <- (\Ptr (H5T_cdata_t a)
hsc_ptr -> Ptr (H5T_cdata_t a) -> Int -> IO H5T_cmd_t
forall b. Ptr b -> Int -> IO H5T_cmd_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr (H5T_cdata_t a)
hsc_ptr Int
0)  Ptr (H5T_cdata_t a)
p
{-# LINE 296 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    v1 <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 297 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    v2 <- (\hsc_ptr -> peekByteOff hsc_ptr 8)   p
{-# LINE 298 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    v3 <- (\hsc_ptr -> peekByteOff hsc_ptr 16)     p
{-# LINE 299 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    return $ H5T_cdata_t v0 v1 v2 v3
  poke :: Ptr (H5T_cdata_t a) -> H5T_cdata_t a -> IO ()
poke Ptr (H5T_cdata_t a)
p (H5T_cdata_t H5T_cmd_t
v0 H5T_bkg_t
v1 HBool_t
v2 Ptr a
v3) = do
    (\Ptr (H5T_cdata_t a)
hsc_ptr -> Ptr (H5T_cdata_t a) -> Int -> H5T_cmd_t -> IO ()
forall b. Ptr b -> Int -> H5T_cmd_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr (H5T_cdata_t a)
hsc_ptr Int
0)  Ptr (H5T_cdata_t a)
p H5T_cmd_t
v0
{-# LINE 302 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 4) p v1
{-# LINE 303 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8)   p v2
{-# LINE 304 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 16)     p v3
{-# LINE 305 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
    return ()

-- |Conversion function persistence
newtype H5T_pers_t = H5T_pers_t Int32 deriving (Ptr H5T_pers_t -> IO H5T_pers_t
Ptr H5T_pers_t -> Int -> IO H5T_pers_t
Ptr H5T_pers_t -> Int -> H5T_pers_t -> IO ()
Ptr H5T_pers_t -> H5T_pers_t -> IO ()
H5T_pers_t -> Int
(H5T_pers_t -> Int)
-> (H5T_pers_t -> Int)
-> (Ptr H5T_pers_t -> Int -> IO H5T_pers_t)
-> (Ptr H5T_pers_t -> Int -> H5T_pers_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5T_pers_t)
-> (forall b. Ptr b -> Int -> H5T_pers_t -> IO ())
-> (Ptr H5T_pers_t -> IO H5T_pers_t)
-> (Ptr H5T_pers_t -> H5T_pers_t -> IO ())
-> Storable H5T_pers_t
forall b. Ptr b -> Int -> IO H5T_pers_t
forall b. Ptr b -> Int -> H5T_pers_t -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: H5T_pers_t -> Int
sizeOf :: H5T_pers_t -> Int
$calignment :: H5T_pers_t -> Int
alignment :: H5T_pers_t -> Int
$cpeekElemOff :: Ptr H5T_pers_t -> Int -> IO H5T_pers_t
peekElemOff :: Ptr H5T_pers_t -> Int -> IO H5T_pers_t
$cpokeElemOff :: Ptr H5T_pers_t -> Int -> H5T_pers_t -> IO ()
pokeElemOff :: Ptr H5T_pers_t -> Int -> H5T_pers_t -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5T_pers_t
peekByteOff :: forall b. Ptr b -> Int -> IO H5T_pers_t
$cpokeByteOff :: forall b. Ptr b -> Int -> H5T_pers_t -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5T_pers_t -> IO ()
$cpeek :: Ptr H5T_pers_t -> IO H5T_pers_t
peek :: Ptr H5T_pers_t -> IO H5T_pers_t
$cpoke :: Ptr H5T_pers_t -> H5T_pers_t -> IO ()
poke :: Ptr H5T_pers_t -> H5T_pers_t -> IO ()
Storable, Int -> H5T_pers_t -> ShowS
[H5T_pers_t] -> ShowS
H5T_pers_t -> String
(Int -> H5T_pers_t -> ShowS)
-> (H5T_pers_t -> String)
-> ([H5T_pers_t] -> ShowS)
-> Show H5T_pers_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5T_pers_t -> ShowS
showsPrec :: Int -> H5T_pers_t -> ShowS
$cshow :: H5T_pers_t -> String
show :: H5T_pers_t -> String
$cshowList :: [H5T_pers_t] -> ShowS
showList :: [H5T_pers_t] -> ShowS
Show)

{-# LINE 309 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |wild card
h5t_PERS_DONTCARE :: H5T_pers_t
h5t_PERS_DONTCARE :: H5T_pers_t
h5t_PERS_DONTCARE = Int32 -> H5T_pers_t
H5T_pers_t (-Int32
1)

{-# LINE 312 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |hard conversion function
h5t_PERS_HARD :: H5T_pers_t
h5t_PERS_HARD :: H5T_pers_t
h5t_PERS_HARD = Int32 -> H5T_pers_t
H5T_pers_t (Int32
0)

{-# LINE 315 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |soft conversion function
h5t_PERS_SOFT :: H5T_pers_t
h5t_PERS_SOFT :: H5T_pers_t
h5t_PERS_SOFT = Int32 -> H5T_pers_t
H5T_pers_t (Int32
1)

{-# LINE 318 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The order to retrieve atomic native datatype
newtype H5T_direction_t = H5T_direction_t Word32 deriving (Storable, Show)

{-# LINE 321 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |default direction is inscendent
h5t_DIR_DEFAULT :: H5T_direction_t
h5t_DIR_DEFAULT :: H5T_direction_t
h5t_DIR_DEFAULT = Word32 -> H5T_direction_t
H5T_direction_t (Word32
0)

{-# LINE 324 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |in inscendent order
h5t_DIR_ASCEND :: H5T_direction_t
h5t_DIR_ASCEND :: H5T_direction_t
h5t_DIR_ASCEND = Word32 -> H5T_direction_t
H5T_direction_t (Word32
1)

{-# LINE 327 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |in descendent order
h5t_DIR_DESCEND :: H5T_direction_t
h5t_DIR_DESCEND :: H5T_direction_t
h5t_DIR_DESCEND = Word32 -> H5T_direction_t
H5T_direction_t (Word32
2)

{-# LINE 330 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The exception type passed into the conversion callback function
newtype H5T_conv_except_t = H5T_conv_except_t Word32 deriving (Storable, Show)

{-# LINE 333 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value is greater than destination's range
h5t_CONV_EXCEPT_RANGE_HI :: H5T_conv_except_t
h5t_CONV_EXCEPT_RANGE_HI :: H5T_conv_except_t
h5t_CONV_EXCEPT_RANGE_HI = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
0)

{-# LINE 336 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value is less than destination's range
h5t_CONV_EXCEPT_RANGE_LOW :: H5T_conv_except_t
h5t_CONV_EXCEPT_RANGE_LOW :: H5T_conv_except_t
h5t_CONV_EXCEPT_RANGE_LOW = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
1)

{-# LINE 339 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value loses precision in destination
h5t_CONV_EXCEPT_PRECISION :: H5T_conv_except_t
h5t_CONV_EXCEPT_PRECISION :: H5T_conv_except_t
h5t_CONV_EXCEPT_PRECISION = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
2)

{-# LINE 342 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value is truncated in destination
h5t_CONV_EXCEPT_TRUNCATE :: H5T_conv_except_t
h5t_CONV_EXCEPT_TRUNCATE :: H5T_conv_except_t
h5t_CONV_EXCEPT_TRUNCATE = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
3)

{-# LINE 345 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value is positive infinity(floating number)
h5t_CONV_EXCEPT_PINF :: H5T_conv_except_t
h5t_CONV_EXCEPT_PINF :: H5T_conv_except_t
h5t_CONV_EXCEPT_PINF = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
4)

{-# LINE 348 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value is negative infinity(floating number)
h5t_CONV_EXCEPT_NINF :: H5T_conv_except_t
h5t_CONV_EXCEPT_NINF :: H5T_conv_except_t
h5t_CONV_EXCEPT_NINF = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
5)

{-# LINE 351 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |source value is NaN(floating number)
h5t_CONV_EXCEPT_NAN :: H5T_conv_except_t
h5t_CONV_EXCEPT_NAN :: H5T_conv_except_t
h5t_CONV_EXCEPT_NAN = Word32 -> H5T_conv_except_t
H5T_conv_except_t (Word32
6)

{-# LINE 354 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The return value from conversion callback function 'h5t_conv_except_func_t'
newtype H5T_conv_ret_t = H5T_conv_ret_t Int32 deriving (Storable, Show)

{-# LINE 357 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |abort conversion
h5t_CONV_ABORT :: H5T_conv_ret_t
h5t_CONV_ABORT :: H5T_conv_ret_t
h5t_CONV_ABORT = Int32 -> H5T_conv_ret_t
H5T_conv_ret_t (-Int32
1)

{-# LINE 360 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |callback function failed to handle the exception
h5t_CONV_UNHANDLED :: H5T_conv_ret_t
h5t_CONV_UNHANDLED :: H5T_conv_ret_t
h5t_CONV_UNHANDLED = Int32 -> H5T_conv_ret_t
H5T_conv_ret_t (Int32
0)

{-# LINE 363 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |callback function handled the exception successfully
h5t_CONV_HANDLED :: H5T_conv_ret_t
h5t_CONV_HANDLED :: H5T_conv_ret_t
h5t_CONV_HANDLED = Int32 -> H5T_conv_ret_t
H5T_conv_ret_t (Int32
1)

{-# LINE 366 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Variable Length Datatype struct in memory
-- (This is only used for VL sequences, not VL strings, which are stored in char *'s)

{-# LINE 370 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Length of VL data (in base type units)

{-# LINE 373 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Pointer to VL data

{-# LINE 376 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

data HVl_t = HVl_t{
  HVl_t -> CSize
hvl_t'len :: CSize,
  hvl_t'p :: Ptr ()
} deriving (HVl_t -> HVl_t -> Bool
(HVl_t -> HVl_t -> Bool) -> (HVl_t -> HVl_t -> Bool) -> Eq HVl_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HVl_t -> HVl_t -> Bool
== :: HVl_t -> HVl_t -> Bool
$c/= :: HVl_t -> HVl_t -> Bool
/= :: HVl_t -> HVl_t -> Bool
Eq,Int -> HVl_t -> ShowS
[HVl_t] -> ShowS
HVl_t -> String
(Int -> HVl_t -> ShowS)
-> (HVl_t -> String) -> ([HVl_t] -> ShowS) -> Show HVl_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HVl_t -> ShowS
showsPrec :: Int -> HVl_t -> ShowS
$cshow :: HVl_t -> String
show :: HVl_t -> String
$cshowList :: [HVl_t] -> ShowS
showList :: [HVl_t] -> ShowS
Show)
p'hvl_t'len :: Ptr HVl_t -> Ptr CSize
p'hvl_t'len Ptr HVl_t
p = Ptr HVl_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr HVl_t
p Int
0
p'hvl_t'len :: Ptr (HVl_t) -> Ptr (CSize)
p'hvl_t'p :: Ptr HVl_t -> Ptr (Ptr ())
p'hvl_t'p Ptr HVl_t
p = Ptr HVl_t -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr HVl_t
p Int
8
p'hvl_t'p :: Ptr (HVl_t) -> Ptr (Ptr ())
instance Storable HVl_t where
  sizeOf :: HVl_t -> Int
sizeOf HVl_t
_ = Int
16
  alignment _ = 8
  peek :: Ptr HVl_t -> IO HVl_t
peek Ptr HVl_t
_p = do
    CSize
v0 <- Ptr HVl_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr HVl_t
_p Int
0
    Ptr ()
v1 <- Ptr HVl_t -> Int -> IO (Ptr ())
forall b. Ptr b -> Int -> IO (Ptr ())
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr HVl_t
_p Int
8
    HVl_t -> IO HVl_t
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (HVl_t -> IO HVl_t) -> HVl_t -> IO HVl_t
forall a b. (a -> b) -> a -> b
$ CSize -> Ptr () -> HVl_t
HVl_t CSize
v0 Ptr ()
v1
  poke :: Ptr HVl_t -> HVl_t -> IO ()
poke Ptr HVl_t
_p (HVl_t CSize
v0 Ptr ()
v1) = do
    Ptr HVl_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr HVl_t
_p Int
0 CSize
v0
    Ptr HVl_t -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr HVl_t
_p Int
8 Ptr ()
v1
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{-# LINE 378 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Indicate that a string is variable length (null-terminated in C, instead of fixed length)
h5t_VARIABLE :: CSize
h5t_VARIABLE = 18446744073709551615
{-# LINE 382 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Maximum length of an opaque tag.
h5t_OPAQUE_TAG_MAX = 256
h5t_OPAQUE_TAG_MAX :: (Num a) => a

{-# LINE 385 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- TODO: find documentation for this type.
type H5T_conv_t a b conversionData = FunPtr
    (HId_t -> HId_t -> Ptr (H5T_cdata_t conversionData)
    -> CSize -> CSize -> CSize -> InOutArray a -> InArray b -> HId_t
    -> IO HErr_t)

-- |Exception handler.  If an exception like overflow happens during conversion,
-- this function is called if it's registered through 'h5p_set_type_conv_cb'.
type H5T_conv_except_func_t a userData = FunPtr
    (H5T_conv_except_t -> HId_t -> HId_t -> In a -> In a -> InOut userData
    -> IO H5T_conv_ret_t)

-- * Constants identifying data types

-- ** The IEEE floating point types in various byte orders.

foreign import ccall "inline_H5T_IEEE_F32BE" h5t_IEEE_F32BE
  :: HId_t

{-# LINE 403 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_IEEE_F32LE" h5t_IEEE_F32LE
  :: HId_t

{-# LINE 404 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_IEEE_F64BE" h5t_IEEE_F64BE
  :: HId_t

{-# LINE 405 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_IEEE_F64LE" h5t_IEEE_F64LE
  :: HId_t

{-# LINE 406 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- ** \"Standard\" Types
-- These are \"standard\" types.  For instance, signed (2's complement) and
-- unsigned integers of various sizes and byte orders.

foreign import ccall "inline_H5T_STD_I8BE" h5t_STD_I8BE
  :: HId_t

{-# LINE 412 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I8LE" h5t_STD_I8LE
  :: HId_t

{-# LINE 413 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I16BE" h5t_STD_I16BE
  :: HId_t

{-# LINE 414 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I16LE" h5t_STD_I16LE
  :: HId_t

{-# LINE 415 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I32BE" h5t_STD_I32BE
  :: HId_t

{-# LINE 416 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I32LE" h5t_STD_I32LE
  :: HId_t

{-# LINE 417 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I64BE" h5t_STD_I64BE
  :: HId_t

{-# LINE 418 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_I64LE" h5t_STD_I64LE
  :: HId_t

{-# LINE 419 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U8BE" h5t_STD_U8BE
  :: HId_t

{-# LINE 420 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U8LE" h5t_STD_U8LE
  :: HId_t

{-# LINE 421 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U16BE" h5t_STD_U16BE
  :: HId_t

{-# LINE 422 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U16LE" h5t_STD_U16LE
  :: HId_t

{-# LINE 423 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U32BE" h5t_STD_U32BE
  :: HId_t

{-# LINE 424 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U32LE" h5t_STD_U32LE
  :: HId_t

{-# LINE 425 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U64BE" h5t_STD_U64BE
  :: HId_t

{-# LINE 426 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_U64LE" h5t_STD_U64LE
  :: HId_t

{-# LINE 427 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B8BE" h5t_STD_B8BE
  :: HId_t

{-# LINE 428 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B8LE" h5t_STD_B8LE
  :: HId_t

{-# LINE 429 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B16BE" h5t_STD_B16BE
  :: HId_t

{-# LINE 430 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B16LE" h5t_STD_B16LE
  :: HId_t

{-# LINE 431 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B32BE" h5t_STD_B32BE
  :: HId_t

{-# LINE 432 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B32LE" h5t_STD_B32LE
  :: HId_t

{-# LINE 433 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B64BE" h5t_STD_B64BE
  :: HId_t

{-# LINE 434 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_B64LE" h5t_STD_B64LE
  :: HId_t

{-# LINE 435 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_REF_OBJ" h5t_STD_REF_OBJ
  :: HId_t

{-# LINE 436 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_STD_REF_DSETREG" h5t_STD_REF_DSETREG
  :: HId_t

{-# LINE 437 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- ** Types which are particular to Unix.

foreign import ccall "inline_H5T_UNIX_D32BE" h5t_UNIX_D32BE
  :: HId_t

{-# LINE 441 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_UNIX_D32LE" h5t_UNIX_D32LE
  :: HId_t

{-# LINE 442 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_UNIX_D64BE" h5t_UNIX_D64BE
  :: HId_t

{-# LINE 443 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_UNIX_D64LE" h5t_UNIX_D64LE
  :: HId_t

{-# LINE 444 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- **  Types particular to the C language.
-- String types use \"bytes\" instead of \"bits\" as their size.

foreign import ccall "inline_H5T_C_S1" h5t_C_S1
  :: HId_t

{-# LINE 449 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- ** Types particular to Fortran.

foreign import ccall "inline_H5T_FORTRAN_S1" h5t_FORTRAN_S1
  :: HId_t

{-# LINE 453 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- ** Types for Intel CPUs.
-- They are little endian with IEEE floating point.
h5t_INTEL_I8, h5t_INTEL_I16, h5t_INTEL_I32, h5t_INTEL_I64 :: HId_t
h5t_INTEL_U8, h5t_INTEL_U16, h5t_INTEL_U32, h5t_INTEL_U64 :: HId_t
h5t_INTEL_B8, h5t_INTEL_B16, h5t_INTEL_B32, h5t_INTEL_B64 :: HId_t
h5t_INTEL_F32, h5t_INTEL_F64 :: HId_t

h5t_INTEL_I8 :: HId_t
h5t_INTEL_I8  = HId_t
h5t_STD_I8LE
h5t_INTEL_I16 :: HId_t
h5t_INTEL_I16 = HId_t
h5t_STD_I16LE
h5t_INTEL_I32 :: HId_t
h5t_INTEL_I32 = HId_t
h5t_STD_I32LE
h5t_INTEL_I64 :: HId_t
h5t_INTEL_I64 = HId_t
h5t_STD_I64LE
h5t_INTEL_U8 :: HId_t
h5t_INTEL_U8  = HId_t
h5t_STD_U8LE
h5t_INTEL_U16 :: HId_t
h5t_INTEL_U16 = HId_t
h5t_STD_U16LE
h5t_INTEL_U32 :: HId_t
h5t_INTEL_U32 = HId_t
h5t_STD_U32LE
h5t_INTEL_U64 :: HId_t
h5t_INTEL_U64 = HId_t
h5t_STD_U64LE
h5t_INTEL_B8 :: HId_t
h5t_INTEL_B8  = HId_t
h5t_STD_B8LE
h5t_INTEL_B16 :: HId_t
h5t_INTEL_B16 = HId_t
h5t_STD_B16LE
h5t_INTEL_B32 :: HId_t
h5t_INTEL_B32 = HId_t
h5t_STD_B32LE
h5t_INTEL_B64 :: HId_t
h5t_INTEL_B64 = HId_t
h5t_STD_B64LE
h5t_INTEL_F32 :: HId_t
h5t_INTEL_F32 = HId_t
h5t_IEEE_F32LE
h5t_INTEL_F64 :: HId_t
h5t_INTEL_F64 = HId_t
h5t_IEEE_F64LE

-- ** Types for Alpha CPUs.
-- They are little endian with IEEE floating point.

h5t_ALPHA_I8, h5t_ALPHA_I16, h5t_ALPHA_I32, h5t_ALPHA_I64 :: HId_t
h5t_ALPHA_U8, h5t_ALPHA_U16, h5t_ALPHA_U32, h5t_ALPHA_U64 :: HId_t
h5t_ALPHA_B8, h5t_ALPHA_B16, h5t_ALPHA_B32, h5t_ALPHA_B64 :: HId_t
h5t_ALPHA_F32, h5t_ALPHA_F64 :: HId_t

h5t_ALPHA_I8 :: HId_t
h5t_ALPHA_I8  = HId_t
h5t_STD_I8LE
h5t_ALPHA_I16 :: HId_t
h5t_ALPHA_I16 = HId_t
h5t_STD_I16LE
h5t_ALPHA_I32 :: HId_t
h5t_ALPHA_I32 = HId_t
h5t_STD_I32LE
h5t_ALPHA_I64 :: HId_t
h5t_ALPHA_I64 = HId_t
h5t_STD_I64LE
h5t_ALPHA_U8 :: HId_t
h5t_ALPHA_U8  = HId_t
h5t_STD_U8LE
h5t_ALPHA_U16 :: HId_t
h5t_ALPHA_U16 = HId_t
h5t_STD_U16LE
h5t_ALPHA_U32 :: HId_t
h5t_ALPHA_U32 = HId_t
h5t_STD_U32LE
h5t_ALPHA_U64 :: HId_t
h5t_ALPHA_U64 = HId_t
h5t_STD_U64LE
h5t_ALPHA_B8 :: HId_t
h5t_ALPHA_B8  = HId_t
h5t_STD_B8LE
h5t_ALPHA_B16 :: HId_t
h5t_ALPHA_B16 = HId_t
h5t_STD_B16LE
h5t_ALPHA_B32 :: HId_t
h5t_ALPHA_B32 = HId_t
h5t_STD_B32LE
h5t_ALPHA_B64 :: HId_t
h5t_ALPHA_B64 = HId_t
h5t_STD_B64LE
h5t_ALPHA_F32 :: HId_t
h5t_ALPHA_F32 = HId_t
h5t_IEEE_F32LE
h5t_ALPHA_F64 :: HId_t
h5t_ALPHA_F64 = HId_t
h5t_IEEE_F64LE

-- ** Types for MIPS CPUs.
-- They are big endian with IEEE floating point.

h5t_MIPS_I8, h5t_MIPS_I16, h5t_MIPS_I32, h5t_MIPS_I64 :: HId_t
h5t_MIPS_U8, h5t_MIPS_U16, h5t_MIPS_U32, h5t_MIPS_U64 :: HId_t
h5t_MIPS_B8, h5t_MIPS_B16, h5t_MIPS_B32, h5t_MIPS_B64 :: HId_t
h5t_MIPS_F32, h5t_MIPS_F64 :: HId_t

h5t_MIPS_I8 :: HId_t
h5t_MIPS_I8  = HId_t
h5t_STD_I8BE
h5t_MIPS_I16 :: HId_t
h5t_MIPS_I16 = HId_t
h5t_STD_I16BE
h5t_MIPS_I32 :: HId_t
h5t_MIPS_I32 = HId_t
h5t_STD_I32BE
h5t_MIPS_I64 :: HId_t
h5t_MIPS_I64 = HId_t
h5t_STD_I64BE
h5t_MIPS_U8 :: HId_t
h5t_MIPS_U8  = HId_t
h5t_STD_U8BE
h5t_MIPS_U16 :: HId_t
h5t_MIPS_U16 = HId_t
h5t_STD_U16BE
h5t_MIPS_U32 :: HId_t
h5t_MIPS_U32 = HId_t
h5t_STD_U32BE
h5t_MIPS_U64 :: HId_t
h5t_MIPS_U64 = HId_t
h5t_STD_U64BE
h5t_MIPS_B8 :: HId_t
h5t_MIPS_B8  = HId_t
h5t_STD_B8BE
h5t_MIPS_B16 :: HId_t
h5t_MIPS_B16 = HId_t
h5t_STD_B16BE
h5t_MIPS_B32 :: HId_t
h5t_MIPS_B32 = HId_t
h5t_STD_B32BE
h5t_MIPS_B64 :: HId_t
h5t_MIPS_B64 = HId_t
h5t_STD_B64BE
h5t_MIPS_F32 :: HId_t
h5t_MIPS_F32 = HId_t
h5t_IEEE_F32BE
h5t_MIPS_F64 :: HId_t
h5t_MIPS_F64 = HId_t
h5t_IEEE_F64BE

-- ** VAX floating point types (i.e. in VAX byte order)

foreign import ccall "inline_H5T_VAX_F32" h5t_VAX_F32
  :: HId_t

{-# LINE 525 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_VAX_F64" h5t_VAX_F64
  :: HId_t

{-# LINE 526 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- ** Predefined native types.
-- These are the types detected by 'h5_detect' and they violate the naming
-- scheme a little.  Instead of a class name, precision and byte order as
-- the last component, they have a C-like type name.
-- If the type begins with 'U' then it is the unsigned version of the
-- integer type; other integer types are signed.  The type LLONG corresponds
-- to C's 'long long' and LDOUBLE is 'long double' (these types might be the
-- same as 'LONG' and 'DOUBLE' respectively).

foreign import ccall "inline_H5T_NATIVE_CHAR" h5t_NATIVE_CHAR
  :: HId_t

{-# LINE 537 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_SCHAR" h5t_NATIVE_SCHAR
  :: HId_t

{-# LINE 538 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UCHAR" h5t_NATIVE_UCHAR
  :: HId_t

{-# LINE 539 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_SHORT" h5t_NATIVE_SHORT
  :: HId_t

{-# LINE 540 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_USHORT" h5t_NATIVE_USHORT
  :: HId_t

{-# LINE 541 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT" h5t_NATIVE_INT
  :: HId_t

{-# LINE 542 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT" h5t_NATIVE_UINT
  :: HId_t

{-# LINE 543 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_LONG" h5t_NATIVE_LONG
  :: HId_t

{-# LINE 544 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_ULONG" h5t_NATIVE_ULONG
  :: HId_t

{-# LINE 545 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_LLONG" h5t_NATIVE_LLONG
  :: HId_t

{-# LINE 546 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_ULLONG" h5t_NATIVE_ULLONG
  :: HId_t

{-# LINE 547 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_FLOAT" h5t_NATIVE_FLOAT
  :: HId_t

{-# LINE 548 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_DOUBLE" h5t_NATIVE_DOUBLE
  :: HId_t

{-# LINE 549 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

{-# LINE 550 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_LDOUBLE" h5t_NATIVE_LDOUBLE
  :: HId_t

{-# LINE 551 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

{-# LINE 552 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_B8" h5t_NATIVE_B8
  :: HId_t

{-# LINE 553 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_B16" h5t_NATIVE_B16
  :: HId_t

{-# LINE 554 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_B32" h5t_NATIVE_B32
  :: HId_t

{-# LINE 555 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_B64" h5t_NATIVE_B64
  :: HId_t

{-# LINE 556 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_OPAQUE" h5t_NATIVE_OPAQUE
  :: HId_t

{-# LINE 557 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_HADDR" h5t_NATIVE_HADDR
  :: HId_t

{-# LINE 558 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_HSIZE" h5t_NATIVE_HSIZE
  :: HId_t

{-# LINE 559 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_HSSIZE" h5t_NATIVE_HSSIZE
  :: HId_t

{-# LINE 560 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_HERR" h5t_NATIVE_HERR
  :: HId_t

{-# LINE 561 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_HBOOL" h5t_NATIVE_HBOOL
  :: HId_t

{-# LINE 562 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- ** C9x integer types

foreign import ccall "inline_H5T_NATIVE_INT8" h5t_NATIVE_INT8
  :: HId_t

{-# LINE 566 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT8" h5t_NATIVE_UINT8
  :: HId_t

{-# LINE 567 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_LEAST8" h5t_NATIVE_INT_LEAST8
  :: HId_t

{-# LINE 568 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_LEAST8" h5t_NATIVE_UINT_LEAST8
  :: HId_t

{-# LINE 569 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_FAST8" h5t_NATIVE_INT_FAST8
  :: HId_t

{-# LINE 570 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_FAST8" h5t_NATIVE_UINT_FAST8
  :: HId_t

{-# LINE 571 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

foreign import ccall "inline_H5T_NATIVE_INT16" h5t_NATIVE_INT16
  :: HId_t

{-# LINE 573 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT16" h5t_NATIVE_UINT16
  :: HId_t

{-# LINE 574 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_LEAST16" h5t_NATIVE_INT_LEAST16
  :: HId_t

{-# LINE 575 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_LEAST16" h5t_NATIVE_UINT_LEAST16
  :: HId_t

{-# LINE 576 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_FAST16" h5t_NATIVE_INT_FAST16
  :: HId_t

{-# LINE 577 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_FAST16" h5t_NATIVE_UINT_FAST16
  :: HId_t

{-# LINE 578 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

foreign import ccall "inline_H5T_NATIVE_INT32" h5t_NATIVE_INT32
  :: HId_t

{-# LINE 580 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT32" h5t_NATIVE_UINT32
  :: HId_t

{-# LINE 581 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_LEAST32" h5t_NATIVE_INT_LEAST32
  :: HId_t

{-# LINE 582 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_LEAST32" h5t_NATIVE_UINT_LEAST32
  :: HId_t

{-# LINE 583 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_FAST32" h5t_NATIVE_INT_FAST32
  :: HId_t

{-# LINE 584 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_FAST32" h5t_NATIVE_UINT_FAST32
  :: HId_t

{-# LINE 585 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

foreign import ccall "inline_H5T_NATIVE_INT64" h5t_NATIVE_INT64
  :: HId_t

{-# LINE 587 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT64" h5t_NATIVE_UINT64
  :: HId_t

{-# LINE 588 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_LEAST64" h5t_NATIVE_INT_LEAST64
  :: HId_t

{-# LINE 589 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_LEAST64" h5t_NATIVE_UINT_LEAST64
  :: HId_t

{-# LINE 590 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_INT_FAST64" h5t_NATIVE_INT_FAST64
  :: HId_t

{-# LINE 591 "src/Bindings/HDF5/Raw/H5T.hsc" #-}
foreign import ccall "inline_H5T_NATIVE_UINT_FAST64" h5t_NATIVE_UINT_FAST64
  :: HId_t

{-# LINE 592 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Operations defined on all datatypes

-- |Create a new type and initialize it to reasonable values.
-- The type is a member of type class 'type' and is 'size' bytes.
--
-- On success, returns a new type identifier.  On failure, returns
-- a negative value.
--
-- > hid_t H5Tcreate(H5T_class_t type, size_t size);
foreign import ccall "H5Tcreate" h5t_create
  :: H5T_class_t -> CSize -> IO HId_t
foreign import ccall "&H5Tcreate" p_H5Tcreate
  :: FunPtr (H5T_class_t -> CSize -> IO HId_t)

{-# LINE 603 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Copies a datatype.  The resulting datatype is not locked.
-- The datatype should be closed when no longer needed by
-- calling 'h5t_close'.
--
-- Returns the ID of a new datatype on success, negative on failure.
--
-- > hid_t H5Tcopy(hid_t type_id);
foreign import ccall "H5Tcopy" h5t_copy
  :: HId_t -> IO HId_t
foreign import ccall "&H5Tcopy" p_H5Tcopy
  :: FunPtr (HId_t -> IO HId_t)

{-# LINE 612 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Frees a datatype and all associated memory.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tclose(hid_t type_id);
foreign import ccall "H5Tclose" h5t_close
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Tclose" p_H5Tclose
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 619 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Determines if two datatypes are equal.
--
-- > htri_t H5Tequal(hid_t type1_id, hid_t type2_id);
foreign import ccall "H5Tequal" h5t_equal
  :: HId_t -> HId_t -> IO HTri_t
foreign import ccall "&H5Tequal" p_H5Tequal
  :: FunPtr (HId_t -> HId_t -> IO HTri_t)

{-# LINE 624 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Locks a type, making it read only and non-destructable.  This
-- is normally done by the library for predefined datatypes so
-- the application doesn't inadvertently change or delete a
-- predefined type.
--
-- Once a datatype is locked it can never be unlocked unless
-- the entire library is closed.
--
-- It is illegal to lock a named datatype since we must allow named
-- types to be closed (to release file resources) but locking a type
-- prevents that.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tlock(hid_t type_id);
foreign import ccall "H5Tlock" h5t_lock
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Tlock" p_H5Tlock
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 641 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Save a transient datatype to a file and turn the type handle
-- into a \"named\", immutable type.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tcommit2(hid_t loc_id, const char *name, hid_t type_id,
-- >     hid_t lcpl_id, hid_t tcpl_id, hid_t tapl_id);
foreign import ccall "H5Tcommit2" h5t_commit2
  :: HId_t -> CString -> HId_t -> HId_t -> HId_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Tcommit2" p_H5Tcommit2
  :: FunPtr (HId_t -> CString -> HId_t -> HId_t -> HId_t -> HId_t -> IO HErr_t)

{-# LINE 650 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Opens a named datatype using a Datatype Access Property
--     List.
--
-- Returns the object ID of the named datatype on success, negative
-- on failure.
--
-- > hid_t H5Topen2(hid_t loc_id, const char *name, hid_t tapl_id);
foreign import ccall "H5Topen2" h5t_open2
  :: HId_t -> CString -> HId_t -> IO HId_t
foreign import ccall "&H5Topen2" p_H5Topen2
  :: FunPtr (HId_t -> CString -> HId_t -> IO HId_t)

{-# LINE 659 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Save a transient datatype to a file and turn the type handle
-- into a \"named\", immutable type.
--
-- The resulting ID should be linked into the file with
-- 'h5o_link' or it will be deleted when closed.
--
-- Note:  Datatype access property list is unused currently, but is
-- checked for sanity anyway.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tcommit_anon(hid_t loc_id, hid_t type_id, hid_t tcpl_id, hid_t tapl_id);
foreign import ccall "H5Tcommit_anon" h5t_commit_anon
  :: HId_t -> HId_t -> HId_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Tcommit_anon" p_H5Tcommit_anon
  :: FunPtr (HId_t -> HId_t -> HId_t -> HId_t -> IO HErr_t)

{-# LINE 673 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns a copy of the datatype creation property list, or negative on
-- failure.  The property list ID should be released by calling 'h5p_close'.
--
-- > hid_t H5Tget_create_plist(hid_t type_id);
foreign import ccall "H5Tget_create_plist" h5t_get_create_plist
  :: HId_t -> IO HId_t
foreign import ccall "&H5Tget_create_plist" p_H5Tget_create_plist
  :: FunPtr (HId_t -> IO HId_t)

{-# LINE 679 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Determines if a datatype is committed or not.
--
-- > htri_t H5Tcommitted(hid_t type_id);
foreign import ccall "H5Tcommitted" h5t_committed
  :: HId_t -> IO HTri_t
foreign import ccall "&H5Tcommitted" p_H5Tcommitted
  :: FunPtr (HId_t -> IO HTri_t)

{-# LINE 684 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Given a datatype ID, converts the object description into
-- binary in a buffer.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tencode(hid_t obj_id, void *buf, size_t *nalloc);
foreign import ccall "H5Tencode" h5t_encode
  :: HId_t -> OutArray a -> InOut CSize -> IO HErr_t
foreign import ccall "&H5Tencode" p_H5Tencode
  :: FunPtr (HId_t -> OutArray a -> InOut CSize -> IO HErr_t)

{-# LINE 692 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Decode a binary object description and return a new object handle,
-- or negative on failure.
--
-- > hid_t H5Tdecode(const void *buf);
foreign import ccall "H5Tdecode" h5t_decode
  :: InArray a -> IO HId_t
foreign import ccall "&H5Tdecode" p_H5Tdecode
  :: FunPtr (InArray a -> IO HId_t)

{-# LINE 698 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- > herr_t H5Tflush(hid_t type_id);
foreign import ccall "H5Tflush" h5t_flush
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Tflush" p_H5Tflush
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 701 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- > herr_t H5Trefresh(hid_t type_id);
foreign import ccall "H5Trefresh" h5t_refresh
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Trefresh" p_H5Trefresh
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 704 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Operations defined on compound datatypes

-- |Adds another member to the compound datatype 'parent_id'.  The
-- new member has a 'name' which must be unique within the
-- compound datatype. The 'offset' argument defines the start of
-- the member in an instance of the compound datatype, and
-- 'member_id' is the type of the new member.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tinsert(hid_t parent_id, const char *name, size_t offset,
-- >        hid_t member_id);
foreign import ccall "H5Tinsert" h5t_insert
  :: HId_t -> CString -> CSize -> HId_t -> IO HErr_t
foreign import ccall "&H5Tinsert" p_H5Tinsert
  :: FunPtr (HId_t -> CString -> CSize -> HId_t -> IO HErr_t)

{-# LINE 718 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Recursively removes padding from within a compound datatype
-- to make it more efficient (space-wise) to store that data.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tpack(hid_t type_id);
foreign import ccall "H5Tpack" h5t_pack
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Tpack" p_H5Tpack
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 726 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Operations defined on enumeration datatypes

-- |Create a new enumeration data type based on the specified
-- 'type', which must be an integer type.
--
-- Returns the ID of a new enumeration data type on success, negative
-- on failure.
--
-- > hid_t H5Tenum_create(hid_t base_id);
foreign import ccall "H5Tenum_create" h5t_enum_create
  :: HId_t -> IO HId_t
foreign import ccall "&H5Tenum_create" p_H5Tenum_create
  :: FunPtr (HId_t -> IO HId_t)

{-# LINE 737 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Insert a new enumeration data type member into an enumeration
-- type.  'type' is the enumeration type, 'name' is the name of the
-- new member, and 'value' points to the value of the new member.
-- The 'name' and 'value' must both be unique within the 'type'. 'value'
-- points to data which is of the data type defined when the
-- enumeration type was created.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tenum_insert(hid_t type, const char *name, const void *value);
foreign import ccall "H5Tenum_insert" h5t_enum_insert
  :: HId_t -> CString -> In a -> IO HErr_t
foreign import ccall "&H5Tenum_insert" p_H5Tenum_insert
  :: FunPtr (HId_t -> CString -> In a -> IO HErr_t)

{-# LINE 749 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Finds the symbol name that corresponds to the specified 'value'
-- of an enumeration data type 'type'. At most 'size' characters of
-- the symbol name are copied into the 'name' buffer. If the
-- entire symbol anem and null terminator do not fit in the 'name'
-- buffer then as many characters as possible are copied (not
-- null terminated) and the function fails.
--
-- Returns non-negative on success, negative on failure.  On failure,
-- the first character of 'name' is set to null if 'size' allows it.
--
-- WARNING: the above 2 paragraphs contradict each other about what happens
-- on failure.  This is because the documentation in the source does.  If
-- I read the source correctly, this is because there are some failures which
-- have one behavior and some which have the other.  Therefore, I would
-- probably not rely on either behavior.
--
-- > herr_t H5Tenum_nameof(hid_t type, const void *value, char *name/*out*/,
-- >        size_t size);
foreign import ccall "H5Tenum_nameof" h5t_enum_nameof
  :: HId_t -> In a -> OutArray CChar -> CSize -> IO HErr_t
foreign import ccall "&H5Tenum_nameof" p_H5Tenum_nameof
  :: FunPtr (HId_t -> In a -> OutArray CChar -> CSize -> IO HErr_t)

{-# LINE 769 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Finds the value that corresponds to the specified 'name' of an
-- enumeration 'type'. The 'value' argument should be at least as
-- large as the value of @'h5t_get_size' type@ in order to hold the
-- result.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tenum_valueof(hid_t type, const char *name,
-- >        void *value/*out*/);
foreign import ccall "H5Tenum_valueof" h5t_enum_valueof
  :: HId_t -> CString -> Out a -> IO HErr_t
foreign import ccall "&H5Tenum_valueof" p_H5Tenum_valueof
  :: FunPtr (HId_t -> CString -> Out a -> IO HErr_t)

{-# LINE 780 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Operations defined on variable-length datatypes

-- |Create a new variable-length datatype based on the specified 'base_type'.
--
-- Returns the ID of a new VL datatype on success, negative on failure.
--
-- > hid_t H5Tvlen_create(hid_t base_id);
foreign import ccall "H5Tvlen_create" h5t_vlen_create
  :: HId_t -> IO HId_t
foreign import ccall "&H5Tvlen_create" p_H5Tvlen_create
  :: FunPtr (HId_t -> IO HId_t)

{-# LINE 789 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Operations defined on array datatypes

-- |Create a new array datatype based on the specified 'base_type'.
-- The type is an array with 'ndims' dimensionality and the size of the
-- array is 'dims'. The total member size should be relatively small.
-- Array datatypes are currently limited to 'h5s_max_rank' number of
-- dimensions and must have the number of dimensions set greater than
-- 0. (i.e. 0 > 'ndims' <= 'h5s_MAX_RANK')  All dimensions sizes must be
-- greater than 0 also.
--
-- Returns the ID of a new array datatype on success, negative on failure.
--
-- > hid_t H5Tarray_create2(hid_t base_id, unsigned ndims,
-- >        const hsize_t dim[/* ndims */]);
foreign import ccall "H5Tarray_create2" h5t_array_create2
  :: HId_t -> CUInt -> InArray HSize_t -> IO HId_t
foreign import ccall "&H5Tarray_create2" p_H5Tarray_create2
  :: FunPtr (HId_t -> CUInt -> InArray HSize_t -> IO HId_t)

{-# LINE 805 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the number of dimensions of an array datatype, or negative on
-- failure.
--
-- > int H5Tget_array_ndims(hid_t type_id);
foreign import ccall "H5Tget_array_ndims" h5t_get_array_ndims
  :: HId_t -> IO CInt
foreign import ccall "&H5Tget_array_ndims" p_H5Tget_array_ndims
  :: FunPtr (HId_t -> IO CInt)

{-# LINE 811 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Query the sizes of dimensions for an array datatype.
--
-- Returns the number of dimensions of the array type on success or
-- negative on failure.
--
-- > int H5Tget_array_dims2(hid_t type_id, hsize_t dims[]);
foreign import ccall "H5Tget_array_dims2" h5t_get_array_dims2
  :: HId_t -> OutArray HSize_t -> IO CInt
foreign import ccall "&H5Tget_array_dims2" p_H5Tget_array_dims2
  :: FunPtr (HId_t -> OutArray HSize_t -> IO CInt)

{-# LINE 819 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Operations defined on opaque datatypes

-- |Tag an opaque datatype with a unique ASCII identifier.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_tag(hid_t type, const char *tag);
foreign import ccall "H5Tset_tag" h5t_set_tag
  :: HId_t -> CString -> IO HErr_t
foreign import ccall "&H5Tset_tag" p_H5Tset_tag
  :: FunPtr (HId_t -> CString -> IO HErr_t)

{-# LINE 828 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Get the tag associated with an opaque datatype.
--
-- Returns a pointer to a 'malloc'ed string.  The caller should 'free' the
-- string.
--
-- > char *H5Tget_tag(hid_t type);
foreign import ccall "H5Tget_tag" h5t_get_tag
  :: HId_t -> IO CString
foreign import ccall "&H5Tget_tag" p_H5Tget_tag
  :: FunPtr (HId_t -> IO CString)

{-# LINE 836 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Querying property values

-- |Returns the type from which 'type' is derived. In the case of
-- an enumeration type the return value is an integer type.
--
-- Returns the type ID for the base datatype on success, or negative on
-- failure.
--
-- > hid_t H5Tget_super(hid_t type);
foreign import ccall "H5Tget_super" h5t_get_super
  :: HId_t -> IO HId_t
foreign import ccall "&H5Tget_super" p_H5Tget_super
  :: FunPtr (HId_t -> IO HId_t)

{-# LINE 847 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the datatype class identifier for datatype 'type_id'.
--
-- Returns one of the non-negative datatype class constants on success
-- or 'h5t_NO_CLASS' (which is negative) on failure.
--
-- > H5T_class_t H5Tget_class(hid_t type_id);
foreign import ccall "H5Tget_class" h5t_get_class
  :: HId_t -> IO H5T_class_t
foreign import ccall "&H5Tget_class" p_H5Tget_class
  :: FunPtr (HId_t -> IO H5T_class_t)

{-# LINE 855 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Check whether a datatype contains (or is) a certain type of
-- datatype.
--
-- > htri_t H5Tdetect_class(hid_t type_id, H5T_class_t cls);
foreign import ccall "H5Tdetect_class" h5t_detect_class
  :: HId_t -> H5T_class_t -> IO HTri_t
foreign import ccall "&H5Tdetect_class" p_H5Tdetect_class
  :: FunPtr (HId_t -> H5T_class_t -> IO HTri_t)

{-# LINE 861 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Determines the total size of a datatype in bytes.
--
-- Returns the size of an instance of the datatype (in bytes) on
-- success or 0 on failure (valid datatypes are never zero size).
--
-- > size_t H5Tget_size(hid_t type_id);
foreign import ccall "H5Tget_size" h5t_get_size
  :: HId_t -> IO CSize
foreign import ccall "&H5Tget_size" p_H5Tget_size
  :: FunPtr (HId_t -> IO CSize)

{-# LINE 869 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the byte order of a datatype on success, or 'h5t_ORDER_ERROR'
-- (which is negative) on failure.
--
-- If the type is compound and its members have mixed orders, this function
-- returns 'h5t_ORDER_MIXED'.
--
-- > H5T_order_t H5Tget_order(hid_t type_id);
foreign import ccall "H5Tget_order" h5t_get_order
  :: HId_t -> IO H5T_order_t
foreign import ccall "&H5Tget_order" p_H5Tget_order
  :: FunPtr (HId_t -> IO H5T_order_t)

{-# LINE 878 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Gets the precision of a datatype.  The precision is
-- the number of significant bits which, unless padding is
-- present, is 8 times larger than the value returned by
-- 'h5t_get_size'.
--
-- Returns 0 on failure (all atomic types have at least one
-- significant bit)
--
-- > size_t H5Tget_precision(hid_t type_id);
foreign import ccall "H5Tget_precision" h5t_get_precision
  :: HId_t -> IO CSize
foreign import ccall "&H5Tget_precision" p_H5Tget_precision
  :: FunPtr (HId_t -> IO CSize)

{-# LINE 889 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Retrieves the bit offset of the first significant bit.  The
-- signficant bits of an atomic datum can be offset from the
-- beginning of the memory for that datum by an amount of
-- padding. The 'offset' property specifies the number of bits
-- of padding that appear to the \"right of\" the value.  That is,
-- if we have a 32-bit datum with 16-bits of precision having
-- the value 0x1122 then it will be layed out in memory as (from
-- small byte address toward larger byte addresses):
--
-- >     Big      Big       Little   Little
-- >     Endian   Endian    Endian   Endian
-- >     offset=0 offset=16 offset=0 offset=16
-- >
-- > 0:  [ pad]   [0x11]    [0x22]   [ pad]
-- > 1:  [ pad]   [0x22]    [0x11]   [ pad]
-- > 2:  [0x11]   [ pad]    [ pad]   [0x22]
-- > 3:  [0x22]   [ pad]    [ pad]   [0x11]
--
-- Returns the offset on success or negative on failure.
--
-- > int H5Tget_offset(hid_t type_id);
foreign import ccall "H5Tget_offset" h5t_get_offset
  :: HId_t -> IO CInt
foreign import ccall "&H5Tget_offset" p_H5Tget_offset
  :: FunPtr (HId_t -> IO CInt)

{-# LINE 912 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Gets the least significant pad type and the most significant
-- pad type and returns their values through the LSB and MSB
-- arguments, either of which may be the null pointer.
--
-- Returns non-negative on success or negative on failure.
--
-- > herr_t H5Tget_pad(hid_t type_id, H5T_pad_t *lsb/*out*/,
-- >        H5T_pad_t *msb/*out*/);
foreign import ccall "H5Tget_pad" h5t_get_pad
  :: HId_t -> Out H5T_pad_t -> Out H5T_pad_t -> IO HErr_t
foreign import ccall "&H5Tget_pad" p_H5Tget_pad
  :: FunPtr (HId_t -> Out H5T_pad_t -> Out H5T_pad_t -> IO HErr_t)

{-# LINE 922 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the sign type for an integer type or 'h5t_SGN_ERROR' (a negative
-- value) on failure.
--
-- > H5T_sign_t H5Tget_sign(hid_t type_id);
foreign import ccall "H5Tget_sign" h5t_get_sign
  :: HId_t -> IO H5T_sign_t
foreign import ccall "&H5Tget_sign" p_H5Tget_sign
  :: FunPtr (HId_t -> IO H5T_sign_t)

{-# LINE 928 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns information about the locations of the various bit
-- fields of a floating point datatype.  The field positions
-- are bit positions in the significant region of the datatype.
-- Bits are numbered with the least significant bit number zero.
--
-- Any (or even all) of the arguments can be null pointers.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tget_fields(hid_t type_id, size_t *spos/*out*/,
-- >        size_t *epos/*out*/, size_t *esize/*out*/,
-- >        size_t *mpos/*out*/, size_t *msize/*out*/);
foreign import ccall "H5Tget_fields" h5t_get_fields
  :: HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CSize -> Out CSize -> IO HErr_t
foreign import ccall "&H5Tget_fields" p_H5Tget_fields
  :: FunPtr (HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CSize -> Out CSize -> IO HErr_t)

{-# LINE 942 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the exponent bias of a floating-point type, or 0 on failure.
--
-- > size_t H5Tget_ebias(hid_t type_id);
foreign import ccall "H5Tget_ebias" h5t_get_ebias
  :: HId_t -> IO CSize
foreign import ccall "&H5Tget_ebias" p_H5Tget_ebias
  :: FunPtr (HId_t -> IO CSize)

{-# LINE 947 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the mantisssa normalization of a floating-point data type,
-- or 'h5t_NORM_ERROR' (a negative value) on failure.
--
-- > H5T_norm_t H5Tget_norm(hid_t type_id);
foreign import ccall "H5Tget_norm" h5t_get_norm
  :: HId_t -> IO H5T_norm_t
foreign import ccall "&H5Tget_norm" p_H5Tget_norm
  :: FunPtr (HId_t -> IO H5T_norm_t)

{-# LINE 953 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |If any internal bits of a floating point type are unused
-- (that is, those significant bits which are not part of the
-- sign, exponent, or mantissa) then they will be filled
-- according to the value of this property.
--
-- > H5T_pad_t H5Tget_inpad(hid_t type_id);
foreign import ccall "H5Tget_inpad" h5t_get_inpad
  :: HId_t -> IO H5T_pad_t
foreign import ccall "&H5Tget_inpad" p_H5Tget_inpad
  :: FunPtr (HId_t -> IO H5T_pad_t)

{-# LINE 961 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The method used to store character strings differs with the
-- programming language: C usually null terminates strings while
-- Fortran left-justifies and space-pads strings.  This property
-- defines the storage mechanism for the string.
--
-- Returns the character set of a string type on success, or
-- 'h5t_STR_ERROR' (a negative value) on failure.
--
-- > H5T_str_t H5Tget_strpad(hid_t type_id);
foreign import ccall "H5Tget_strpad" h5t_get_strpad
  :: HId_t -> IO H5T_str_t
foreign import ccall "&H5Tget_strpad" p_H5Tget_strpad
  :: FunPtr (HId_t -> IO H5T_str_t)

{-# LINE 972 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Determines how many members 'type_id' has.  The type must be
-- either a compound datatype or an enumeration datatype.
--
-- Returns the number of members defined in the datatype on success, or
-- negative on failure.
--
-- > int H5Tget_nmembers(hid_t type_id);
foreign import ccall "H5Tget_nmembers" h5t_get_nmembers
  :: HId_t -> IO CInt
foreign import ccall "&H5Tget_nmembers" p_H5Tget_nmembers
  :: FunPtr (HId_t -> IO CInt)

{-# LINE 981 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the name of a member of a compound or enumeration
-- datatype.  Members are stored in no particular order with
-- numbers 0 through N-1 where N is the value returned by
-- 'h5t_get_nmembers'.
--
-- Returns a pointer to a string allocated with 'malloc', or NULL on
-- failure.  The caller is responsible for 'free'ing the string.
--
-- > char *H5Tget_member_name(hid_t type_id, unsigned membno);
foreign import ccall "H5Tget_member_name" h5t_get_member_name
  :: HId_t -> CUInt -> IO CString
foreign import ccall "&H5Tget_member_name" p_H5Tget_member_name
  :: FunPtr (HId_t -> CUInt -> IO CString)

{-# LINE 992 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the index of a member in a compound or enumeration
-- datatype by given name.  Members are stored in no particular
-- order with numbers 0 through N-1 where N is the value
-- returned by 'h5t_get_nmembers'.
--
-- Returns the index of the member on success, or negative on
-- failure.
--
-- > int H5Tget_member_index(hid_t type_id, const char *name);
foreign import ccall "H5Tget_member_index" h5t_get_member_index
  :: HId_t -> CString -> IO CInt
foreign import ccall "&H5Tget_member_index" p_H5Tget_member_index
  :: FunPtr (HId_t -> CString -> IO CInt)

{-# LINE 1003 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the byte offset of the beginning of a member with
-- respect to the beginning of the compound datatype datum.
--
-- Returns the byte offset on success, or zero on failure.
-- Zero is a valid offset, but this function will fail only
-- if a call to 'h5t_get_member_dims' fails with the same
-- arguments.
--
-- > size_t H5Tget_member_offset(hid_t type_id, unsigned membno);
foreign import ccall "H5Tget_member_offset" h5t_get_member_offset
  :: HId_t -> CUInt -> IO CSize
foreign import ccall "&H5Tget_member_offset" p_H5Tget_member_offset
  :: FunPtr (HId_t -> CUInt -> IO CSize)

{-# LINE 1014 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns the datatype class of a member of a compound datatype.
--
-- Returns non-negative on success, negative on failure.
--
-- > H5T_class_t H5Tget_member_class(hid_t type_id, unsigned membno);
foreign import ccall "H5Tget_member_class" h5t_get_member_class
  :: HId_t -> CUInt -> IO H5T_class_t
foreign import ccall "&H5Tget_member_class" p_H5Tget_member_class
  :: FunPtr (HId_t -> CUInt -> IO H5T_class_t)

{-# LINE 1021 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Returns a copy of the datatype of the specified member, or negative
-- on failure.  The caller should invoke 'h5t_close' to release resources
-- associated with the type.
--
-- > hid_t H5Tget_member_type(hid_t type_id, unsigned membno);
foreign import ccall "H5Tget_member_type" h5t_get_member_type
  :: HId_t -> CUInt -> IO HId_t
foreign import ccall "&H5Tget_member_type" p_H5Tget_member_type
  :: FunPtr (HId_t -> CUInt -> IO HId_t)

{-# LINE 1028 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Return the value for an enumeration data type member.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tget_member_value(hid_t type_id, unsigned membno, void *value/*out*/);
foreign import ccall "H5Tget_member_value" h5t_get_member_value
  :: HId_t -> CUInt -> Out a -> IO HErr_t
foreign import ccall "&H5Tget_member_value" p_H5Tget_member_value
  :: FunPtr (HId_t -> CUInt -> Out a -> IO HErr_t)

{-# LINE 1035 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |HDF5 is able to distinguish between character sets of
-- different nationalities and to convert between them to the
-- extent possible.
--
-- Returns the character set of a string type on success, or
-- 'h5t_CSET_ERROR' (a negative value) on failure.
--
-- > H5T_cset_t H5Tget_cset(hid_t type_id);
foreign import ccall "H5Tget_cset" h5t_get_cset
  :: HId_t -> IO H5T_cset_t
foreign import ccall "&H5Tget_cset" p_H5Tget_cset
  :: FunPtr (HId_t -> IO H5T_cset_t)

{-# LINE 1045 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Check whether a datatype is a variable-length string
--
-- > htri_t H5Tis_variable_str(hid_t type_id);
foreign import ccall "H5Tis_variable_str" h5t_is_variable_str
  :: HId_t -> IO HTri_t
foreign import ccall "&H5Tis_variable_str" p_H5Tis_variable_str
  :: FunPtr (HId_t -> IO HTri_t)

{-# LINE 1050 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |High-level API to return the native type of a datatype.
-- The native type is chosen by matching the size and class of
-- querried datatype from the following native premitive
-- datatypes:
--
--  'h5t_NATIVE_CHAR'         'h5t_NATIVE_UCHAR'
--  'h5t_NATIVE_SHORT'        'h5t_NATIVE_USHORT'
--  'h5t_NATIVE_INT'          'h5t_NATIVE_UINT'
--  'h5t_NATIVE_LONG'         'h5t_NATIVE_ULONG'
--  'h5t_NATIVE_LLONG'        'h5t_NATIVE_ULLONG'
--
--  'H5T_NATIVE_FLOAT'
--  'H5T_NATIVE_DOUBLE'
--  'H5T_NATIVE_LDOUBLE'
--
-- Compound, array, enum, and VL types all choose among these
-- types for theire members.  Time, Bifield, Opaque, Reference
-- types are only copy out.
--
-- Returns the native data type if successful, negative otherwise.
--
-- > hid_t H5Tget_native_type(hid_t type_id, H5T_direction_t direction);
foreign import ccall "H5Tget_native_type" h5t_get_native_type
  :: HId_t -> H5T_direction_t -> IO HId_t
foreign import ccall "&H5Tget_native_type" p_H5Tget_native_type
  :: FunPtr (HId_t -> H5T_direction_t -> IO HId_t)

{-# LINE 1074 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Setting property values

-- |Sets the total size in bytes for a datatype (this operation
-- is not permitted on reference datatypes).  If the size is
-- decreased so that the significant bits of the datatype
-- extend beyond the edge of the new size, then the 'offset'
-- property is decreased toward zero.  If the 'offset' becomes
-- zero and the significant bits of the datatype still hang
-- over the edge of the new size, then the number of significant
-- bits is decreased.
--
-- Adjusting the size of an 'h5t_STRING' automatically sets the
-- precision to @8*size@.
--
-- All datatypes have a positive size.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_size(hid_t type_id, size_t size);
foreign import ccall "H5Tset_size" h5t_set_size
  :: HId_t -> CSize -> IO HErr_t
foreign import ccall "&H5Tset_size" p_H5Tset_size
  :: FunPtr (HId_t -> CSize -> IO HErr_t)

{-# LINE 1095 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the byte order for a datatype.
--
-- Notes:  There are some restrictions on this operation:
--
--  1. For enum type, members shouldn't be defined yet.
--
--  2. 'h5t_ORDER_NONE' only works for reference and fixed-length
--     string.
--
--  3. For opaque type, the order will be ignored.
--
--  4. For compound type, all restrictions above apply to the
--     members.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_order(hid_t type_id, H5T_order_t order);
foreign import ccall "H5Tset_order" h5t_set_order
  :: HId_t -> H5T_order_t -> IO HErr_t
foreign import ccall "&H5Tset_order" p_H5Tset_order
  :: FunPtr (HId_t -> H5T_order_t -> IO HErr_t)

{-# LINE 1114 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the precision of a datatype.  The precision is
-- the number of significant bits which, unless padding is
-- present, is 8 times larger than the value returned by
-- 'h5t_get_size'.
--
-- If the precision is increased then the offset is decreased
-- and then the size is increased to insure that significant
-- bits do not \"hang over\" the edge of the datatype.
--
-- The precision property of strings is read-only.
--
-- When decreasing the precision of a floating point type, set
-- the locations and sizes of the sign, mantissa, and exponent
-- fields first.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_precision(hid_t type_id, size_t prec);
foreign import ccall "H5Tset_precision" h5t_set_precision
  :: HId_t -> CSize -> IO HErr_t
foreign import ccall "&H5Tset_precision" p_H5Tset_precision
  :: FunPtr (HId_t -> CSize -> IO HErr_t)

{-# LINE 1134 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the bit offset of the first significant bit.  The
-- signficant bits of an atomic datum can be offset from the
-- beginning of the memory for that datum by an amount of
-- padding. The `offset' property specifies the number of bits
-- of padding that appear to the "right of" the value.  That is,
-- if we have a 32-bit datum with 16-bits of precision having
-- the value 0x1122 then it will be layed out in memory as (from
-- small byte address toward larger byte addresses):
--
-- >     Big      Big       Little   Little
-- >     Endian   Endian    Endian   Endian
-- >     offset=0 offset=16 offset=0 offset=16
-- >
-- > 0:  [ pad]   [0x11]    [0x22]   [ pad]
-- > 1:  [ pad]   [0x22]    [0x11]   [ pad]
-- > 2:  [0x11]   [ pad]    [ pad]   [0x22]
-- > 3:  [0x22]   [ pad]    [ pad]   [0x11]
--
-- If the offset is incremented then the total size is
-- incremented also if necessary to prevent significant bits of
-- the value from hanging over the edge of the data type.
--
-- The offset of an 'h5t_STRING' cannot be set to anything but
-- zero.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_offset(hid_t type_id, size_t offset);
foreign import ccall "H5Tset_offset" h5t_set_offset
  :: HId_t -> CSize -> IO HErr_t
foreign import ccall "&H5Tset_offset" p_H5Tset_offset
  :: FunPtr (HId_t -> CSize -> IO HErr_t)

{-# LINE 1164 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the LSB and MSB pad types.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_pad(hid_t type_id, H5T_pad_t lsb, H5T_pad_t msb);
foreign import ccall "H5Tset_pad" h5t_set_pad
  :: HId_t -> H5T_pad_t -> H5T_pad_t -> IO HErr_t
foreign import ccall "&H5Tset_pad" p_H5Tset_pad
  :: FunPtr (HId_t -> H5T_pad_t -> H5T_pad_t -> IO HErr_t)

{-# LINE 1171 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the sign property for an integer.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_sign(hid_t type_id, H5T_sign_t sign);
foreign import ccall "H5Tset_sign" h5t_set_sign
  :: HId_t -> H5T_sign_t -> IO HErr_t
foreign import ccall "&H5Tset_sign" p_H5Tset_sign
  :: FunPtr (HId_t -> H5T_sign_t -> IO HErr_t)

{-# LINE 1178 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the locations and sizes of the various floating point
-- bit fields.  The field positions are bit positions in the
-- significant region of the datatype.  Bits are numbered with
-- the least significant bit number zero.
--
-- Fields are not allowed to extend beyond the number of bits of
-- precision, nor are they allowed to overlap with one another.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_fields(hid_t type_id, size_t spos, size_t epos,
-- >        size_t esize, size_t mpos, size_t msize);
foreign import ccall "H5Tset_fields" h5t_set_fields
  :: HId_t -> CSize -> CSize -> CSize -> CSize -> CSize -> IO HErr_t
foreign import ccall "&H5Tset_fields" p_H5Tset_fields
  :: FunPtr (HId_t -> CSize -> CSize -> CSize -> CSize -> CSize -> IO HErr_t)

{-# LINE 1192 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the exponent bias of a floating-point type.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_ebias(hid_t type_id, size_t ebias);
foreign import ccall "H5Tset_ebias" h5t_set_ebias
  :: HId_t -> CSize -> IO HErr_t
foreign import ccall "&H5Tset_ebias" p_H5Tset_ebias
  :: FunPtr (HId_t -> CSize -> IO HErr_t)

{-# LINE 1199 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Sets the mantissa normalization method for a floating point
-- datatype.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_norm(hid_t type_id, H5T_norm_t norm);
foreign import ccall "H5Tset_norm" h5t_set_norm
  :: HId_t -> H5T_norm_t -> IO HErr_t
foreign import ccall "&H5Tset_norm" p_H5Tset_norm
  :: FunPtr (HId_t -> H5T_norm_t -> IO HErr_t)

{-# LINE 1207 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |If any internal bits of a floating point type are unused
-- (that is, those significant bits which are not part of the
-- sign, exponent, or mantissa) then they will be filled
-- according to the value of this property.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_inpad(hid_t type_id, H5T_pad_t pad);
foreign import ccall "H5Tset_inpad" h5t_set_inpad
  :: HId_t -> H5T_pad_t -> IO HErr_t
foreign import ccall "&H5Tset_inpad" p_H5Tset_inpad
  :: FunPtr (HId_t -> H5T_pad_t -> IO HErr_t)

{-# LINE 1217 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |HDF5 is able to distinguish between character sets of
-- different nationalities and to convert between them to the
-- extent possible.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_cset(hid_t type_id, H5T_cset_t cset);
foreign import ccall "H5Tset_cset" h5t_set_cset
  :: HId_t -> H5T_cset_t -> IO HErr_t
foreign import ccall "&H5Tset_cset" p_H5Tset_cset
  :: FunPtr (HId_t -> H5T_cset_t -> IO HErr_t)

{-# LINE 1226 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |The method used to store character strings differs with the
-- programming language: C usually null terminates strings while
-- Fortran left-justifies and space-pads strings.  This property
-- defines the storage mechanism for the string.
--
-- When converting from a long string to a short string if the
-- short string is 'h5t_STR_NULLPAD' or 'h5t_STR_SPACEPAD' then the
-- string is simply truncated; otherwise if the short string is
-- 'h5t_STR_NULLTERM' it will be truncated and a null terminator
-- is appended.
--
-- When converting from a short string to a long string, the
-- long string is padded on the end by appending nulls or
-- spaces.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tset_strpad(hid_t type_id, H5T_str_t strpad);
foreign import ccall "H5Tset_strpad" h5t_set_strpad
  :: HId_t -> H5T_str_t -> IO HErr_t
foreign import ccall "&H5Tset_strpad" p_H5Tset_strpad
  :: FunPtr (HId_t -> H5T_str_t -> IO HErr_t)

{-# LINE 1246 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Type conversion database

-- |Register a hard or soft conversion function for a data type
-- conversion path.  The path is specified by the source and
-- destination data types 'src_id' and 'dst_id' (for soft functions
-- only the class of these types is important).  If 'func' is a
-- hard function then it replaces any previous path; if it's a
-- soft function then it replaces all existing paths to which it
-- applies and is used for any new path to which it applies as
-- long as that path doesn't have a hard function.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tregister(H5T_pers_t pers, const char *name, hid_t src_id,
-- >        hid_t dst_id, H5T_conv_t func);
foreign import ccall "H5Tregister" h5t_register
  :: H5T_pers_t -> CString -> HId_t -> HId_t -> H5T_conv_t a b c -> IO HErr_t
foreign import ccall "&H5Tregister" p_H5Tregister
  :: FunPtr (H5T_pers_t -> CString -> HId_t -> HId_t -> H5T_conv_t a b c -> IO HErr_t)

{-# LINE 1263 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Removes conversion paths that match the specified criteria.
-- All arguments are optional. Missing arguments are wild cards.
-- The special no-op path cannot be removed.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Tunregister(H5T_pers_t pers, const char *name, hid_t src_id,
-- >        hid_t dst_id, H5T_conv_t func);
foreign import ccall "H5Tunregister" h5t_unregister
  :: H5T_pers_t -> CString -> HId_t -> HId_t -> H5T_conv_t a b c -> IO HErr_t
foreign import ccall "&H5Tunregister" p_H5Tunregister
  :: FunPtr (H5T_pers_t -> CString -> HId_t -> HId_t -> H5T_conv_t a b c -> IO HErr_t)

{-# LINE 1273 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- TODO: check docs on this funtion and figure out what its type should be
-- |Finds a conversion function that can handle a conversion from
-- type 'src_id' to type 'dst_id'.  The 'pcdata' argument is a pointer
-- to a pointer to type conversion data which was created and
-- initialized by the type conversion function of this path
-- when the conversion function was installed on the path.
--
-- > H5T_convT H5Tfind(hid_t src_id, hid_t dst_id, H5T_cdata_t **pcdata);
foreign import ccall "H5Tfind" h5t_find
  :: HId_t -> HId_t -> Out (Ptr (H5T_cdata_t c)) -> IO (H5T_conv_t a b c)
foreign import ccall "&H5Tfind" p_H5Tfind
  :: FunPtr (HId_t -> HId_t -> Out (Ptr (H5T_cdata_t c)) -> IO (H5T_conv_t a b c))

{-# LINE 1283 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Finds out whether the library's conversion function from
-- type 'src_id' to type 'dst_id' is a compiler (hard) conversion.
-- A hard conversion uses compiler's casting; a soft conversion
-- uses the library's own conversion function.
--
-- > htri_t H5Tcompiler_conv(hid_t src_id, hid_t dst_id);
foreign import ccall "H5Tcompiler_conv" h5t_compiler_conv
  :: HId_t -> HId_t -> IO HTri_t
foreign import ccall "&H5Tcompiler_conv" p_H5Tcompiler_conv
  :: FunPtr (HId_t -> HId_t -> IO HTri_t)

{-# LINE 1291 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Convert 'nelmts' elements from type 'src_id' to type 'dst_id'.  The
-- source elements are packed in 'buf' and on return the
-- destination will be packed in 'buf'.  That is, the conversion
-- is performed in place.  The optional background buffer is an
-- array of 'nelmts' values of destination type which are merged
-- with the converted values to fill in cracks (for instance,
-- 'background' might be an array of structs with the 'a' and 'b'
-- fields already initialized and the conversion of BUF supplies
-- the 'c' and 'd' field values).  The 'plist_id' a dataset transfer
-- property list which is passed to the conversion functions.  (It's
-- currently only used to pass along the VL datatype custom allocation
-- information -QAK 7/1/99)
--
-- > herr_t H5Tconvert(hid_t src_id, hid_t dst_id, size_t nelmts,
-- >        void *buf, void *background, hid_t plist_id);
foreign import ccall "H5Tconvert" h5t_convert
  :: HId_t -> HId_t -> CSize -> InOutArray a -> InArray b -> HId_t -> IO HErr_t
foreign import ccall "&H5Tconvert" p_H5Tconvert
  :: FunPtr (HId_t -> HId_t -> CSize -> InOutArray a -> InArray b -> HId_t -> IO HErr_t)

{-# LINE 1308 "src/Bindings/HDF5/Raw/H5T.hsc" #-}


{-# LINE 1310 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- * Symbols defined for compatibility with previous versions of the HDF5 API.
--
-- Use of these symbols is deprecated.

-- |Save a transient datatype to a file and turn the type handle
-- into a named, immutable type.
--
-- Note:  Deprecated in favor of 'h5t_commit2'
--
-- > herr_t H5Tcommit1(hid_t loc_id, const char *name, hid_t type_id);
foreign import ccall "H5Tcommit1" h5t_commit1
  :: HId_t -> CString -> HId_t -> IO HErr_t
foreign import ccall "&H5Tcommit1" p_H5Tcommit1
  :: FunPtr (HId_t -> CString -> HId_t -> IO HErr_t)

{-# LINE 1322 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Opens a named datatype.
--
-- Deprecated in favor of 'h5t_open2'.
--
-- > hid_t H5Topen1(hid_t loc_id, const char *name);
foreign import ccall "H5Topen1" h5t_open1
  :: HId_t -> CString -> IO HId_t
foreign import ccall "&H5Topen1" p_H5Topen1
  :: FunPtr (HId_t -> CString -> IO HId_t)

{-# LINE 1329 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Create a new array datatype based on the specified 'base_type'.
-- The type is an array with 'ndims' dimensionality and the size of the
-- array is 'dims'. The total member size should be relatively small.
-- Array datatypes are currently limited to 'h5s_MAX_RANK' number of
-- dimensions and must have the number of dimensions set greater than
-- 0. (i.e. @0 > ndims <= 'h5s_MAX_RANK'@)  All dimensions sizes must
-- be greater than 0 also.
--
-- Returns the ID of a new array datatype on success, negative on
-- failure.
--
-- > hid_t H5Tarray_create1(hid_t base_id, int ndims,
-- >        const hsize_t dim[/* ndims */],
-- >        const int perm[/* ndims */]);
foreign import ccall "H5Tarray_create1" h5t_array_create1
  :: HId_t -> CInt -> InArray HSize_t -> InArray CInt -> IO HId_t
foreign import ccall "&H5Tarray_create1" p_H5Tarray_create1
  :: FunPtr (HId_t -> CInt -> InArray HSize_t -> InArray CInt -> IO HId_t)

{-# LINE 1345 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

-- |Query the sizes of dimensions for an array datatype.
--
-- Returns the number of dimensions of the array type on success,
-- negative on failure.
--
-- > int H5Tget_array_dims1(hid_t type_id, hsize_t dims[], int perm[]);
foreign import ccall "H5Tget_array_dims1" h5t_get_array_dims1
  :: HId_t -> OutArray HSize_t -> OutArray CInt -> IO CInt
foreign import ccall "&H5Tget_array_dims1" p_H5Tget_array_dims1
  :: FunPtr (HId_t -> OutArray HSize_t -> OutArray CInt -> IO CInt)

{-# LINE 1353 "src/Bindings/HDF5/Raw/H5T.hsc" #-}

--

{-# LINE 1356 "src/Bindings/HDF5/Raw/H5T.hsc" #-}