{-# LINE 1 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
module Bindings.HDF5.Raw.H5O 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
h5o_COPY_SHALLOW_HIERARCHY_FLAG :: forall a. Num a => a
h5o_COPY_SHALLOW_HIERARCHY_FLAG = a
1
h5o_COPY_SHALLOW_HIERARCHY_FLAG :: (Num a) => a
{-# LINE 23 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_EXPAND_SOFT_LINK_FLAG = 2
h5o_COPY_EXPAND_SOFT_LINK_FLAG :: (Num a) => a
{-# LINE 26 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_EXPAND_EXT_LINK_FLAG = 4
h5o_COPY_EXPAND_EXT_LINK_FLAG :: (Num a) => a
{-# LINE 29 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_EXPAND_REFERENCE_FLAG = 8
h5o_COPY_EXPAND_REFERENCE_FLAG :: (Num a) => a
{-# LINE 32 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_WITHOUT_ATTR_FLAG = 16
h5o_COPY_WITHOUT_ATTR_FLAG :: (Num a) => a
{-# LINE 35 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_PRESERVE_NULL_FLAG = 32
h5o_COPY_PRESERVE_NULL_FLAG :: (Num a) => a
{-# LINE 38 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_MERGE_COMMITTED_DTYPE_FLAG = 64
h5o_COPY_MERGE_COMMITTED_DTYPE_FLAG :: (Num a) => a
{-# LINE 41 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_COPY_ALL = 127
h5o_COPY_ALL :: (Num a) => a
{-# LINE 44 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_NONE_FLAG :: forall a. Num a => a
h5o_SHMESG_NONE_FLAG = a
0
h5o_SHMESG_NONE_FLAG :: (Num a) => a
{-# LINE 52 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_SDSPACE_FLAG = 2
h5o_SHMESG_SDSPACE_FLAG :: (Num a) => a
{-# LINE 55 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_DTYPE_FLAG = 8
h5o_SHMESG_DTYPE_FLAG :: (Num a) => a
{-# LINE 58 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_FILL_FLAG = 32
h5o_SHMESG_FILL_FLAG :: (Num a) => a
{-# LINE 61 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_PLINE_FLAG = 2048
h5o_SHMESG_PLINE_FLAG :: (Num a) => a
{-# LINE 64 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_ATTR_FLAG = 4096
h5o_SHMESG_ATTR_FLAG :: (Num a) => a
{-# LINE 67 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_ALL_FLAG = 6186
h5o_SHMESG_ALL_FLAG :: (Num a) => a
{-# LINE 69 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_HDR_CHUNK0_SIZE :: forall a. Num a => a
h5o_HDR_CHUNK0_SIZE = a
3
h5o_HDR_CHUNK0_SIZE :: (Num a) => a
{-# LINE 74 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_HDR_ATTR_CRT_ORDER_TRACKED = 4
h5o_HDR_ATTR_CRT_ORDER_TRACKED :: (Num a) => a
{-# LINE 77 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_HDR_ATTR_CRT_ORDER_INDEXED = 8
h5o_HDR_ATTR_CRT_ORDER_INDEXED :: (Num a) => a
{-# LINE 80 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_HDR_ATTR_STORE_PHASE_CHANGE = 16
h5o_HDR_ATTR_STORE_PHASE_CHANGE :: (Num a) => a
{-# LINE 83 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_HDR_STORE_TIMES = 32
h5o_HDR_STORE_TIMES :: (Num a) => a
{-# LINE 86 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_HDR_ALL_FLAGS = 63
h5o_HDR_ALL_FLAGS :: (Num a) => a
{-# LINE 88 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_MAX_NINDEXES :: forall a. Num a => a
h5o_SHMESG_MAX_NINDEXES = a
8
h5o_SHMESG_MAX_NINDEXES :: (Num a) => a
{-# LINE 92 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_MAX_LIST_SIZE = 5000
h5o_SHMESG_MAX_LIST_SIZE :: (Num a) => a
{-# LINE 93 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
newtype H5O_type_t = H5O_type_t Int32 deriving (Ptr H5O_type_t -> IO H5O_type_t
Ptr H5O_type_t -> Int -> IO H5O_type_t
Ptr H5O_type_t -> Int -> H5O_type_t -> IO ()
Ptr H5O_type_t -> H5O_type_t -> IO ()
H5O_type_t -> Int
(H5O_type_t -> Int)
-> (H5O_type_t -> Int)
-> (Ptr H5O_type_t -> Int -> IO H5O_type_t)
-> (Ptr H5O_type_t -> Int -> H5O_type_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5O_type_t)
-> (forall b. Ptr b -> Int -> H5O_type_t -> IO ())
-> (Ptr H5O_type_t -> IO H5O_type_t)
-> (Ptr H5O_type_t -> H5O_type_t -> IO ())
-> Storable H5O_type_t
forall b. Ptr b -> Int -> IO H5O_type_t
forall b. Ptr b -> Int -> H5O_type_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 :: H5O_type_t -> Int
sizeOf :: H5O_type_t -> Int
$calignment :: H5O_type_t -> Int
alignment :: H5O_type_t -> Int
$cpeekElemOff :: Ptr H5O_type_t -> Int -> IO H5O_type_t
peekElemOff :: Ptr H5O_type_t -> Int -> IO H5O_type_t
$cpokeElemOff :: Ptr H5O_type_t -> Int -> H5O_type_t -> IO ()
pokeElemOff :: Ptr H5O_type_t -> Int -> H5O_type_t -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5O_type_t
peekByteOff :: forall b. Ptr b -> Int -> IO H5O_type_t
$cpokeByteOff :: forall b. Ptr b -> Int -> H5O_type_t -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5O_type_t -> IO ()
$cpeek :: Ptr H5O_type_t -> IO H5O_type_t
peek :: Ptr H5O_type_t -> IO H5O_type_t
$cpoke :: Ptr H5O_type_t -> H5O_type_t -> IO ()
poke :: Ptr H5O_type_t -> H5O_type_t -> IO ()
Storable, Int -> H5O_type_t -> ShowS
[H5O_type_t] -> ShowS
H5O_type_t -> String
(Int -> H5O_type_t -> ShowS)
-> (H5O_type_t -> String)
-> ([H5O_type_t] -> ShowS)
-> Show H5O_type_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5O_type_t -> ShowS
showsPrec :: Int -> H5O_type_t -> ShowS
$cshow :: H5O_type_t -> String
show :: H5O_type_t -> String
$cshowList :: [H5O_type_t] -> ShowS
showList :: [H5O_type_t] -> ShowS
Show, H5O_type_t -> H5O_type_t -> Bool
(H5O_type_t -> H5O_type_t -> Bool)
-> (H5O_type_t -> H5O_type_t -> Bool) -> Eq H5O_type_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5O_type_t -> H5O_type_t -> Bool
== :: H5O_type_t -> H5O_type_t -> Bool
$c/= :: H5O_type_t -> H5O_type_t -> Bool
/= :: H5O_type_t -> H5O_type_t -> Bool
Eq)
{-# LINE 98 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_TYPE_UNKNOWN :: H5O_type_t
h5o_TYPE_UNKNOWN :: H5O_type_t
h5o_TYPE_UNKNOWN = Int32 -> H5O_type_t
H5O_type_t (-Int32
1)
{-# LINE 101 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_TYPE_GROUP :: H5O_type_t
h5o_TYPE_GROUP :: H5O_type_t
h5o_TYPE_GROUP = Int32 -> H5O_type_t
H5O_type_t (Int32
0)
{-# LINE 104 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_TYPE_DATASET :: H5O_type_t
h5o_TYPE_DATASET :: H5O_type_t
h5o_TYPE_DATASET = Int32 -> H5O_type_t
H5O_type_t (Int32
1)
{-# LINE 107 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_TYPE_NAMED_DATATYPE :: H5O_type_t
h5o_TYPE_NAMED_DATATYPE :: H5O_type_t
h5o_TYPE_NAMED_DATATYPE = Int32 -> H5O_type_t
H5O_type_t (Int32
2)
{-# LINE 110 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_TYPE_NTYPES = 3
h5o_TYPE_NTYPES :: (Num a) => a
{-# LINE 113 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 115 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 116 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 117 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 118 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 119 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 120 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 121 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 122 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 123 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 124 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 125 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
data H5O_hdr_info_t = H5O_hdr_info_t{
h5o_hdr_info_t'version :: CUInt,
h5o_hdr_info_t'nmesgs :: CUInt,
h5o_hdr_info_t'nchunks :: CUInt,
h5o_hdr_info_t'flags :: CUInt,
h5o_hdr_info_t'space'total :: HSize_t,
h5o_hdr_info_t'space'meta :: HSize_t,
h5o_hdr_info_t'space'mesg :: HSize_t,
h5o_hdr_info_t'space'free :: HSize_t,
h5o_hdr_info_t'mesg'present :: Word64,
h5o_hdr_info_t'mesg'shared :: Word64
} deriving (Eq,Show)
p'H5O_hdr_info_t'version :: Ptr H5O_hdr_info_t -> Ptr CUInt
p'H5O_hdr_info_t'version Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
0
p'H5O_hdr_info_t'version :: Ptr (H5O_hdr_info_t) -> Ptr (CUInt)
p'H5O_hdr_info_t'nmesgs :: Ptr H5O_hdr_info_t -> Ptr CUInt
p'H5O_hdr_info_t'nmesgs Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
4
p'H5O_hdr_info_t'nmesgs :: Ptr (H5O_hdr_info_t) -> Ptr (CUInt)
p'H5O_hdr_info_t'nchunks :: Ptr H5O_hdr_info_t -> Ptr CUInt
p'H5O_hdr_info_t'nchunks Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
8
p'H5O_hdr_info_t'nchunks :: Ptr (H5O_hdr_info_t) -> Ptr (CUInt)
p'H5O_hdr_info_t'flags :: Ptr H5O_hdr_info_t -> Ptr CUInt
p'H5O_hdr_info_t'flags Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
12
p'H5O_hdr_info_t'flags :: Ptr (H5O_hdr_info_t) -> Ptr (CUInt)
p'H5O_hdr_info_t'space'total :: Ptr H5O_hdr_info_t -> Ptr HSize_t
p'H5O_hdr_info_t'space'total Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
16
p'H5O_hdr_info_t'space'total :: Ptr (H5O_hdr_info_t) -> Ptr (HSize_t)
p'H5O_hdr_info_t'space'meta :: Ptr H5O_hdr_info_t -> Ptr HSize_t
p'H5O_hdr_info_t'space'meta Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
24
p'H5O_hdr_info_t'space'meta :: Ptr (H5O_hdr_info_t) -> Ptr (HSize_t)
p'H5O_hdr_info_t'space'mesg :: Ptr H5O_hdr_info_t -> Ptr HSize_t
p'H5O_hdr_info_t'space'mesg Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
32
p'H5O_hdr_info_t'space'mesg :: Ptr (H5O_hdr_info_t) -> Ptr (HSize_t)
p'H5O_hdr_info_t'space'free :: Ptr H5O_hdr_info_t -> Ptr HSize_t
p'H5O_hdr_info_t'space'free Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
40
p'H5O_hdr_info_t'space'free :: Ptr (H5O_hdr_info_t) -> Ptr (HSize_t)
p'H5O_hdr_info_t'mesg'present :: Ptr H5O_hdr_info_t -> Ptr Word64
p'H5O_hdr_info_t'mesg'present Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
48
p'H5O_hdr_info_t'mesg'present :: Ptr (H5O_hdr_info_t) -> Ptr (Word64)
p'H5O_hdr_info_t'mesg'shared :: Ptr H5O_hdr_info_t -> Ptr Word64
p'H5O_hdr_info_t'mesg'shared Ptr H5O_hdr_info_t
p = Ptr H5O_hdr_info_t -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_hdr_info_t
p Int
56
p'H5O_hdr_info_t'mesg'shared :: Ptr (H5O_hdr_info_t) -> Ptr (Word64)
instance Storable H5O_hdr_info_t where
sizeOf _ = 64
alignment _ = 8
peek _p = do
v0 <- peekByteOff _p 0
v1 <- peekByteOff _p 4
v2 <- peekByteOff _p 8
v3 <- peekByteOff _p 12
v4 <- peekByteOff _p 16
v5 <- peekByteOff _p 24
v6 <- peekByteOff _p 32
v7 <- peekByteOff _p 40
v8 <- peekByteOff _p 48
v9 <- peekByteOff _p 56
return $ H5O_hdr_info_t v0 v1 v2 v3 v4 v5 v6 v7 v8 v9
poke _p (H5O_hdr_info_t v0 v1 v2 v3 v4 v5 v6 v7 v8 v9) = do
pokeByteOff _p 0 v0
pokeByteOff _p 4 v1
pokeByteOff _p 8 v2
pokeByteOff _p 12 v3
pokeByteOff _p 16 v4
pokeByteOff _p 24 v5
pokeByteOff _p 32 v6
pokeByteOff _p 40 v7
pokeByteOff _p 48 v8
pokeByteOff _p 56 v9
return ()
{-# LINE 126 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 128 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 129 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 130 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 131 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 132 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
data H5O_stat_t = H5O_stat_t{
h5o_stat_t'size :: HSize_t,
h5o_stat_t'free :: HSize_t,
h5o_stat_t'nmesgs :: CUInt,
h5o_stat_t'nchunks :: CUInt
} deriving (Eq,Show)
p'H5O_stat_t'size p = plusPtr p 0
p'H5O_stat_t'size :: Ptr (H5O_stat_t) -> Ptr (HSize_t)
p'H5O_stat_t'free p = plusPtr p 8
p'H5O_stat_t'free :: Ptr (H5O_stat_t) -> Ptr (HSize_t)
p'H5O_stat_t'nmesgs p = plusPtr p 16
p'H5O_stat_t'nmesgs :: Ptr (H5O_stat_t) -> Ptr (CUInt)
p'H5O_stat_t'nchunks p = plusPtr p 20
p'H5O_stat_t'nchunks :: Ptr (H5O_stat_t) -> Ptr (CUInt)
instance Storable H5O_stat_t where
sizeOf _ = 24
alignment _ = 8
peek _p = do
v0 <- peekByteOff _p 0
v1 <- peekByteOff _p 8
v2 <- peekByteOff _p 16
v3 <- peekByteOff _p 20
return $ H5O_stat_t v0 v1 v2 v3
poke _p (H5O_stat_t v0 v1 v2 v3) = do
pokeByteOff _p 0 v0
pokeByteOff _p 8 v1
pokeByteOff _p 16 v2
pokeByteOff _p 20 v3
return ()
{-# LINE 133 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
newtype H5O_msg_crt_idx_t = H5O_msg_crt_idx_t Word32 deriving (Storable, Show, Eq, Ord, Read)
{-# LINE 136 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
newtype H5O_mcdt_search_ret_t = H5O_mcdt_search_ret_t Int32 deriving (Storable, Show)
{-# LINE 138 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_MCDT_SEARCH_ERROR :: H5O_mcdt_search_ret_t
h5o_MCDT_SEARCH_ERROR = H5O_mcdt_search_ret_t (-1)
{-# LINE 141 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_MCDT_SEARCH_CONT :: H5O_mcdt_search_ret_t
h5o_MCDT_SEARCH_CONT = H5O_mcdt_search_ret_t (0)
{-# LINE 144 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_MCDT_SEARCH_STOP :: H5O_mcdt_search_ret_t
h5o_MCDT_SEARCH_STOP = H5O_mcdt_search_ret_t (1)
{-# LINE 147 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
type H5O_mcdt_search_cb_t a = FunPtr (InOut a -> IO H5O_mcdt_search_ret_t)
foreign import ccall "H5Oopen" h5o_open
:: HId_t -> CString -> HId_t -> IO HId_t
foreign import ccall "&H5Oopen" p_H5Oopen
:: FunPtr (HId_t -> CString -> HId_t -> IO HId_t)
{-# LINE 171 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oopen_by_addr" h5o_open_by_addr
:: HId_t -> HAddr_t -> IO HId_t
foreign import ccall "&H5Oopen_by_addr" p_H5Oopen_by_addr
:: FunPtr (HId_t -> HAddr_t -> IO HId_t)
{-# LINE 202 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oopen_by_idx" h5o_open_by_idx
:: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> HId_t -> IO HId_t
foreign import ccall "&H5Oopen_by_idx" p_H5Oopen_by_idx
:: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> HId_t -> IO HId_t)
{-# LINE 221 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oexists_by_name" h5o_exists_by_name
:: HId_t -> CString -> HId_t -> IO HTri_t
foreign import ccall "&H5Oexists_by_name" p_H5Oexists_by_name
:: FunPtr (HId_t -> CString -> HId_t -> IO HTri_t)
{-# LINE 226 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Olink" h5o_link
:: HId_t -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Olink" p_H5Olink
:: FunPtr (HId_t -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
{-# LINE 242 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oincr_refcount" h5o_incr_refcount
:: HId_t -> IO HErr_t
foreign import ccall "&H5Oincr_refcount" p_H5Oincr_refcount
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 256 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Odecr_refcount" h5o_decr_refcount
:: HId_t -> IO HErr_t
foreign import ccall "&H5Odecr_refcount" p_H5Odecr_refcount
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 270 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Ocopy" h5o_copy
:: HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Ocopy" p_H5Ocopy
:: FunPtr (HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
{-# LINE 356 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oset_comment"
:: HId_t -> CString -> IO HErr_t
foreign import ccall "&H5Oset_comment"
:: FunPtr (HId_t -> CString -> IO HErr_t)
{-# LINE 366 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oset_comment_by_name"
:: HId_t -> CString -> CString -> HId_t -> IO HErr_t
foreign import ccall "&H5Oset_comment_by_name"
:: FunPtr (HId_t -> CString -> CString -> HId_t -> IO HErr_t)
{-# LINE 379 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oget_comment"
:: HId_t -> OutArray CChar -> CSize -> IO CSSize
foreign import ccall "&H5Oget_comment"
:: FunPtr (HId_t -> OutArray CChar -> CSize -> IO CSSize)
{-# LINE 388 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oget_comment_by_name"
:: HId_t -> CString -> OutArray CChar -> CSize -> HId_t -> IO CSSize
foreign import ccall "&H5Oget_comment_by_name"
:: FunPtr (HId_t -> CString -> OutArray CChar -> CSize -> HId_t -> IO CSSize)
{-# LINE 398 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oclose" h5o_close
:: HId_t -> IO HErr_t
foreign import ccall "&H5Oclose" p_H5Oclose
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 410 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oare_mdc_flushes_disabled" h5o_are_mdc_flushes_disabled
:: HId_t -> Out hbool_t -> IO HErr_t
foreign import ccall "&H5Oare_mdc_flushes_disabled" p_H5Oare_mdc_flushes_disabled
:: FunPtr (HId_t -> Out hbool_t -> IO HErr_t)
{-# LINE 412 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Odisable_mdc_flushes" h5o_disable_mdc_flushes
:: HId_t -> IO HErr_t
foreign import ccall "&H5Odisable_mdc_flushes" p_H5Odisable_mdc_flushes
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 413 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oenable_mdc_flushes" h5o_enable_mdc_flushes
:: HId_t -> IO HErr_t
foreign import ccall "&H5Oenable_mdc_flushes" p_H5Oenable_mdc_flushes
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 414 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oflush" h5o_flush
:: HId_t -> IO HErr_t
foreign import ccall "&H5Oflush" p_H5Oflush
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 415 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Orefresh" h5o_refresh
:: HId_t -> IO HErr_t
foreign import ccall "&H5Orefresh" p_H5Orefresh
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 416 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 418 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_INFO_BASIC = 1
h5o_INFO_BASIC :: (Num a) => a
{-# LINE 420 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_INFO_TIME = 2
h5o_INFO_TIME :: (Num a) => a
{-# LINE 421 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_INFO_NUM_ATTRS = 4
h5o_INFO_NUM_ATTRS :: (Num a) => a
{-# LINE 422 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_INFO_HDR = 8
h5o_INFO_HDR :: (Num a) => a
{-# LINE 423 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_INFO_META_SIZE = 16
h5o_INFO_META_SIZE :: (Num a) => a
{-# LINE 424 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_INFO_ALL = 31
h5o_INFO_ALL :: (Num a) => a
{-# LINE 425 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 427 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 478 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 480 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 481 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 482 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 483 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 484 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 485 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 486 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 487 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 488 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 489 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 490 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 491 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 492 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
data H5O_info_t = H5O_info_t{
h5o_info_t'fileno :: CULong,
h5o_info_t'addr :: HAddr_t,
h5o_info_t'type :: H5O_type_t,
h5o_info_t'rc :: CUInt,
h5o_info_t'atime :: CTime,
h5o_info_t'mtime :: CTime,
h5o_info_t'ctime :: CTime,
h5o_info_t'btime :: CTime,
h5o_info_t'num_attrs :: HSize_t,
h5o_info_t'hdr :: H5O_hdr_info_t,
h5o_info_t'meta_size'obj :: H5_ih_info_t,
h5o_info_t'meta_size'attr :: H5_ih_info_t
} deriving (Eq,Show)
p'H5O_info_t'fileno :: Ptr H5O_info_t -> Ptr CULong
p'H5O_info_t'fileno Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr CULong
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
0
p'H5O_info_t'fileno :: Ptr (H5O_info_t) -> Ptr (CULong)
p'H5O_info_t'addr :: Ptr H5O_info_t -> Ptr HAddr_t
p'H5O_info_t'addr Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr HAddr_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
8
p'H5O_info_t'addr :: Ptr (H5O_info_t) -> Ptr (HAddr_t)
p'H5O_info_t'type :: Ptr H5O_info_t -> Ptr H5O_type_t
p'H5O_info_t'type Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr H5O_type_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
16
p'H5O_info_t'type :: Ptr (H5O_info_t) -> Ptr (H5O_type_t)
p'H5O_info_t'rc :: Ptr H5O_info_t -> Ptr CUInt
p'H5O_info_t'rc Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
20
p'H5O_info_t'rc :: Ptr (H5O_info_t) -> Ptr (CUInt)
p'H5O_info_t'atime :: Ptr H5O_info_t -> Ptr CTime
p'H5O_info_t'atime Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr CTime
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
24
p'H5O_info_t'atime :: Ptr (H5O_info_t) -> Ptr (CTime)
p'H5O_info_t'mtime :: Ptr H5O_info_t -> Ptr CTime
p'H5O_info_t'mtime Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr CTime
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
32
p'H5O_info_t'mtime :: Ptr (H5O_info_t) -> Ptr (CTime)
p'H5O_info_t'ctime :: Ptr H5O_info_t -> Ptr CTime
p'H5O_info_t'ctime Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr CTime
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
40
p'H5O_info_t'ctime :: Ptr (H5O_info_t) -> Ptr (CTime)
p'H5O_info_t'btime :: Ptr H5O_info_t -> Ptr CTime
p'H5O_info_t'btime Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr CTime
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
48
p'H5O_info_t'btime :: Ptr (H5O_info_t) -> Ptr (CTime)
p'H5O_info_t'num_attrs :: Ptr H5O_info_t -> Ptr HSize_t
p'H5O_info_t'num_attrs Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
56
p'H5O_info_t'num_attrs :: Ptr (H5O_info_t) -> Ptr (HSize_t)
p'H5O_info_t'hdr :: Ptr H5O_info_t -> Ptr H5O_hdr_info_t
p'H5O_info_t'hdr Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr H5O_hdr_info_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
64
p'H5O_info_t'hdr :: Ptr (H5O_info_t) -> Ptr (H5O_hdr_info_t)
p'H5O_info_t'meta_size'obj :: Ptr H5O_info_t -> Ptr H5_ih_info_t
p'H5O_info_t'meta_size'obj Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr H5_ih_info_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
128
p'H5O_info_t'meta_size'obj :: Ptr (H5O_info_t) -> Ptr (H5_ih_info_t)
p'H5O_info_t'meta_size'attr :: Ptr H5O_info_t -> Ptr H5_ih_info_t
p'H5O_info_t'meta_size'attr Ptr H5O_info_t
p = Ptr H5O_info_t -> Int -> Ptr H5_ih_info_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_info_t
p Int
144
p'H5O_info_t'meta_size'attr :: Ptr (H5O_info_t) -> Ptr (H5_ih_info_t)
instance Storable H5O_info_t where
sizeOf :: H5O_info_t -> Int
sizeOf H5O_info_t
_ = Int
160
alignment _ = 8
peek _p = do
v0 <- peekByteOff _p 0
v1 <- peekByteOff _p 8
v2 <- peekByteOff _p 16
v3 <- peekByteOff _p 20
v4 <- peekByteOff _p 24
v5 <- peekByteOff _p 32
v6 <- peekByteOff _p 40
v7 <- peekByteOff _p 48
v8 <- peekByteOff _p 56
v9 <- peekByteOff _p 64
v10 <- peekByteOff _p 128
v11 <- peekByteOff _p 144
return $ H5O_info_t v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11
poke :: Ptr H5O_info_t -> H5O_info_t -> IO ()
poke Ptr H5O_info_t
_p (H5O_info_t CULong
v0 HAddr_t
v1 H5O_type_t
v2 CUInt
v3 CTime
v4 CTime
v5 CTime
v6 CTime
v7 HSize_t
v8 H5O_hdr_info_t
v9 H5_ih_info_t
v10 H5_ih_info_t
v11) = do
Ptr H5O_info_t -> Int -> CULong -> IO ()
forall b. Ptr b -> Int -> CULong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
0 CULong
v0
Ptr H5O_info_t -> Int -> HAddr_t -> IO ()
forall b. Ptr b -> Int -> HAddr_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
8 HAddr_t
v1
Ptr H5O_info_t -> Int -> H5O_type_t -> IO ()
forall b. Ptr b -> Int -> H5O_type_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
16 H5O_type_t
v2
Ptr H5O_info_t -> Int -> CUInt -> IO ()
forall b. Ptr b -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
20 CUInt
v3
Ptr H5O_info_t -> Int -> CTime -> IO ()
forall b. Ptr b -> Int -> CTime -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
24 CTime
v4
Ptr H5O_info_t -> Int -> CTime -> IO ()
forall b. Ptr b -> Int -> CTime -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
32 CTime
v5
Ptr H5O_info_t -> Int -> CTime -> IO ()
forall b. Ptr b -> Int -> CTime -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
40 CTime
v6
Ptr H5O_info_t -> Int -> CTime -> IO ()
forall b. Ptr b -> Int -> CTime -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
48 CTime
v7
Ptr H5O_info_t -> Int -> HSize_t -> IO ()
forall b. Ptr b -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
56 HSize_t
v8
pokeByteOff _p 64 v9
pokeByteOff _p 128 v10
pokeByteOff _p 144 v11
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 493 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 495 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 509 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
type H5O_iterate_t a = FunPtr (HId_t -> CString -> In H5O_info_t -> InOut a -> IO HErr_t)
type H5O_iterate1_t a = H5O_iterate_t a
{-# LINE 512 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 532 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oget_info" h5o_get_info
:: HId_t -> Out H5O_info_t -> IO HErr_t
foreign import ccall "&H5Oget_info" p_H5Oget_info
:: FunPtr (HId_t -> Out H5O_info_t -> IO HErr_t)
{-# LINE 533 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_get_info1 :: HId_t -> Out H5O_info_t -> IO HErr_t
h5o_get_info1 = h5o_get_info
{-# LINE 536 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 557 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oget_info_by_idx" h5o_get_info_by_idx
:: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5O_info_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Oget_info_by_idx" p_H5Oget_info_by_idx
:: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5O_info_t -> HId_t -> IO HErr_t)
{-# LINE 558 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_get_info_by_idx1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5O_info_t -> HId_t -> IO HErr_t
h5o_get_info_by_idx1 = h5o_get_info_by_idx
{-# LINE 561 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 581 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Oget_info_by_name" h5o_get_info_by_name
:: HId_t -> CString -> Out H5O_info_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Oget_info_by_name" p_H5Oget_info_by_name
:: FunPtr (HId_t -> CString -> Out H5O_info_t -> HId_t -> IO HErr_t)
{-# LINE 582 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_get_info_by_name1 :: HId_t -> CString -> Out H5O_info_t -> HId_t -> IO HErr_t
h5o_get_info_by_name1 = h5o_get_info_by_name
{-# LINE 585 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 631 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Ovisit" h5o_visit
:: HId_t -> H5_index_t -> H5_iter_order_t -> H5O_iterate_t a -> InOut a -> IO HErr_t
foreign import ccall "&H5Ovisit" p_H5Ovisit
:: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> H5O_iterate_t a -> InOut a -> IO HErr_t)
{-# LINE 632 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_visit1 :: HId_t -> H5_index_t -> H5_iter_order_t -> H5O_iterate_t a -> InOut a -> IO HErr_t
h5o_visit1 = h5o_visit
{-# LINE 635 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
{-# LINE 682 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
foreign import ccall "H5Ovisit_by_name" h5o_visit_by_name
:: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5O_iterate_t a -> InOut a -> HId_t -> IO HErr_t
foreign import ccall "&H5Ovisit_by_name" p_H5Ovisit_by_name
:: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5O_iterate_t a -> InOut a -> HId_t -> IO HErr_t)
{-# LINE 683 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_visit_by_name1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5O_iterate_t a -> InOut a -> HId_t -> IO HErr_t
h5o_visit_by_name1 = h5o_visit_by_name
{-# LINE 686 "src/Bindings/HDF5/Raw/H5O.hsc" #-}