{-# LINE 1 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
module Bindings.HDF5.Raw.H5F 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.H5AC
import Bindings.HDF5.Raw.H5I
import Foreign.Ptr.Conventions
h5f_ACC_RDONLY :: forall a. Num a => a
h5f_ACC_RDONLY = a
0
h5f_ACC_RDONLY :: (Num a) => a
{-# LINE 32 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_RDWR = 1
h5f_ACC_RDWR :: (Num a) => a
{-# LINE 35 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_TRUNC = 2
h5f_ACC_TRUNC :: (Num a) => a
{-# LINE 38 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_EXCL = 4
h5f_ACC_EXCL :: (Num a) => a
{-# LINE 41 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_DEBUG = 0
h5f_ACC_DEBUG :: (Num a) => a
{-# LINE 44 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_CREAT = 16
h5f_ACC_CREAT :: (Num a) => a
{-# LINE 47 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 49 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_SWMR_WRITE :: forall a. Num a => a
h5f_ACC_SWMR_WRITE = a
32
h5f_ACC_SWMR_WRITE :: (Num a) => a
{-# LINE 55 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_SWMR_READ :: forall a. Num a => a
h5f_ACC_SWMR_READ = a
64
h5f_ACC_SWMR_READ :: (Num a) => a
{-# LINE 61 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 63 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 65 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_ACC_DEFAULT :: forall a. Num a => a
h5f_ACC_DEFAULT = a
65535
h5f_ACC_DEFAULT :: (Num a) => a
{-# LINE 69 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 71 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_FILE :: forall a. Num a => a
h5f_OBJ_FILE = a
1
h5f_OBJ_FILE :: (Num a) => a
{-# LINE 76 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_DATASET = 2
h5f_OBJ_DATASET :: (Num a) => a
{-# LINE 79 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_GROUP = 4
h5f_OBJ_GROUP :: (Num a) => a
{-# LINE 82 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_DATATYPE = 8
h5f_OBJ_DATATYPE :: (Num a) => a
{-# LINE 85 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_ATTR = 16
h5f_OBJ_ATTR :: (Num a) => a
{-# LINE 88 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_ALL = 31
h5f_OBJ_ALL :: (Num a) => a
{-# LINE 90 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_OBJ_LOCAL = 32
h5f_OBJ_LOCAL :: (Num a) => a
{-# LINE 93 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FAMILY_DEFAULT :: HSize_t
h5f_FAMILY_DEFAULT = HSize_t (0)
{-# LINE 95 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 105 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
newtype H5F_scope_t = H5F_scope_t Word32 deriving (Ptr H5F_scope_t -> IO H5F_scope_t
Ptr H5F_scope_t -> Int -> IO H5F_scope_t
Ptr H5F_scope_t -> Int -> H5F_scope_t -> IO ()
Ptr H5F_scope_t -> H5F_scope_t -> IO ()
H5F_scope_t -> Int
(H5F_scope_t -> Int)
-> (H5F_scope_t -> Int)
-> (Ptr H5F_scope_t -> Int -> IO H5F_scope_t)
-> (Ptr H5F_scope_t -> Int -> H5F_scope_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5F_scope_t)
-> (forall b. Ptr b -> Int -> H5F_scope_t -> IO ())
-> (Ptr H5F_scope_t -> IO H5F_scope_t)
-> (Ptr H5F_scope_t -> H5F_scope_t -> IO ())
-> Storable H5F_scope_t
forall b. Ptr b -> Int -> IO H5F_scope_t
forall b. Ptr b -> Int -> H5F_scope_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
poke :: Ptr H5F_scope_t -> H5F_scope_t -> IO ()
$cpoke :: Ptr H5F_scope_t -> H5F_scope_t -> IO ()
peek :: Ptr H5F_scope_t -> IO H5F_scope_t
$cpeek :: Ptr H5F_scope_t -> IO H5F_scope_t
pokeByteOff :: forall b. Ptr b -> Int -> H5F_scope_t -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> H5F_scope_t -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO H5F_scope_t
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5F_scope_t
pokeElemOff :: Ptr H5F_scope_t -> Int -> H5F_scope_t -> IO ()
$cpokeElemOff :: Ptr H5F_scope_t -> Int -> H5F_scope_t -> IO ()
peekElemOff :: Ptr H5F_scope_t -> Int -> IO H5F_scope_t
$cpeekElemOff :: Ptr H5F_scope_t -> Int -> IO H5F_scope_t
alignment :: H5F_scope_t -> Int
$calignment :: H5F_scope_t -> Int
sizeOf :: H5F_scope_t -> Int
$csizeOf :: H5F_scope_t -> Int
Storable, Int -> H5F_scope_t -> ShowS
[H5F_scope_t] -> ShowS
H5F_scope_t -> String
(Int -> H5F_scope_t -> ShowS)
-> (H5F_scope_t -> String)
-> ([H5F_scope_t] -> ShowS)
-> Show H5F_scope_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [H5F_scope_t] -> ShowS
$cshowList :: [H5F_scope_t] -> ShowS
show :: H5F_scope_t -> String
$cshow :: H5F_scope_t -> String
showsPrec :: Int -> H5F_scope_t -> ShowS
$cshowsPrec :: Int -> H5F_scope_t -> ShowS
Show)
{-# LINE 108 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_SCOPE_LOCAL :: H5F_scope_t
h5f_SCOPE_LOCAL :: H5F_scope_t
h5f_SCOPE_LOCAL = Word32 -> H5F_scope_t
H5F_scope_t (Word32
0)
{-# LINE 111 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_SCOPE_GLOBAL :: H5F_scope_t
h5f_SCOPE_GLOBAL :: H5F_scope_t
h5f_SCOPE_GLOBAL = Word32 -> H5F_scope_t
H5F_scope_t (Word32
1)
{-# LINE 114 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_UNLIMITED :: HSize_t
h5f_UNLIMITED :: HSize_t
h5f_UNLIMITED = Word64 -> HSize_t
HSize_t (Word64
18446744073709551615)
{-# LINE 117 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
newtype H5F_close_degree_t = H5F_close_degree_t Word32 deriving (Storable, Show, Eq)
{-# LINE 120 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_CLOSE_DEFAULT :: H5F_close_degree_t
h5f_CLOSE_DEFAULT :: H5F_close_degree_t
h5f_CLOSE_DEFAULT = Word32 -> H5F_close_degree_t
H5F_close_degree_t (Word32
0)
{-# LINE 123 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_CLOSE_WEAK :: H5F_close_degree_t
h5f_CLOSE_WEAK :: H5F_close_degree_t
h5f_CLOSE_WEAK = Word32 -> H5F_close_degree_t
H5F_close_degree_t (Word32
1)
{-# LINE 126 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_CLOSE_SEMI :: H5F_close_degree_t
h5f_CLOSE_SEMI :: H5F_close_degree_t
h5f_CLOSE_SEMI = Word32 -> H5F_close_degree_t
H5F_close_degree_t (Word32
2)
{-# LINE 129 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_CLOSE_STRONG :: H5F_close_degree_t
h5f_CLOSE_STRONG :: H5F_close_degree_t
h5f_CLOSE_STRONG = Word32 -> H5F_close_degree_t
H5F_close_degree_t (Word32
3)
{-# LINE 132 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 135 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 139 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 142 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 145 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 149 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 152 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 155 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 158 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 161 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 164 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 167 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
data H5F_info2_t = H5F_info2_t{
H5F_info2_t -> CUInt
h5f_info2_t'super'version :: CUInt,
H5F_info2_t -> HSize_t
h5f_info2_t'super'super_size :: HSize_t,
H5F_info2_t -> HSize_t
h5f_info2_t'super'super_ext_size :: HSize_t,
H5F_info2_t -> CUInt
h5f_info2_t'free'version :: CUInt,
H5F_info2_t -> HSize_t
h5f_info2_t'free'meta_size :: HSize_t,
H5F_info2_t -> HSize_t
h5f_info2_t'free'tot_space :: HSize_t,
H5F_info2_t -> CUInt
h5f_info2_t'sohm'version :: CUInt,
H5F_info2_t -> HSize_t
h5f_info2_t'sohm'hdr_size :: HSize_t,
h5f_info2_t'sohm'msgs_info :: H5_ih_info_t
} deriving (H5F_info2_t -> H5F_info2_t -> Bool
(H5F_info2_t -> H5F_info2_t -> Bool)
-> (H5F_info2_t -> H5F_info2_t -> Bool) -> Eq H5F_info2_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: H5F_info2_t -> H5F_info2_t -> Bool
$c/= :: H5F_info2_t -> H5F_info2_t -> Bool
== :: H5F_info2_t -> H5F_info2_t -> Bool
$c== :: H5F_info2_t -> H5F_info2_t -> Bool
Eq,Int -> H5F_info2_t -> ShowS
[H5F_info2_t] -> ShowS
H5F_info2_t -> String
(Int -> H5F_info2_t -> ShowS)
-> (H5F_info2_t -> String)
-> ([H5F_info2_t] -> ShowS)
-> Show H5F_info2_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [H5F_info2_t] -> ShowS
$cshowList :: [H5F_info2_t] -> ShowS
show :: H5F_info2_t -> String
$cshow :: H5F_info2_t -> String
showsPrec :: Int -> H5F_info2_t -> ShowS
$cshowsPrec :: Int -> H5F_info2_t -> ShowS
Show)
p'H5F_info2_t'super'version :: Ptr H5F_info2_t -> Ptr CUInt
p'H5F_info2_t'super'version Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
0
p'H5F_info2_t'super'version :: Ptr (H5F_info2_t) -> Ptr (CUInt)
p'H5F_info2_t'super'super_size :: Ptr H5F_info2_t -> Ptr HSize_t
p'H5F_info2_t'super'super_size Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
8
p'H5F_info2_t'super'super_size :: Ptr (H5F_info2_t) -> Ptr (HSize_t)
p'H5F_info2_t'super'super_ext_size :: Ptr H5F_info2_t -> Ptr HSize_t
p'H5F_info2_t'super'super_ext_size Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
16
p'H5F_info2_t'super'super_ext_size :: Ptr (H5F_info2_t) -> Ptr (HSize_t)
p'H5F_info2_t'free'version :: Ptr H5F_info2_t -> Ptr CUInt
p'H5F_info2_t'free'version Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
24
p'H5F_info2_t'free'version :: Ptr (H5F_info2_t) -> Ptr (CUInt)
p'H5F_info2_t'free'meta_size :: Ptr H5F_info2_t -> Ptr HSize_t
p'H5F_info2_t'free'meta_size Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
32
p'H5F_info2_t'free'meta_size :: Ptr (H5F_info2_t) -> Ptr (HSize_t)
p'H5F_info2_t'free'tot_space :: Ptr H5F_info2_t -> Ptr HSize_t
p'H5F_info2_t'free'tot_space Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
40
p'H5F_info2_t'free'tot_space :: Ptr (H5F_info2_t) -> Ptr (HSize_t)
p'H5F_info2_t'sohm'version :: Ptr H5F_info2_t -> Ptr CUInt
p'H5F_info2_t'sohm'version Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
48
p'H5F_info2_t'sohm'version :: Ptr (H5F_info2_t) -> Ptr (CUInt)
p'H5F_info2_t'sohm'hdr_size :: Ptr H5F_info2_t -> Ptr HSize_t
p'H5F_info2_t'sohm'hdr_size Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
56
p'H5F_info2_t'sohm'hdr_size :: Ptr (H5F_info2_t) -> Ptr (HSize_t)
p'H5F_info2_t'sohm'msgs_info :: Ptr H5F_info2_t -> Ptr H5_ih_info_t
p'H5F_info2_t'sohm'msgs_info Ptr H5F_info2_t
p = Ptr H5F_info2_t -> Int -> Ptr H5_ih_info_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info2_t
p Int
64
p'H5F_info2_t'sohm'msgs_info :: Ptr (H5F_info2_t) -> Ptr (H5_ih_info_t)
instance Storable H5F_info2_t where
sizeOf _ = 80
alignment _ = 8
peek _p = do
v0 <- peekByteOff _p 0
v1 <- peekByteOff _p 8
v2 <- peekByteOff _p 16
v3 <- peekByteOff _p 24
v4 <- peekByteOff _p 32
v5 <- peekByteOff _p 40
v6 <- peekByteOff _p 48
v7 <- peekByteOff _p 56
v8 <- peekByteOff _p 64
return $ H5F_info2_t v0 v1 v2 v3 v4 v5 v6 v7 v8
poke :: Ptr H5F_info2_t -> H5F_info2_t -> IO ()
poke Ptr H5F_info2_t
_p (H5F_info2_t CUInt
v0 HSize_t
v1 HSize_t
v2 CUInt
v3 HSize_t
v4 HSize_t
v5 CUInt
v6 HSize_t
v7 H5_ih_info_t
v8) = do
Ptr H5F_info2_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info2_t
_p Int
0 CUInt
v0
Ptr H5F_info2_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info2_t
_p Int
8 HSize_t
v1
pokeByteOff _p 16 v2
pokeByteOff _p 24 v3
pokeByteOff _p 32 v4
Ptr H5F_info2_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info2_t
_p Int
40 HSize_t
v5
pokeByteOff _p 48 v6
pokeByteOff _p 56 v7
pokeByteOff _p 64 v8
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 169 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 171 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 173 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
newtype H5F_mem_t = H5F_mem_t Int32 deriving (Storable, Show, Eq)
{-# LINE 178 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_NOLIST :: H5F_mem_t
h5fd_MEM_NOLIST = H5F_mem_t (-1)
{-# LINE 181 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_DEFAULT :: H5F_mem_t
h5fd_MEM_DEFAULT = H5F_mem_t (0)
{-# LINE 186 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_SUPER :: H5F_mem_t
h5fd_MEM_SUPER = H5F_mem_t (1)
{-# LINE 188 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_BTREE :: H5F_mem_t
h5fd_MEM_BTREE = H5F_mem_t (2)
{-# LINE 190 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_DRAW :: H5F_mem_t
h5fd_MEM_DRAW = H5F_mem_t (3)
{-# LINE 192 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_GHEAP :: H5F_mem_t
h5fd_MEM_GHEAP = H5F_mem_t (4)
{-# LINE 194 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_LHEAP :: H5F_mem_t
h5fd_MEM_LHEAP = H5F_mem_t (5)
{-# LINE 196 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_OHDR :: H5F_mem_t
h5fd_MEM_OHDR = H5F_mem_t (6)
{-# LINE 198 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5fd_MEM_NTYPES = 7
h5fd_MEM_NTYPES :: (Num a) => a
{-# LINE 200 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 202 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 204 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 207 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 210 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 213 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
data H5F_sect_info_t = H5F_sect_info_t{
h5f_sect_info_t'addr :: HAddr_t,
h5f_sect_info_t'size :: HSize_t
} deriving (Eq,Show)
p'H5F_sect_info_t'addr p = plusPtr p 0
p'H5F_sect_info_t'addr :: Ptr (H5F_sect_info_t) -> Ptr (HAddr_t)
p'H5F_sect_info_t'size p = plusPtr p 8
p'H5F_sect_info_t'size :: Ptr (H5F_sect_info_t) -> Ptr (HSize_t)
instance Storable H5F_sect_info_t where
sizeOf _ = 16
alignment _ = 8
peek _p = do
v0 <- peekByteOff _p 0
v1 <- peekByteOff _p 8
return $ H5F_sect_info_t v0 v1
poke _p (H5F_sect_info_t v0 v1) = do
pokeByteOff _p 0 v0
pokeByteOff _p 8 v1
return ()
{-# LINE 215 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 217 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
newtype H5F_libver_t = H5F_libver_t Int32 deriving (Storable, Show)
{-# LINE 220 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_LIBVER_EARLIEST :: H5F_libver_t
h5f_LIBVER_EARLIEST = H5F_libver_t (0)
{-# LINE 223 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_LIBVER_LATEST :: H5F_libver_t
h5f_LIBVER_LATEST = H5F_libver_t (2)
{-# LINE 226 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 233 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 235 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
newtype H5F_file_space_type_t = H5F_file_space_type_t Word32 deriving (Ptr H5F_file_space_type_t -> IO H5F_file_space_type_t
Ptr H5F_file_space_type_t -> Int -> IO H5F_file_space_type_t
Ptr H5F_file_space_type_t -> Int -> H5F_file_space_type_t -> IO ()
Ptr H5F_file_space_type_t -> H5F_file_space_type_t -> IO ()
H5F_file_space_type_t -> Int
(H5F_file_space_type_t -> Int)
-> (H5F_file_space_type_t -> Int)
-> (Ptr H5F_file_space_type_t -> Int -> IO H5F_file_space_type_t)
-> (Ptr H5F_file_space_type_t
-> Int -> H5F_file_space_type_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5F_file_space_type_t)
-> (forall b. Ptr b -> Int -> H5F_file_space_type_t -> IO ())
-> (Ptr H5F_file_space_type_t -> IO H5F_file_space_type_t)
-> (Ptr H5F_file_space_type_t -> H5F_file_space_type_t -> IO ())
-> Storable H5F_file_space_type_t
forall b. Ptr b -> Int -> IO H5F_file_space_type_t
forall b. Ptr b -> Int -> H5F_file_space_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
poke :: Ptr H5F_file_space_type_t -> H5F_file_space_type_t -> IO ()
$cpoke :: Ptr H5F_file_space_type_t -> H5F_file_space_type_t -> IO ()
peek :: Ptr H5F_file_space_type_t -> IO H5F_file_space_type_t
$cpeek :: Ptr H5F_file_space_type_t -> IO H5F_file_space_type_t
pokeByteOff :: forall b. Ptr b -> Int -> H5F_file_space_type_t -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> H5F_file_space_type_t -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO H5F_file_space_type_t
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5F_file_space_type_t
pokeElemOff :: Ptr H5F_file_space_type_t -> Int -> H5F_file_space_type_t -> IO ()
$cpokeElemOff :: Ptr H5F_file_space_type_t -> Int -> H5F_file_space_type_t -> IO ()
peekElemOff :: Ptr H5F_file_space_type_t -> Int -> IO H5F_file_space_type_t
$cpeekElemOff :: Ptr H5F_file_space_type_t -> Int -> IO H5F_file_space_type_t
alignment :: H5F_file_space_type_t -> Int
$calignment :: H5F_file_space_type_t -> Int
sizeOf :: H5F_file_space_type_t -> Int
$csizeOf :: H5F_file_space_type_t -> Int
Storable, Int -> H5F_file_space_type_t -> ShowS
[H5F_file_space_type_t] -> ShowS
H5F_file_space_type_t -> String
(Int -> H5F_file_space_type_t -> ShowS)
-> (H5F_file_space_type_t -> String)
-> ([H5F_file_space_type_t] -> ShowS)
-> Show H5F_file_space_type_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [H5F_file_space_type_t] -> ShowS
$cshowList :: [H5F_file_space_type_t] -> ShowS
show :: H5F_file_space_type_t -> String
$cshow :: H5F_file_space_type_t -> String
showsPrec :: Int -> H5F_file_space_type_t -> ShowS
$cshowsPrec :: Int -> H5F_file_space_type_t -> ShowS
Show, H5F_file_space_type_t -> H5F_file_space_type_t -> Bool
(H5F_file_space_type_t -> H5F_file_space_type_t -> Bool)
-> (H5F_file_space_type_t -> H5F_file_space_type_t -> Bool)
-> Eq H5F_file_space_type_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: H5F_file_space_type_t -> H5F_file_space_type_t -> Bool
$c/= :: H5F_file_space_type_t -> H5F_file_space_type_t -> Bool
== :: H5F_file_space_type_t -> H5F_file_space_type_t -> Bool
$c== :: H5F_file_space_type_t -> H5F_file_space_type_t -> Bool
Eq)
{-# LINE 238 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FILE_SPACE_DEFAULT :: H5F_file_space_type_t
h5f_FILE_SPACE_DEFAULT :: H5F_file_space_type_t
h5f_FILE_SPACE_DEFAULT = Word32 -> H5F_file_space_type_t
H5F_file_space_type_t (Word32
0)
{-# LINE 241 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FILE_SPACE_ALL_PERSIST :: H5F_file_space_type_t
h5f_FILE_SPACE_ALL_PERSIST :: H5F_file_space_type_t
h5f_FILE_SPACE_ALL_PERSIST = Word32 -> H5F_file_space_type_t
H5F_file_space_type_t (Word32
1)
{-# LINE 244 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FILE_SPACE_ALL :: H5F_file_space_type_t
h5f_FILE_SPACE_ALL :: H5F_file_space_type_t
h5f_FILE_SPACE_ALL = Word32 -> H5F_file_space_type_t
H5F_file_space_type_t (Word32
2)
{-# LINE 248 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FILE_SPACE_AGGR_VFD :: H5F_file_space_type_t
h5f_FILE_SPACE_AGGR_VFD :: H5F_file_space_type_t
h5f_FILE_SPACE_AGGR_VFD = Word32 -> H5F_file_space_type_t
H5F_file_space_type_t (Word32
3)
{-# LINE 251 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FILE_SPACE_VFD :: H5F_file_space_type_t
h5f_FILE_SPACE_VFD :: H5F_file_space_type_t
h5f_FILE_SPACE_VFD = Word32 -> H5F_file_space_type_t
H5F_file_space_type_t (Word32
4)
{-# LINE 254 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_FILE_SPACE_NTYPES = 5
h5f_FILE_SPACE_NTYPES :: (Num a) => a
{-# LINE 256 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
h5f_NUM_METADATA_READ_RETRY_TYPES :: forall a. Num a => a
h5f_NUM_METADATA_READ_RETRY_TYPES = a
21
h5f_NUM_METADATA_READ_RETRY_TYPES :: (Num a) => a
{-# LINE 261 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 263 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 264 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 265 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
data H5F_retry_info_t = H5F_retry_info_t{
h5f_retry_info_t'nbins :: CUInt,
h5f_retry_info_t'retries :: Ptr Word32
} deriving (Eq,Show)
p'H5F_retry_info_t'nbins :: Ptr H5F_retry_info_t -> Ptr CUInt
p'H5F_retry_info_t'nbins Ptr H5F_retry_info_t
p = Ptr H5F_retry_info_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_retry_info_t
p Int
0
p'H5F_retry_info_t'nbins :: Ptr (H5F_retry_info_t) -> Ptr (CUInt)
p'H5F_retry_info_t'retries :: Ptr H5F_retry_info_t -> Ptr (Ptr Word32)
p'H5F_retry_info_t'retries Ptr H5F_retry_info_t
p = Ptr H5F_retry_info_t -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_retry_info_t
p Int
8
p'H5F_retry_info_t'retries :: Ptr (H5F_retry_info_t) -> Ptr (Ptr Word32)
instance Storable H5F_retry_info_t where
sizeOf :: H5F_retry_info_t -> Int
sizeOf H5F_retry_info_t
_ = Int
176
alignment :: H5F_retry_info_t -> Int
alignment H5F_retry_info_t
_ = Int
8
peek :: Ptr H5F_retry_info_t -> IO H5F_retry_info_t
peek Ptr H5F_retry_info_t
_p = do
CUInt
v0 <- Ptr H5F_retry_info_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_retry_info_t
_p Int
0
Ptr Word32
v1 <- Ptr H5F_retry_info_t -> Int -> IO (Ptr Word32)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_retry_info_t
_p Int
8
H5F_retry_info_t -> IO H5F_retry_info_t
forall (m :: * -> *) a. Monad m => a -> m a
return (H5F_retry_info_t -> IO H5F_retry_info_t)
-> H5F_retry_info_t -> IO H5F_retry_info_t
forall a b. (a -> b) -> a -> b
$ CUInt -> Ptr Word32 -> H5F_retry_info_t
H5F_retry_info_t CUInt
v0 Ptr Word32
v1
poke :: Ptr H5F_retry_info_t -> H5F_retry_info_t -> IO ()
poke Ptr H5F_retry_info_t
_p (H5F_retry_info_t CUInt
v0 Ptr Word32
v1) = do
Ptr H5F_retry_info_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_retry_info_t
_p Int
0 CUInt
v0
Ptr H5F_retry_info_t -> Int -> Ptr Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_retry_info_t
_p Int
8 Ptr Word32
v1
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 266 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
type H5F_flush_cb_t a = FunPtr (HId_t -> InOut a -> IO HErr_t)
{-# LINE 273 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fis_hdf5" h5f_is_hdf5
:: CString -> IO HTri_t
foreign import ccall "&H5Fis_hdf5" p_H5Fis_hdf5
:: FunPtr (CString -> IO HTri_t)
{-# LINE 285 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fcreate" h5f_create
:: CString -> CUInt -> HId_t -> HId_t -> IO HId_t
foreign import ccall "&H5Fcreate" p_H5Fcreate
:: FunPtr (CString -> CUInt -> HId_t -> HId_t -> IO HId_t)
{-# LINE 308 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fopen" h5f_open
:: CString -> CUInt -> HId_t -> IO HId_t
foreign import ccall "&H5Fopen" p_H5Fopen
:: FunPtr (CString -> CUInt -> HId_t -> IO HId_t)
{-# LINE 324 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Freopen" h5f_reopen
:: HId_t -> IO HId_t
foreign import ccall "&H5Freopen" p_H5Freopen
:: FunPtr (HId_t -> IO HId_t)
{-# LINE 335 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fflush" h5f_flush
:: HId_t -> H5F_scope_t -> IO HErr_t
foreign import ccall "&H5Fflush" p_H5Fflush
:: FunPtr (HId_t -> H5F_scope_t -> IO HErr_t)
{-# LINE 344 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fclose" h5f_close
:: HId_t -> IO HErr_t
foreign import ccall "&H5Fclose" p_H5Fclose
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 356 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_create_plist" h5f_get_create_plist
:: HId_t -> IO HId_t
foreign import ccall "&H5Fget_create_plist" p_H5Fget_create_plist
:: FunPtr (HId_t -> IO HId_t)
{-# LINE 366 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_access_plist" h5f_get_access_plist
:: HId_t -> IO HId_t
foreign import ccall "&H5Fget_access_plist" p_H5Fget_access_plist
:: FunPtr (HId_t -> IO HId_t)
{-# LINE 379 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_intent" h5f_get_intent
:: HId_t -> Out CUInt -> IO HErr_t
foreign import ccall "&H5Fget_intent" p_H5Fget_intent
:: FunPtr (HId_t -> Out CUInt -> IO HErr_t)
{-# LINE 387 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_obj_count" h5f_get_obj_count
:: HId_t -> CUInt -> IO CSSize
foreign import ccall "&H5Fget_obj_count" p_H5Fget_obj_count
:: FunPtr (HId_t -> CUInt -> IO CSSize)
{-# LINE 395 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_obj_ids" h5f_get_obj_ids
:: HId_t -> CUInt -> CSize -> OutArray HId_t -> IO CSSize
foreign import ccall "&H5Fget_obj_ids" p_H5Fget_obj_ids
:: FunPtr (HId_t -> CUInt -> CSize -> OutArray HId_t -> IO CSSize)
{-# LINE 402 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_vfd_handle" h5f_get_vfd_handle
:: HId_t -> HId_t -> Out (Ptr CFile) -> IO HErr_t
foreign import ccall "&H5Fget_vfd_handle" p_H5Fget_vfd_handle
:: FunPtr (HId_t -> HId_t -> Out (Ptr CFile) -> IO HErr_t)
{-# LINE 409 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fmount" h5f_mount
:: HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Fmount" p_H5Fmount
:: FunPtr (HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
{-# LINE 417 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Funmount" h5f_unmount
:: HId_t -> CString -> IO HErr_t
foreign import ccall "&H5Funmount" p_H5Funmount
:: FunPtr (HId_t -> CString -> IO HErr_t)
{-# LINE 431 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_freespace" h5f_get_freespace
:: HId_t -> IO HSSize_t
foreign import ccall "&H5Fget_freespace" p_H5Fget_freespace
:: FunPtr (HId_t -> IO HSSize_t)
{-# LINE 437 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_filesize" h5f_get_filesize
:: HId_t -> Out HSize_t -> IO HErr_t
foreign import ccall "&H5Fget_filesize" p_H5Fget_filesize
:: FunPtr (HId_t -> Out HSize_t -> IO HErr_t)
{-# LINE 446 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 448 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_file_image" h5f_get_file_image
:: HId_t -> InArray a -> CSize -> IO CSSize
foreign import ccall "&H5Fget_file_image" p_H5Fget_file_image
:: FunPtr (HId_t -> InArray a -> CSize -> IO CSSize)
{-# LINE 484 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 486 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_mdc_config" h5f_get_mdc_config
:: HId_t -> Out H5AC_cache_config_t -> IO HErr_t
foreign import ccall "&H5Fget_mdc_config" p_H5Fget_mdc_config
:: FunPtr (HId_t -> Out H5AC_cache_config_t -> IO HErr_t)
{-# LINE 499 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fset_mdc_config" h5f_set_mdc_config
:: HId_t -> In H5AC_cache_config_t -> IO HErr_t
foreign import ccall "&H5Fset_mdc_config" p_H5Fset_mdc_config
:: FunPtr (HId_t -> In H5AC_cache_config_t -> IO HErr_t)
{-# LINE 509 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_mdc_hit_rate" h5f_get_mdc_hit_rate
:: HId_t -> Out CDouble -> IO HErr_t
foreign import ccall "&H5Fget_mdc_hit_rate" p_H5Fget_mdc_hit_rate
:: FunPtr (HId_t -> Out CDouble -> IO HErr_t)
{-# LINE 519 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_mdc_size" h5f_get_mdc_size
:: HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CInt -> IO HErr_t
foreign import ccall "&H5Fget_mdc_size" p_H5Fget_mdc_size
:: FunPtr (HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CInt -> IO HErr_t)
{-# LINE 534 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Freset_mdc_hit_rate_stats" h5f_reset_mdc_hit_rate_stats
:: HId_t -> IO HErr_t
foreign import ccall "&H5Freset_mdc_hit_rate_stats" p_H5Freset_mdc_hit_rate_stats
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 548 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_name" h5f_get_name
:: HId_t -> OutArray CChar -> CSize -> IO CSSize
foreign import ccall "&H5Fget_name" p_H5Fget_name
:: FunPtr (HId_t -> OutArray CChar -> CSize -> IO CSSize)
{-# LINE 565 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 575 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_info2" h5f_get_info2
:: HId_t -> Out H5F_info2_t -> IO HErr_t
foreign import ccall "&H5Fget_info2" p_H5Fget_info2
:: FunPtr (HId_t -> Out H5F_info2_t -> IO HErr_t)
{-# LINE 578 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_metadata_read_retry_info" h5f_get_metadata_read_retry_info
:: HId_t -> Out H5F_retry_info_t -> IO HErr_t
foreign import ccall "&H5Fget_metadata_read_retry_info" p_H5Fget_metadata_read_retry_info
:: FunPtr (HId_t -> Out H5F_retry_info_t -> IO HErr_t)
{-# LINE 581 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fstart_swmr_write" h5f_start_swmr_write
:: HId_t -> IO HErr_t
foreign import ccall "&H5Fstart_swmr_write" p_H5Fstart_swmr_write
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 584 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_free_sections" h5f_get_free_sections
:: HId_t -> H5F_mem_t -> CSize -> Out H5F_sect_info_t -> IO CSSize
foreign import ccall "&H5Fget_free_sections" p_H5Fget_free_sections
:: FunPtr (HId_t -> H5F_mem_t -> CSize -> Out H5F_sect_info_t -> IO CSSize)
{-# LINE 588 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 590 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 592 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fclear_elink_file_cache" h5f_clear_elink_file_cache
:: HId_t -> IO HErr_t
foreign import ccall "&H5Fclear_elink_file_cache" p_H5Fclear_elink_file_cache
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 600 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 601 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 603 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fstart_mdc_logging" h5f_start_mdc_logging
:: HId_t -> IO HErr_t
foreign import ccall "&H5Fstart_mdc_logging" p_H5Fstart_mdc_logging
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 606 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fstop_mdc_logging" h5f_stop_mdc_logging
:: HId_t -> IO HErr_t
foreign import ccall "&H5Fstop_mdc_logging" p_H5Fstop_mdc_logging
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 609 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_mdc_logging_status" h5f_get_mdc_logging_status
:: HId_t -> Out hbool_t -> Out hbool_t -> IO HErr_t
foreign import ccall "&H5Fget_mdc_logging_status" p_H5Fget_mdc_logging_status
:: FunPtr (HId_t -> Out hbool_t -> Out hbool_t -> IO HErr_t)
{-# LINE 614 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fformat_convert" h5f_format_convert
:: HId_t -> IO HErr_t
foreign import ccall "&H5Fformat_convert" p_H5Fformat_convert
:: FunPtr (HId_t -> IO HErr_t)
{-# LINE 617 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall "H5Fget_info1" h5f_get_info1
:: HId_t -> Out H5F_info1_t -> IO HErr_t
foreign import ccall "&H5Fget_info1" p_H5Fget_info1
:: FunPtr (HId_t -> Out H5F_info1_t -> IO HErr_t)
{-# LINE 620 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 622 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 638 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 641 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 645 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 648 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 651 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 654 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
data H5F_info1_t = H5F_info1_t{
h5f_info1_t'super_ext_size :: HSize_t,
h5f_info1_t'sohm'hdr_size :: HSize_t,
h5f_info1_t'sohm'msgs_info :: H5_ih_info_t
} deriving (Eq,Show)
p'H5F_info1_t'super_ext_size :: Ptr H5F_info1_t -> Ptr HSize_t
p'H5F_info1_t'super_ext_size Ptr H5F_info1_t
p = Ptr H5F_info1_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info1_t
p Int
0
p'H5F_info1_t'super_ext_size :: Ptr (H5F_info1_t) -> Ptr (HSize_t)
p'H5F_info1_t'sohm'hdr_size :: Ptr H5F_info1_t -> Ptr HSize_t
p'H5F_info1_t'sohm'hdr_size Ptr H5F_info1_t
p = Ptr H5F_info1_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info1_t
p Int
8
p'H5F_info1_t'sohm'hdr_size :: Ptr (H5F_info1_t) -> Ptr (HSize_t)
p'H5F_info1_t'sohm'msgs_info :: Ptr H5F_info1_t -> Ptr H5_ih_info_t
p'H5F_info1_t'sohm'msgs_info Ptr H5F_info1_t
p = Ptr H5F_info1_t -> Int -> Ptr H5_ih_info_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info1_t
p Int
16
p'H5F_info1_t'sohm'msgs_info :: Ptr (H5F_info1_t) -> Ptr (H5_ih_info_t)
instance Storable H5F_info1_t where
sizeOf :: H5F_info1_t -> Int
sizeOf H5F_info1_t
_ = Int
32
alignment :: H5F_info1_t -> Int
alignment H5F_info1_t
_ = Int
8
peek :: Ptr H5F_info1_t -> IO H5F_info1_t
peek Ptr H5F_info1_t
_p = do
HSize_t
v0 <- Ptr H5F_info1_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_info1_t
_p Int
0
HSize_t
v1 <- Ptr H5F_info1_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_info1_t
_p Int
8
H5_ih_info_t
v2 <- Ptr H5F_info1_t -> Int -> IO H5_ih_info_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_info1_t
_p Int
16
H5F_info1_t -> IO H5F_info1_t
forall (m :: * -> *) a. Monad m => a -> m a
return (H5F_info1_t -> IO H5F_info1_t) -> H5F_info1_t -> IO H5F_info1_t
forall a b. (a -> b) -> a -> b
$ HSize_t -> HSize_t -> H5_ih_info_t -> H5F_info1_t
H5F_info1_t HSize_t
v0 HSize_t
v1 H5_ih_info_t
v2
poke :: Ptr H5F_info1_t -> H5F_info1_t -> IO ()
poke Ptr H5F_info1_t
_p (H5F_info1_t HSize_t
v0 HSize_t
v1 H5_ih_info_t
v2) = do
Ptr H5F_info1_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info1_t
_p Int
0 HSize_t
v0
pokeByteOff _p 8 v1
pokeByteOff _p 16 v2
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 655 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 657 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 659 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 663 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 666 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 669 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 672 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
data H5F_info_t = H5F_info_t{
h5f_info_t'super_ext_size :: HSize_t,
h5f_info_t'sohm'hdr_size :: HSize_t,
h5f_info_t'sohm'msgs_info :: H5_ih_info_t
} deriving (Eq,Show)
p'H5F_info_t'super_ext_size p = plusPtr p 0
p'H5F_info_t'super_ext_size :: Ptr (H5F_info_t) -> Ptr (HSize_t)
p'H5F_info_t'sohm'hdr_size :: Ptr H5F_info_t -> Ptr HSize_t
p'H5F_info_t'sohm'hdr_size Ptr H5F_info_t
p = Ptr H5F_info_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info_t
p Int
8
p'H5F_info_t'sohm'hdr_size :: Ptr (H5F_info_t) -> Ptr (HSize_t)
p'H5F_info_t'sohm'msgs_info :: Ptr H5F_info_t -> Ptr H5_ih_info_t
p'H5F_info_t'sohm'msgs_info Ptr H5F_info_t
p = Ptr H5F_info_t -> Int -> Ptr H5_ih_info_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5F_info_t
p Int
16
p'H5F_info_t'sohm'msgs_info :: Ptr (H5F_info_t) -> Ptr (H5_ih_info_t)
instance Storable H5F_info_t where
sizeOf :: H5F_info_t -> Int
sizeOf H5F_info_t
_ = Int
32
alignment :: H5F_info_t -> Int
alignment H5F_info_t
_ = Int
8
peek :: Ptr H5F_info_t -> IO H5F_info_t
peek Ptr H5F_info_t
_p = do
HSize_t
v0 <- Ptr H5F_info_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_info_t
_p Int
0
HSize_t
v1 <- Ptr H5F_info_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_info_t
_p Int
8
H5_ih_info_t
v2 <- Ptr H5F_info_t -> Int -> IO H5_ih_info_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5F_info_t
_p Int
16
H5F_info_t -> IO H5F_info_t
forall (m :: * -> *) a. Monad m => a -> m a
return (H5F_info_t -> IO H5F_info_t) -> H5F_info_t -> IO H5F_info_t
forall a b. (a -> b) -> a -> b
$ HSize_t -> HSize_t -> H5_ih_info_t -> H5F_info_t
H5F_info_t HSize_t
v0 HSize_t
v1 H5_ih_info_t
v2
poke :: Ptr H5F_info_t -> H5F_info_t -> IO ()
poke Ptr H5F_info_t
_p (H5F_info_t HSize_t
v0 HSize_t
v1 H5_ih_info_t
v2) = do
Ptr H5F_info_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info_t
_p Int
0 HSize_t
v0
Ptr H5F_info_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info_t
_p Int
8 HSize_t
v1
Ptr H5F_info_t -> Int -> H5_ih_info_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5F_info_t
_p Int
16 H5_ih_info_t
v2
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 674 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 711 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 714 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 715 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
foreign import ccall unsafe "H5Fget_info1" h5f_get_info
{-# LINE 719 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
{-# LINE 722 "src/Bindings/HDF5/Raw/H5F.hsc" #-}
:: HId_t -> Out H5F_info_t -> IO HErr_t