{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Bindings.HDF5.PropertyList.FCPL
( module Bindings.HDF5.PropertyList.GCPL
, FCPL
, FileCreationPropertyList
, setUserblock
, getUserblock
, setSizes
, getSizes
, setSymK
, getSymK
, setIstoreK
, getIstoreK
, setSharedMesgNIndexes
, getSharedMesgNIndexes
, setSharedMesgIndex
, getSharedMesgIndex
, setSharedMesgPhaseChange
, getSharedMesgPhaseChange
) where
import Bindings.HDF5.Core
import Bindings.HDF5.Error
import Bindings.HDF5.PropertyList.GCPL
import Bindings.HDF5.Raw.H5P
import Data.Maybe
import Foreign.C.Types
import Foreign.Ptr.Conventions
newtype FCPL = FCPL GCPL
deriving (FCPL -> FCPL -> Bool
(FCPL -> FCPL -> Bool) -> (FCPL -> FCPL -> Bool) -> Eq FCPL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FCPL -> FCPL -> Bool
== :: FCPL -> FCPL -> Bool
$c/= :: FCPL -> FCPL -> Bool
/= :: FCPL -> FCPL -> Bool
Eq, FCPL -> HId_t
(FCPL -> HId_t) -> HId FCPL
forall t. (t -> HId_t) -> HId t
$chid :: FCPL -> HId_t
hid :: FCPL -> HId_t
HId, HId_t -> FCPL
(HId_t -> FCPL) -> FromHId FCPL
forall t. (HId_t -> t) -> FromHId t
$cuncheckedFromHId :: HId_t -> FCPL
uncheckedFromHId :: HId_t -> FCPL
FromHId, FCPL -> Bool
(FCPL -> Bool) -> HDFResultType FCPL
forall t. (t -> Bool) -> HDFResultType t
$cisError :: FCPL -> Bool
isError :: FCPL -> Bool
HDFResultType, FromHId FCPL
HId FCPL
(HId FCPL, FromHId FCPL) => PropertyListOrClass FCPL
forall t. (HId t, FromHId t) => PropertyListOrClass t
PropertyListOrClass, PropertyList FCPL
PropertyList FCPL => ObjectCreationPropertyList FCPL
forall t. PropertyList t => ObjectCreationPropertyList t
ObjectCreationPropertyList, ObjectCreationPropertyList FCPL
ObjectCreationPropertyList FCPL => GroupCreationPropertyList FCPL
forall t.
ObjectCreationPropertyList t =>
GroupCreationPropertyList t
GroupCreationPropertyList)
instance PropertyList FCPL where
staticPlistClass :: Tagged FCPL PropertyListClassID
staticPlistClass = PropertyListClassID -> Tagged FCPL PropertyListClassID
forall {k} (s :: k) b. b -> Tagged s b
Tagged PropertyListClassID
fileCreate
class GroupCreationPropertyList t => FileCreationPropertyList t where
instance FileCreationPropertyList FCPL
setUserblock :: FileCreationPropertyList fcpl => fcpl -> HSize -> IO ()
setUserblock :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> HSize -> IO ()
setUserblock fcpl
fcpl HSize
sz =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> HSize_t -> IO HErr_t
h5p_set_userblock (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) (HSize -> HSize_t
hSize HSize
sz)
getUserblock :: FileCreationPropertyList fcpl => fcpl -> IO HSize
getUserblock :: forall fcpl. FileCreationPropertyList fcpl => fcpl -> IO HSize
getUserblock fcpl
fcpl =
(HSize_t -> HSize) -> IO HSize_t -> IO HSize
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HSize_t -> HSize
HSize (IO HSize_t -> IO HSize) -> IO HSize_t -> IO HSize
forall a b. (a -> b) -> a -> b
$
(Out HSize_t -> IO ()) -> IO HSize_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out HSize_t -> IO ()) -> IO HSize_t)
-> (Out HSize_t -> IO ()) -> IO HSize_t
forall a b. (a -> b) -> a -> b
$ \Out HSize_t
sz ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> Out HSize_t -> IO HErr_t
h5p_get_userblock (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) Out HSize_t
sz
setSizes :: FileCreationPropertyList fcpl => fcpl -> CSize -> CSize -> IO ()
setSizes :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> CSize -> CSize -> IO ()
setSizes fcpl
fcpl CSize
sizeof_addr CSize
sizeof_size =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CSize -> CSize -> IO HErr_t
h5p_set_sizes (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) CSize
sizeof_addr CSize
sizeof_size
getSizes :: FileCreationPropertyList fcpl => fcpl -> IO (CSize, CSize)
getSizes :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> IO (CSize, CSize)
getSizes fcpl
fcpl =
(Out CSize -> IO CSize) -> IO (CSize, CSize)
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m (a, b)
withOut ((Out CSize -> IO CSize) -> IO (CSize, CSize))
-> (Out CSize -> IO CSize) -> IO (CSize, CSize)
forall a b. (a -> b) -> a -> b
$ \Out CSize
sizeof_addr ->
(Out CSize -> IO ()) -> IO CSize
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out CSize -> IO ()) -> IO CSize)
-> (Out CSize -> IO ()) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Out CSize
sizeof_size ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> Out CSize -> Out CSize -> IO HErr_t
h5p_get_sizes (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) Out CSize
sizeof_addr Out CSize
sizeof_size
setSymK :: FileCreationPropertyList fcpl => fcpl -> Maybe CUInt -> Maybe CUInt -> IO ()
setSymK :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> Maybe CUInt -> Maybe CUInt -> IO ()
setSymK fcpl
fcpl Maybe CUInt
mbIK Maybe CUInt
mbLK =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CUInt -> CUInt -> IO HErr_t
h5p_set_sym_k (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) (CUInt -> Maybe CUInt -> CUInt
forall a. a -> Maybe a -> a
fromMaybe CUInt
0 Maybe CUInt
mbIK) (CUInt -> Maybe CUInt -> CUInt
forall a. a -> Maybe a -> a
fromMaybe CUInt
0 Maybe CUInt
mbLK)
getSymK :: FileCreationPropertyList fcpl => fcpl -> IO (CUInt, CUInt)
getSymK :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> IO (CUInt, CUInt)
getSymK fcpl
fcpl =
(Out CUInt -> IO CUInt) -> IO (CUInt, CUInt)
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m (a, b)
withOut ((Out CUInt -> IO CUInt) -> IO (CUInt, CUInt))
-> (Out CUInt -> IO CUInt) -> IO (CUInt, CUInt)
forall a b. (a -> b) -> a -> b
$ \Out CUInt
ik ->
(Out CUInt -> IO ()) -> IO CUInt
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out CUInt -> IO ()) -> IO CUInt)
-> (Out CUInt -> IO ()) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \Out CUInt
lk ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> Out CUInt -> Out CUInt -> IO HErr_t
h5p_get_sym_k (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) Out CUInt
ik Out CUInt
lk
setIstoreK :: FileCreationPropertyList fcpl => fcpl -> CUInt -> IO ()
setIstoreK :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> CUInt -> IO ()
setIstoreK fcpl
fcpl CUInt
ik =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CUInt -> IO HErr_t
h5p_set_istore_k (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) CUInt
ik
getIstoreK :: FileCreationPropertyList fcpl => fcpl -> IO CUInt
getIstoreK :: forall fcpl. FileCreationPropertyList fcpl => fcpl -> IO CUInt
getIstoreK fcpl
fcpl =
(Out CUInt -> IO ()) -> IO CUInt
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out CUInt -> IO ()) -> IO CUInt)
-> (Out CUInt -> IO ()) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \Out CUInt
ik ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> Out CUInt -> IO HErr_t
h5p_get_istore_k (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) Out CUInt
ik
setSharedMesgNIndexes :: FileCreationPropertyList fcpl => fcpl -> CUInt -> IO ()
setSharedMesgNIndexes :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> CUInt -> IO ()
setSharedMesgNIndexes fcpl
fcpl CUInt
nIndexes =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CUInt -> IO HErr_t
h5p_set_shared_mesg_nindexes (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) CUInt
nIndexes
getSharedMesgNIndexes :: FileCreationPropertyList fcpl => fcpl -> IO CUInt
getSharedMesgNIndexes :: forall fcpl. FileCreationPropertyList fcpl => fcpl -> IO CUInt
getSharedMesgNIndexes fcpl
fcpl =
(Out CUInt -> IO ()) -> IO CUInt
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out CUInt -> IO ()) -> IO CUInt)
-> (Out CUInt -> IO ()) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \Out CUInt
nIndexes ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> Out CUInt -> IO HErr_t
h5p_get_shared_mesg_nindexes (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) Out CUInt
nIndexes
setSharedMesgIndex :: FileCreationPropertyList fcpl => fcpl -> CUInt -> CUInt -> CUInt -> IO ()
setSharedMesgIndex :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> CUInt -> CUInt -> CUInt -> IO ()
setSharedMesgIndex fcpl
fcpl CUInt
indexNum CUInt
mesgTypeFlags CUInt
minMesgSize =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CUInt -> CUInt -> CUInt -> IO HErr_t
h5p_set_shared_mesg_index (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) CUInt
indexNum CUInt
mesgTypeFlags CUInt
minMesgSize
getSharedMesgIndex :: FileCreationPropertyList fcpl => fcpl -> CUInt -> IO (CUInt, CUInt)
getSharedMesgIndex :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> CUInt -> IO (CUInt, CUInt)
getSharedMesgIndex fcpl
fcpl CUInt
indexNum =
(Out CUInt -> IO CUInt) -> IO (CUInt, CUInt)
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m (a, b)
withOut ((Out CUInt -> IO CUInt) -> IO (CUInt, CUInt))
-> (Out CUInt -> IO CUInt) -> IO (CUInt, CUInt)
forall a b. (a -> b) -> a -> b
$ \Out CUInt
mesgTypeFlags ->
(Out CUInt -> IO ()) -> IO CUInt
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out CUInt -> IO ()) -> IO CUInt)
-> (Out CUInt -> IO ()) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \Out CUInt
minMesgSize ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CUInt -> Out CUInt -> Out CUInt -> IO HErr_t
h5p_get_shared_mesg_index (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) CUInt
indexNum Out CUInt
mesgTypeFlags Out CUInt
minMesgSize
setSharedMesgPhaseChange :: FileCreationPropertyList fcpl => fcpl -> CUInt -> CUInt -> IO ()
setSharedMesgPhaseChange :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> CUInt -> CUInt -> IO ()
setSharedMesgPhaseChange fcpl
fcpl CUInt
maxList CUInt
minBTree =
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CUInt -> CUInt -> IO HErr_t
h5p_set_shared_mesg_phase_change (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) CUInt
maxList CUInt
minBTree
getSharedMesgPhaseChange :: FileCreationPropertyList fcpl => fcpl -> IO (CUInt, CUInt)
getSharedMesgPhaseChange :: forall fcpl.
FileCreationPropertyList fcpl =>
fcpl -> IO (CUInt, CUInt)
getSharedMesgPhaseChange fcpl
fcpl =
(Out CUInt -> IO CUInt) -> IO (CUInt, CUInt)
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m (a, b)
withOut ((Out CUInt -> IO CUInt) -> IO (CUInt, CUInt))
-> (Out CUInt -> IO CUInt) -> IO (CUInt, CUInt)
forall a b. (a -> b) -> a -> b
$ \Out CUInt
maxList ->
(Out CUInt -> IO ()) -> IO CUInt
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out CUInt -> IO ()) -> IO CUInt)
-> (Out CUInt -> IO ()) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \Out CUInt
minBTree ->
IO HErr_t -> IO ()
forall t. HDFResultType t => IO t -> IO ()
withErrorCheck_ (IO HErr_t -> IO ()) -> IO HErr_t -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> Out CUInt -> Out CUInt -> IO HErr_t
h5p_get_shared_mesg_phase_change (fcpl -> HId_t
forall t. HId t => t -> HId_t
hid fcpl
fcpl) Out CUInt
maxList Out CUInt
minBTree