{-# 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     -- Generic Functions
import Bindings.HDF5.Raw.H5I    -- IDs
import Foreign.Ptr.Conventions

-- * Constants

-- ** Flags for object copy ('h5o_copy')

-- |Copy only immediate members
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" #-}

-- |Expand soft links into new objects
h5o_COPY_EXPAND_SOFT_LINK_FLAG = 2
h5o_COPY_EXPAND_SOFT_LINK_FLAG :: (Num a) => a

{-# LINE 26 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Expand external links into new objects
h5o_COPY_EXPAND_EXT_LINK_FLAG = 4
h5o_COPY_EXPAND_EXT_LINK_FLAG :: (Num a) => a

{-# LINE 29 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Copy objects that are pointed by references
h5o_COPY_EXPAND_REFERENCE_FLAG = 8
h5o_COPY_EXPAND_REFERENCE_FLAG :: (Num a) => a

{-# LINE 32 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Copy object without copying attributes
h5o_COPY_WITHOUT_ATTR_FLAG = 16
h5o_COPY_WITHOUT_ATTR_FLAG :: (Num a) => a

{-# LINE 35 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Copy NULL messages (empty space)
h5o_COPY_PRESERVE_NULL_FLAG = 32
h5o_COPY_PRESERVE_NULL_FLAG :: (Num a) => a

{-# LINE 38 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


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

-- |Merge committed datatypes in dest file
h5o_COPY_MERGE_COMMITTED_DTYPE_FLAG :: forall a. Num a => a
h5o_COPY_MERGE_COMMITTED_DTYPE_FLAG = a
64
h5o_COPY_MERGE_COMMITTED_DTYPE_FLAG :: (Num a) => a

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


{-# LINE 45 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |All object copying flags (for internal checking)
h5o_COPY_ALL :: forall a. Num a => a
h5o_COPY_ALL = a
127
h5o_COPY_ALL :: (Num a) => a

{-# LINE 48 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- ** Flags for shared message indexes
-- Pass these flags in using the mesg_type_flags parameter in
-- H5P_set_shared_mesg_index.


-- | No shared messages
h5o_SHMESG_NONE_FLAG :: forall a. Num a => a
h5o_SHMESG_NONE_FLAG = a
0
h5o_SHMESG_NONE_FLAG :: (Num a) => a

{-# LINE 56 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- | Simple Dataspace Message
h5o_SHMESG_SDSPACE_FLAG = 2
h5o_SHMESG_SDSPACE_FLAG :: (Num a) => a

{-# LINE 59 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- | Datatype Message
h5o_SHMESG_DTYPE_FLAG = 8
h5o_SHMESG_DTYPE_FLAG :: (Num a) => a

{-# LINE 62 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- | Fill Value Message
h5o_SHMESG_FILL_FLAG = 32
h5o_SHMESG_FILL_FLAG :: (Num a) => a

{-# LINE 65 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- | Filter pipeline message
h5o_SHMESG_PLINE_FLAG = 2048
h5o_SHMESG_PLINE_FLAG :: (Num a) => a

{-# LINE 68 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- | Attribute Message
h5o_SHMESG_ATTR_FLAG = 4096
h5o_SHMESG_ATTR_FLAG :: (Num a) => a

{-# LINE 71 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

h5o_SHMESG_ALL_FLAG = 6186
h5o_SHMESG_ALL_FLAG :: (Num a) => a

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

-- ** Object header status flag definitions

-- |2-bit field indicating # of bytes to store the size of chunk 0's data
h5o_HDR_CHUNK0_SIZE :: forall a. Num a => a
h5o_HDR_CHUNK0_SIZE = a
3
h5o_HDR_CHUNK0_SIZE :: (Num a) => a

{-# LINE 78 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Attribute creation order is tracked
h5o_HDR_ATTR_CRT_ORDER_TRACKED = 4
h5o_HDR_ATTR_CRT_ORDER_TRACKED :: (Num a) => a

{-# LINE 81 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Attribute creation order has index
h5o_HDR_ATTR_CRT_ORDER_INDEXED = 8
h5o_HDR_ATTR_CRT_ORDER_INDEXED :: (Num a) => a

{-# LINE 84 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Non-default attribute storage phase change values stored
h5o_HDR_ATTR_STORE_PHASE_CHANGE = 16
h5o_HDR_ATTR_STORE_PHASE_CHANGE :: (Num a) => a

{-# LINE 87 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Store access, modification, change & birth times for object
h5o_HDR_STORE_TIMES = 32
h5o_HDR_STORE_TIMES :: (Num a) => a

{-# LINE 90 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

h5o_HDR_ALL_FLAGS = 63
h5o_HDR_ALL_FLAGS :: (Num a) => a

{-# LINE 92 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- ** Maximum shared message values

h5o_SHMESG_MAX_NINDEXES :: forall a. Num a => a
h5o_SHMESG_MAX_NINDEXES = a
8
h5o_SHMESG_MAX_NINDEXES :: (Num a) => a

{-# LINE 96 "src/Bindings/HDF5/Raw/H5O.hsc" #-}
h5o_SHMESG_MAX_LIST_SIZE = 5000
h5o_SHMESG_MAX_LIST_SIZE :: (Num a) => a

{-# LINE 97 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- * Types

-- |Types of objects in file
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
poke :: Ptr H5O_type_t -> H5O_type_t -> IO ()
$cpoke :: Ptr H5O_type_t -> H5O_type_t -> IO ()
peek :: Ptr H5O_type_t -> IO H5O_type_t
$cpeek :: Ptr H5O_type_t -> IO H5O_type_t
pokeByteOff :: forall b. Ptr b -> Int -> H5O_type_t -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> H5O_type_t -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO H5O_type_t
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5O_type_t
pokeElemOff :: Ptr H5O_type_t -> Int -> H5O_type_t -> IO ()
$cpokeElemOff :: Ptr H5O_type_t -> Int -> H5O_type_t -> IO ()
peekElemOff :: Ptr H5O_type_t -> Int -> IO H5O_type_t
$cpeekElemOff :: Ptr H5O_type_t -> Int -> IO H5O_type_t
alignment :: H5O_type_t -> Int
$calignment :: H5O_type_t -> Int
sizeOf :: H5O_type_t -> Int
$csizeOf :: H5O_type_t -> Int
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
showList :: [H5O_type_t] -> ShowS
$cshowList :: [H5O_type_t] -> ShowS
show :: H5O_type_t -> String
$cshow :: H5O_type_t -> String
showsPrec :: Int -> H5O_type_t -> ShowS
$cshowsPrec :: Int -> 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
/= :: H5O_type_t -> H5O_type_t -> Bool
$c/= :: H5O_type_t -> H5O_type_t -> Bool
== :: H5O_type_t -> H5O_type_t -> Bool
$c== :: H5O_type_t -> H5O_type_t -> Bool
Eq)

{-# LINE 102 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Unknown object type
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 105 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Object is a group
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 108 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Object is a dataset
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 111 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Object is a named data type
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 114 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Number of different object types
h5o_TYPE_NTYPES = 3
h5o_TYPE_NTYPES :: (Num a) => a

{-# LINE 117 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


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

-- |Information struct for object header metadata
-- (for 'h5o_get_info'/ 'h5o_get_info_by_name' / 'h5o_get_info_by_idx')

{-# LINE 123 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Version number of header format in file

{-# LINE 126 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Number of object header messages

{-# LINE 129 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Number of object header chunks

{-# LINE 132 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Object header status flags

{-# LINE 135 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Total space for storing object header in file

{-# LINE 138 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Space within header for object header metadata information

{-# LINE 141 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Space within header for actual message information

{-# LINE 144 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Free space within object header

{-# LINE 147 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Flags to indicate presence of message type in header

{-# LINE 150 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Flags to indicate message type is shared in header

{-# LINE 153 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

data H5O_hdr_info_t = H5O_hdr_info_t{
  H5O_hdr_info_t -> CUInt
h5o_hdr_info_t'version :: CUInt,
  H5O_hdr_info_t -> CUInt
h5o_hdr_info_t'nmesgs :: CUInt,
  H5O_hdr_info_t -> CUInt
h5o_hdr_info_t'nchunks :: CUInt,
  H5O_hdr_info_t -> CUInt
h5o_hdr_info_t'flags :: CUInt,
  H5O_hdr_info_t -> HSize_t
h5o_hdr_info_t'space'total :: HSize_t,
  H5O_hdr_info_t -> HSize_t
h5o_hdr_info_t'space'meta :: HSize_t,
  H5O_hdr_info_t -> HSize_t
h5o_hdr_info_t'space'mesg :: HSize_t,
  H5O_hdr_info_t -> HSize_t
h5o_hdr_info_t'space'free :: HSize_t,
  H5O_hdr_info_t -> Word64
h5o_hdr_info_t'mesg'present :: Word64,
  H5O_hdr_info_t -> Word64
h5o_hdr_info_t'mesg'shared :: Word64
} deriving (H5O_hdr_info_t -> H5O_hdr_info_t -> Bool
(H5O_hdr_info_t -> H5O_hdr_info_t -> Bool)
-> (H5O_hdr_info_t -> H5O_hdr_info_t -> Bool) -> Eq H5O_hdr_info_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: H5O_hdr_info_t -> H5O_hdr_info_t -> Bool
$c/= :: H5O_hdr_info_t -> H5O_hdr_info_t -> Bool
== :: H5O_hdr_info_t -> H5O_hdr_info_t -> Bool
$c== :: H5O_hdr_info_t -> H5O_hdr_info_t -> Bool
Eq,Int -> H5O_hdr_info_t -> ShowS
[H5O_hdr_info_t] -> ShowS
H5O_hdr_info_t -> String
(Int -> H5O_hdr_info_t -> ShowS)
-> (H5O_hdr_info_t -> String)
-> ([H5O_hdr_info_t] -> ShowS)
-> Show H5O_hdr_info_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [H5O_hdr_info_t] -> ShowS
$cshowList :: [H5O_hdr_info_t] -> ShowS
show :: H5O_hdr_info_t -> String
$cshow :: H5O_hdr_info_t -> String
showsPrec :: Int -> H5O_hdr_info_t -> ShowS
$cshowsPrec :: Int -> H5O_hdr_info_t -> ShowS
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 :: H5O_hdr_info_t -> Int
sizeOf H5O_hdr_info_t
_ = Int
64
  alignment :: H5O_hdr_info_t -> Int
alignment H5O_hdr_info_t
_ = Int
8
  peek :: Ptr H5O_hdr_info_t -> IO H5O_hdr_info_t
peek Ptr H5O_hdr_info_t
_p = do
    CUInt
v0 <- Ptr H5O_hdr_info_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
0
    CUInt
v1 <- Ptr H5O_hdr_info_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
4
    CUInt
v2 <- Ptr H5O_hdr_info_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
8
    CUInt
v3 <- Ptr H5O_hdr_info_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
12
    HSize_t
v4 <- Ptr H5O_hdr_info_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
16
    HSize_t
v5 <- Ptr H5O_hdr_info_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
24
    HSize_t
v6 <- Ptr H5O_hdr_info_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
32
    HSize_t
v7 <- Ptr H5O_hdr_info_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
40
    Word64
v8 <- Ptr H5O_hdr_info_t -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
48
    Word64
v9 <- Ptr H5O_hdr_info_t -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_hdr_info_t
_p Int
56
    H5O_hdr_info_t -> IO H5O_hdr_info_t
forall (m :: * -> *) a. Monad m => a -> m a
return (H5O_hdr_info_t -> IO H5O_hdr_info_t)
-> H5O_hdr_info_t -> IO H5O_hdr_info_t
forall a b. (a -> b) -> a -> b
$ CUInt
-> CUInt
-> CUInt
-> CUInt
-> HSize_t
-> HSize_t
-> HSize_t
-> HSize_t
-> Word64
-> Word64
-> H5O_hdr_info_t
H5O_hdr_info_t CUInt
v0 CUInt
v1 CUInt
v2 CUInt
v3 HSize_t
v4 HSize_t
v5 HSize_t
v6 HSize_t
v7 Word64
v8 Word64
v9
  poke :: Ptr H5O_hdr_info_t -> H5O_hdr_info_t -> IO ()
poke Ptr H5O_hdr_info_t
_p (H5O_hdr_info_t CUInt
v0 CUInt
v1 CUInt
v2 CUInt
v3 HSize_t
v4 HSize_t
v5 HSize_t
v6 HSize_t
v7 Word64
v8 Word64
v9) = do
    Ptr H5O_hdr_info_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
0 CUInt
v0
    Ptr H5O_hdr_info_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
4 CUInt
v1
    Ptr H5O_hdr_info_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
8 CUInt
v2
    Ptr H5O_hdr_info_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
12 CUInt
v3
    Ptr H5O_hdr_info_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
16 HSize_t
v4
    Ptr H5O_hdr_info_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
24 HSize_t
v5
    Ptr H5O_hdr_info_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
32 HSize_t
v6
    Ptr H5O_hdr_info_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
40 HSize_t
v7
    Ptr H5O_hdr_info_t -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
48 Word64
v8
    Ptr H5O_hdr_info_t -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_hdr_info_t
_p Int
56 Word64
v9
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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


{-# LINE 157 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Information struct for object
-- (for 'h5o_get_info'/ 'h5o_get_info_by_name' / 'h5o_get_info_by_idx')

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

-- |File number that object is located in

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

-- |Object address in file

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

-- |Basic object type (group, dataset, etc.)

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

-- |Reference count of object

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

-- |Access time

{-# LINE 176 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Modification time

{-# LINE 179 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Change time

{-# LINE 182 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Birth time

{-# LINE 185 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |# of attributes attached to object

{-# LINE 188 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


{-# LINE 190 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Object header information

{-# LINE 193 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


{-# LINE 227 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |v1/v2 B-tree & local/fractal heap for groups, B-tree for chunked datasets

{-# LINE 230 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |v2 B-tree & heap for attributes

{-# LINE 233 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

data H5O_info_t = H5O_info_t{
  H5O_info_t -> CULong
h5o_info_t'fileno :: CULong,
  H5O_info_t -> HAddr_t
h5o_info_t'addr :: HAddr_t,
  H5O_info_t -> H5O_type_t
h5o_info_t'type :: H5O_type_t,
  h5o_info_t'rc :: CUInt,
  H5O_info_t -> CTime
h5o_info_t'atime :: CTime,
  H5O_info_t -> CTime
h5o_info_t'mtime :: CTime,
  h5o_info_t'ctime :: CTime,
  H5O_info_t -> CTime
h5o_info_t'btime :: CTime,
  h5o_info_t'num_attrs :: HSize_t,
  H5O_info_t -> H5O_hdr_info_t
h5o_info_t'hdr :: H5O_hdr_info_t,
  H5O_info_t -> H5_ih_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 :: H5O_info_t -> Int
alignment H5O_info_t
_ = Int
8
  peek :: Ptr H5O_info_t -> IO H5O_info_t
peek Ptr H5O_info_t
_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 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 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 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 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 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 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 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 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 a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
56 HSize_t
v8
    Ptr H5O_info_t -> Int -> H5O_hdr_info_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
64 H5O_hdr_info_t
v9
    Ptr H5O_info_t -> Int -> H5_ih_info_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
128 H5_ih_info_t
v10
    Ptr H5O_info_t -> Int -> H5_ih_info_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_info_t
_p Int
144 H5_ih_info_t
v11
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{-# LINE 235 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


-- |Typedef for message creation indexes
newtype H5O_msg_crt_idx_t = H5O_msg_crt_idx_t Word32 deriving (Storable, Show, Eq, Ord, Read)

{-# LINE 239 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Prototype for 'h5o_visit' / 'h5o_visit_by_name' operator
type H5O_iterate_t a = FunPtr (HId_t -> CString -> In H5O_info_t -> InOut a -> IO HErr_t)

newtype H5O_mcdt_search_ret_t = H5O_mcdt_search_ret_t Int32 deriving (Storable, Show)

{-# LINE 244 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Abort H5Ocopy
h5o_MCDT_SEARCH_ERROR :: H5O_mcdt_search_ret_t
h5o_MCDT_SEARCH_ERROR = H5O_mcdt_search_ret_t (-1)

{-# LINE 247 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Continue the global search of all committed datatypes in the destination file
h5o_MCDT_SEARCH_CONT :: H5O_mcdt_search_ret_t
h5o_MCDT_SEARCH_CONT = H5O_mcdt_search_ret_t (0)

{-# LINE 250 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Stop the search, but continue copying.  The committed datatype will be copied but not merged.
h5o_MCDT_SEARCH_STOP :: H5O_mcdt_search_ret_t
h5o_MCDT_SEARCH_STOP = H5O_mcdt_search_ret_t (1)

{-# LINE 253 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Callback to invoke when completing the search for a matching committed datatype from the committed dtype list
--
-- > typedef H5O_mcdt_search_ret_t (*H5O_mcdt_search_cb_t)(void *op_data);
type H5O_mcdt_search_cb_t a = FunPtr (InOut a -> IO H5O_mcdt_search_ret_t)

-- * Functions

-- |Opens an object within an HDF5 file.
--
-- This function opens an object in the same way that 'h5g_open2',
-- 'h5t_open2', and 'h5d_open2' do. However, 'h5o_open' doesn't require
-- the type of object to be known beforehand. This can be
-- useful in user-defined links, for instance, when only a
-- path is known.
--
-- The opened object should be closed again with 'h5o_close'
-- or 'h5g_close', 'h5t_close', or 'h5d_close'.
--
-- On success, returns an open object identifier
-- On failure, returns a negative value.
--
-- > hid_t H5Oopen(hid_t loc_id, const char *name, hid_t lapl_id);
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 277 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Warning! This function is EXTREMELY DANGEROUS!
--
-- Improper use can lead to FILE CORRUPTION, INACCESSIBLE DATA,
-- and other VERY BAD THINGS!
--
-- This function opens an object using its address within the
-- HDF5 file, similar to an HDF5 hard link. The open object
-- is identical to an object opened with 'h5o_open' and should
-- be closed with 'h5o_close' or a type-specific closing
-- function (such as 'h5g_close').
--
-- This function is very dangerous if called on an invalid
-- address. For this reason, 'h5o_incr_refcount' should be
-- used to prevent HDF5 from deleting any object that is
-- referenced by address (e.g. by a user-defined link).
-- 'h5o_decr_refcount' should be used when the object is
-- no longer being referenced by address (e.g. when the UD link
-- is deleted).
--
-- The address of the HDF5 file on disk has no effect on
-- 'h5o_open_by_addr', nor does the use of any unusual file
-- drivers. The \"address\" is really the offset within the
-- HDF5 file, and HDF5's file drivers will transparently
-- map this to an address on disk for the filesystem.
--
-- On success, returns an open object identifier
-- On failure, returns a negative value.
--
-- > hid_t H5Oopen_by_addr(hid_t loc_id, haddr_t addr);
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 308 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Opens an object within an HDF5 file, according to the offset
-- within an index.
--
-- This function opens an object in the same way that 'h5g_open',
-- 'h5t_open', and 'h5d_open' do. However, 'h5o_open' doesn't require
-- the type of object to be known beforehand. This can be
-- useful in user-defined links, for instance, when only a
-- path is known.
--
-- The opened object should be closed again with 'h5o_close'
-- or 'h5g_close', 'h5t_close', or 'h5d_close'.
--
-- On success, returns an open object identifier
-- On failure, returns a negative value.
--
-- > hid_t H5Oopen_by_idx(hid_t loc_id, const char *group_name,
-- >     H5_index_t idx_type, H5_iter_order_t order, hsize_t n, hid_t lapl_id);
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 327 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


{-# LINE 329 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Determine if a linked-to object exists
--
-- > htri_t H5Oexists_by_name(hid_t loc_id, const char *name, hid_t lapl_id);
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 334 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


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

-- |Retrieve information about an object.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oget_info(hid_t loc_id, H5O_info_t *oinfo);
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 343 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Retrieve information about an object.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oget_info_by_name(hid_t loc_id, const char *name, H5O_info_t *oinfo,
-- >     hid_t lapl_id);
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 351 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Retrieve information about an object, according to the order
-- of an index.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oget_info_by_idx(hid_t loc_id, const char *group_name,
-- >     H5_index_t idx_type, H5_iter_order_t order, hsize_t n, H5O_info_t *oinfo,
-- >     hid_t lapl_id);
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 361 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Creates a hard link from 'new_name' to the object specified
-- by 'obj_id' using properties defined in the Link Creation
-- Property List 'lcpl'.
--
-- This function should be used to link objects that have just
-- been created.
--
-- 'new_name' is interpreted relative to 'new_loc_id', which
-- is either a file ID or a group ID.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Olink(hid_t obj_id, hid_t new_loc_id, const char *new_name,
-- >     hid_t lcpl_id, hid_t lapl_id);
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 377 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Warning! This function is EXTREMELY DANGEROUS!
-- Improper use can lead to FILE CORRUPTION, INACCESSIBLE DATA,
-- and other VERY BAD THINGS!
--
-- This function increments the \"hard link\" reference count
-- for an object. It should be used when a user-defined link
-- that references an object by address is created. When the
-- link is deleted, 'h5o_decr_refcount' should be used.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oincr_refcount(hid_t object_id);
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 391 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Warning! This function is EXTREMELY DANGEROUS!
-- Improper use can lead to FILE CORRUPTION, INACCESSIBLE DATA,
-- and other VERY BAD THINGS!
--
-- This function decrements the \"hard link\" reference count
-- for an object. It should be used when user-defined links
-- that reference an object by address are deleted, and only
-- after 'h5o_incr_refcount' has already been used.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Odecr_refcount(hid_t object_id);
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 405 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Copy an object (group or dataset) to destination location
-- within a file or cross files. 'plist_id' is a property list
-- which is used to pass user options and properties to the
-- copy. The name, 'dst_name', must not already be taken by some
-- other object in the destination group.
--
-- 'h5o_copy' will fail if the name of the destination object
--     exists in the destination group.  For example,
--     @H5Ocopy(fid_src, \"/dset\", fid_dst, \"/dset\", ...)@
--     will fail if \"/dset\" exists in the destination file
--
-- OPTIONS THAT HAVE BEEN IMPLEMENTED:
--
--     ['h5o_COPY_SHALLOW_HIERARCHY_FLAG']
--         If this flag is specified, only immediate members of
--         the group are copied. Otherwise (default), it will
--         recursively copy all objects below the group
--
--     ['h5o_COPY_EXPAND_SOFT_LINK_FLAG']
--         If this flag is specified, it will copy the objects
--         pointed by the soft links. Otherwise (default), it
--         will copy the soft link as they are
--
--     ['h5o_COPY_WITHOUT_ATTR_FLAG']
--         If this flag is specified, it will copy object without
--         copying attributes. Otherwise (default), it will
--         copy object along with all its attributes
--
--     ['h5o_COPY_EXPAND_REFERENCE_FLAG']
--         1. Copy object between two different files:
--             When this flag is specified, it will copy objects that
--             are pointed by the references and update the values of
--             references in the destination file.  Otherwise (default)
--             the values of references in the destination will set to
--             zero
--             The current implementation does not handle references
--             inside of other datatype structure. For example, if
--             a member of compound datatype is reference, H5Ocopy()
--             will copy that field as it is. It will not set the
--             value to zero as default is used nor copy the object
--             pointed by that field the flag is set
--         2. Copy object within the same file:
--             This flag does not have any effect to the 'h5o_copy'.
--             Datasets or attributes of references are copied as they
--             are, i.e. values of references of the destination object
--             are the same as the values of the source object
--
-- OPTIONS THAT MAY APPLY TO COPY IN THE FUTURE:
--
--     ['h5o_COPY_EXPAND_EXT_LINK_FLAG']
--         If this flag is specified, it will expand the external links
--         into new objects, Otherwise (default), it will keep external
--         links as they are (default)
--
-- PROPERTIES THAT MAY APPLY TO COPY IN FUTURE:
--
--   * Change data layout such as chunk size
--
--   * Add filter such as data compression.
--
--   * Add an attribute to the copied object(s) that say the date/time
--     for the copy or other information about the source file.
--
-- The intermediate group creation property should be passed in
-- using the lcpl instead of the ocpypl.
--
-- Parameters:
--
-- [@ src_loc_id :: HId_t   @]  Source file or group identifier.
--
-- [@ src_name   :: CString @]  Name of the source object to be copied
--
-- [@ dst_loc_id :: HId_t   @]  Destination file or group identifier
--
-- [@ dst_name   :: CString @]  Name of the destination object
--
-- [@ ocpypl_id  :: HId_t   @]  Properties which apply to the copy
--
-- [@ lcpl_id    :: HId_t   @]  Properties which apply to the new hard link
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Ocopy(hid_t src_loc_id, const char *src_name, hid_t dst_loc_id,
-- >     const char *dst_name, hid_t ocpypl_id, hid_t lcpl_id);
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 491 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Gives the specified object a comment.  The 'comment' string
-- should be a null terminated string.  An object can have only
-- one comment at a time.  Passing NULL for the 'comment' argument
-- will remove the comment property from the object.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oset_comment(hid_t obj_id, const char *comment);
foreign import ccall "H5Oset_comment" h5o_set_comment
  :: HId_t -> CString -> IO HErr_t
foreign import ccall "&H5Oset_comment" p_H5Oset_comment
  :: FunPtr (HId_t -> CString -> IO HErr_t)

{-# LINE 501 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Gives the specified object a comment.  The 'comment' string
-- should be a null terminated string.  An object can have only
-- one comment at a time.  Passing NULL for the 'comment' argument
-- will remove the comment property from the object.
--
-- Note:  Deprecated in favor of using attributes on objects.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oset_comment_by_name(hid_t loc_id, const char *name,
-- >     const char *comment, hid_t lapl_id);
foreign import ccall "H5Oset_comment_by_name" h5o_set_comment_by_name
  :: HId_t -> CString -> CString -> HId_t -> IO HErr_t
foreign import ccall "&H5Oset_comment_by_name" p_H5Oset_comment_by_name
  :: FunPtr (HId_t -> CString -> CString -> HId_t -> IO HErr_t)

{-# LINE 514 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Retrieve comment for an object.
--
-- On success, returns the number of bytes in the comment including the
-- null terminator, or zero if the object has no comment.  On failure
-- returns a negative value.
--
-- > ssize_t H5Oget_comment(hid_t obj_id, char *comment, size_t bufsize);
foreign import ccall "H5Oget_comment" h5o_get_comment
  :: HId_t -> OutArray CChar -> CSize -> IO CSSize
foreign import ccall "&H5Oget_comment" p_H5Oget_comment
  :: FunPtr (HId_t -> OutArray CChar -> CSize -> IO CSSize)

{-# LINE 523 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Retrieve comment for an object.
--
-- On success, returns the number of bytes in the comment including the
-- null terminator, or zero if the object has no comment.  On failure
-- returns a negative value.
--
-- > ssize_t H5Oget_comment_by_name(hid_t loc_id, const char *name,
-- >     char *comment, size_t bufsize, hid_t lapl_id);
foreign import ccall "H5Oget_comment_by_name" h5o_get_comment_by_name
  :: HId_t -> CString -> OutArray CChar -> CSize -> HId_t -> IO CSSize
foreign import ccall "&H5Oget_comment_by_name" p_H5Oget_comment_by_name
  :: FunPtr (HId_t -> CString -> OutArray CChar -> CSize -> HId_t -> IO CSSize)

{-# LINE 533 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Recursively visit an object and all the objects reachable
-- from it.  If the starting object is a group, all the objects
-- linked to from that group will be visited.  Links within
-- each group are visited according to the order within the
-- specified index (unless the specified index does not exist for
-- a particular group, then the "name" index is used).
--
-- NOTE: Soft links and user-defined links are ignored during
-- this operation.
--
-- NOTE: Each _object_ reachable from the initial group will only
-- be visited once.  If multiple hard links point to the same
-- object, the first link to the object's path (according to the
-- iteration index and iteration order given) will be used to in
-- the callback about the object.
--
-- On success, returns the return value of the first operator that
-- returns non-zero, or zero if all members were processed with no
-- operator returning non-zero.
--
-- Returns negative if something goes wrong within the library, or
-- the negative value returned by one of the operators.
--
-- > herr_t H5Ovisit(hid_t obj_id, H5_index_t idx_type, H5_iter_order_t order,
-- >     H5O_iterate_t op, void *op_data);
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 560 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Recursively visit an object and all the objects reachable
-- from it.  If the starting object is a group, all the objects
-- linked to from that group will be visited.  Links within
-- each group are visited according to the order within the
-- specified index (unless the specified index does not exist for
-- a particular group, then the "name" index is used).
--
-- NOTE: Soft links and user-defined links are ignored during
-- this operation.
--
-- NOTE: Each _object_ reachable from the initial group will only
-- be visited once.  If multiple hard links point to the same
-- object, the first link to the object's path (according to the
-- iteration index and iteration order given) will be used to in
-- the callback about the object.
--
-- On success, returns the return value of the first operator that
-- returns non-zero, or zero if all members were processed with no
-- operator returning non-zero.
--
-- Returns negative if something goes wrong within the library, or
-- the negative value returned by one of the operators.
--
-- > herr_t H5Ovisit_by_name(hid_t loc_id, const char *obj_name,
-- >     H5_index_t idx_type, H5_iter_order_t order, H5O_iterate_t op,
-- >     void *op_data, hid_t lapl_id);
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 588 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Close an open file object.
--
-- This is the companion to 'h5o_open'. It is used to close any
-- open object in an HDF5 file (but not IDs are that not file
-- objects, such as property lists and dataspaces). It has
-- the same effect as calling 'h5g_close', 'h5d_close', or 'h5t_close'.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Oclose(hid_t object_id);
foreign import ccall "H5Oclose" h5o_close
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Oclose" p_H5Oclose
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 600 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


{-# LINE 602 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- > herr_t H5Oflush(hid_t obj_id);
foreign import ccall "H5Oflush" h5o_flush
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Oflush" p_H5Oflush
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 605 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- > herr_t H5Orefresh(hid_t oid);
foreign import ccall "H5Orefresh" h5o_refresh
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Orefresh" p_H5Orefresh
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 608 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- > herr_t H5Odisable_mdc_flushes(hid_t object_id);
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 611 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- > herr_t H5Oenable_mdc_flushes(hid_t object_id);
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 614 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- > herr_t H5Oare_mdc_flushes_disabled(hid_t object_id, hbool_t *are_disabled);
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 617 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


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


{-# LINE 621 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- * Deprecated types

-- |A struct that's part of the 'h5g_stat_t' routine (deprecated)

{-# LINE 626 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Total size of object header in file

{-# LINE 629 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Free space within object header

{-# LINE 632 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Number of object header messages

{-# LINE 635 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

-- |Number of object header chunks

{-# LINE 638 "src/Bindings/HDF5/Raw/H5O.hsc" #-}

data H5O_stat_t = H5O_stat_t{
  H5O_stat_t -> HSize_t
h5o_stat_t'size :: HSize_t,
  H5O_stat_t -> HSize_t
h5o_stat_t'free :: HSize_t,
  H5O_stat_t -> CUInt
h5o_stat_t'nmesgs :: CUInt,
  H5O_stat_t -> CUInt
h5o_stat_t'nchunks :: CUInt
} deriving (H5O_stat_t -> H5O_stat_t -> Bool
(H5O_stat_t -> H5O_stat_t -> Bool)
-> (H5O_stat_t -> H5O_stat_t -> Bool) -> Eq H5O_stat_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: H5O_stat_t -> H5O_stat_t -> Bool
$c/= :: H5O_stat_t -> H5O_stat_t -> Bool
== :: H5O_stat_t -> H5O_stat_t -> Bool
$c== :: H5O_stat_t -> H5O_stat_t -> Bool
Eq,Int -> H5O_stat_t -> ShowS
[H5O_stat_t] -> ShowS
H5O_stat_t -> String
(Int -> H5O_stat_t -> ShowS)
-> (H5O_stat_t -> String)
-> ([H5O_stat_t] -> ShowS)
-> Show H5O_stat_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [H5O_stat_t] -> ShowS
$cshowList :: [H5O_stat_t] -> ShowS
show :: H5O_stat_t -> String
$cshow :: H5O_stat_t -> String
showsPrec :: Int -> H5O_stat_t -> ShowS
$cshowsPrec :: Int -> H5O_stat_t -> ShowS
Show)
p'H5O_stat_t'size :: Ptr H5O_stat_t -> Ptr HSize_t
p'H5O_stat_t'size Ptr H5O_stat_t
p = Ptr H5O_stat_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_stat_t
p Int
0
p'H5O_stat_t'size :: Ptr (H5O_stat_t) -> Ptr (HSize_t)
p'H5O_stat_t'free :: Ptr H5O_stat_t -> Ptr HSize_t
p'H5O_stat_t'free Ptr H5O_stat_t
p = Ptr H5O_stat_t -> Int -> Ptr HSize_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_stat_t
p Int
8
p'H5O_stat_t'free :: Ptr (H5O_stat_t) -> Ptr (HSize_t)
p'H5O_stat_t'nmesgs :: Ptr H5O_stat_t -> Ptr CUInt
p'H5O_stat_t'nmesgs Ptr H5O_stat_t
p = Ptr H5O_stat_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_stat_t
p Int
16
p'H5O_stat_t'nmesgs :: Ptr (H5O_stat_t) -> Ptr (CUInt)
p'H5O_stat_t'nchunks :: Ptr H5O_stat_t -> Ptr CUInt
p'H5O_stat_t'nchunks Ptr H5O_stat_t
p = Ptr H5O_stat_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5O_stat_t
p Int
20
p'H5O_stat_t'nchunks :: Ptr (H5O_stat_t) -> Ptr (CUInt)
instance Storable H5O_stat_t where
  sizeOf :: H5O_stat_t -> Int
sizeOf H5O_stat_t
_ = Int
24
  alignment :: H5O_stat_t -> Int
alignment H5O_stat_t
_ = Int
8
  peek :: Ptr H5O_stat_t -> IO H5O_stat_t
peek Ptr H5O_stat_t
_p = do
    HSize_t
v0 <- Ptr H5O_stat_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_stat_t
_p Int
0
    HSize_t
v1 <- Ptr H5O_stat_t -> Int -> IO HSize_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_stat_t
_p Int
8
    CUInt
v2 <- Ptr H5O_stat_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_stat_t
_p Int
16
    CUInt
v3 <- Ptr H5O_stat_t -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5O_stat_t
_p Int
20
    H5O_stat_t -> IO H5O_stat_t
forall (m :: * -> *) a. Monad m => a -> m a
return (H5O_stat_t -> IO H5O_stat_t) -> H5O_stat_t -> IO H5O_stat_t
forall a b. (a -> b) -> a -> b
$ HSize_t -> HSize_t -> CUInt -> CUInt -> H5O_stat_t
H5O_stat_t HSize_t
v0 HSize_t
v1 CUInt
v2 CUInt
v3
  poke :: Ptr H5O_stat_t -> H5O_stat_t -> IO ()
poke Ptr H5O_stat_t
_p (H5O_stat_t HSize_t
v0 HSize_t
v1 CUInt
v2 CUInt
v3) = do
    Ptr H5O_stat_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_stat_t
_p Int
0 HSize_t
v0
    Ptr H5O_stat_t -> Int -> HSize_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_stat_t
_p Int
8 HSize_t
v1
    Ptr H5O_stat_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_stat_t
_p Int
16 CUInt
v2
    Ptr H5O_stat_t -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5O_stat_t
_p Int
20 CUInt
v3
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{-# LINE 640 "src/Bindings/HDF5/Raw/H5O.hsc" #-}


{-# LINE 642 "src/Bindings/HDF5/Raw/H5O.hsc" #-}