{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Bindings.HDF5.Object
( ObjectId
, Object(..)
, ObjectType(..)
, objectTypeOf
, objectTypeOf1
, uncheckedCastObject
, castObject
, openObject
, getObjectType
, linkObject
, closeObject
, copyObject
, doesObjectExist
) where
import Data.Maybe
import Bindings.HDF5.Core
import Bindings.HDF5.Error
import Bindings.HDF5.PropertyList.LAPL
import Bindings.HDF5.PropertyList.LCPL
import Bindings.HDF5.PropertyList.OCPYPL
import Bindings.HDF5.Raw.H5I
import Bindings.HDF5.Raw.H5O
import Bindings.HDF5.Raw.H5P
import qualified Data.ByteString as BS
import Foreign.Storable
newtype ObjectId = ObjectId HId_t
deriving (ObjectId -> ObjectId -> Bool
(ObjectId -> ObjectId -> Bool)
-> (ObjectId -> ObjectId -> Bool) -> Eq ObjectId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectId -> ObjectId -> Bool
== :: ObjectId -> ObjectId -> Bool
$c/= :: ObjectId -> ObjectId -> Bool
/= :: ObjectId -> ObjectId -> Bool
Eq, ObjectId -> HId_t
(ObjectId -> HId_t) -> HId ObjectId
forall t. (t -> HId_t) -> HId t
$chid :: ObjectId -> HId_t
hid :: ObjectId -> HId_t
HId, HId_t -> ObjectId
(HId_t -> ObjectId) -> FromHId ObjectId
forall t. (HId_t -> t) -> FromHId t
$cuncheckedFromHId :: HId_t -> ObjectId
uncheckedFromHId :: HId_t -> ObjectId
FromHId, ObjectId -> Bool
(ObjectId -> Bool) -> HDFResultType ObjectId
forall t. (t -> Bool) -> HDFResultType t
$cisError :: ObjectId -> Bool
isError :: ObjectId -> Bool
HDFResultType, Ptr ObjectId -> IO ObjectId
Ptr ObjectId -> Int -> IO ObjectId
Ptr ObjectId -> Int -> ObjectId -> IO ()
Ptr ObjectId -> ObjectId -> IO ()
ObjectId -> Int
(ObjectId -> Int)
-> (ObjectId -> Int)
-> (Ptr ObjectId -> Int -> IO ObjectId)
-> (Ptr ObjectId -> Int -> ObjectId -> IO ())
-> (forall b. Ptr b -> Int -> IO ObjectId)
-> (forall b. Ptr b -> Int -> ObjectId -> IO ())
-> (Ptr ObjectId -> IO ObjectId)
-> (Ptr ObjectId -> ObjectId -> IO ())
-> Storable ObjectId
forall b. Ptr b -> Int -> IO ObjectId
forall b. Ptr b -> Int -> ObjectId -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: ObjectId -> Int
sizeOf :: ObjectId -> Int
$calignment :: ObjectId -> Int
alignment :: ObjectId -> Int
$cpeekElemOff :: Ptr ObjectId -> Int -> IO ObjectId
peekElemOff :: Ptr ObjectId -> Int -> IO ObjectId
$cpokeElemOff :: Ptr ObjectId -> Int -> ObjectId -> IO ()
pokeElemOff :: Ptr ObjectId -> Int -> ObjectId -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ObjectId
peekByteOff :: forall b. Ptr b -> Int -> IO ObjectId
$cpokeByteOff :: forall b. Ptr b -> Int -> ObjectId -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> ObjectId -> IO ()
$cpeek :: Ptr ObjectId -> IO ObjectId
peek :: Ptr ObjectId -> IO ObjectId
$cpoke :: Ptr ObjectId -> ObjectId -> IO ()
poke :: Ptr ObjectId -> ObjectId -> IO ()
Storable)
class (HId t, FromHId t) => Object t where
staticObjectType :: Tagged t (Maybe ObjectType)
instance Object ObjectId where
staticObjectType :: Tagged ObjectId (Maybe ObjectType)
staticObjectType = Maybe ObjectType -> Tagged ObjectId (Maybe ObjectType)
forall {k} (s :: k) b. b -> Tagged s b
Tagged Maybe ObjectType
forall a. Maybe a
Nothing
objectTypeOf :: Object t => t -> Maybe ObjectType
objectTypeOf :: forall t. Object t => t -> Maybe ObjectType
objectTypeOf = Tagged t (Maybe ObjectType) -> t -> Maybe ObjectType
forall t a. Tagged t a -> t -> a
f Tagged t (Maybe ObjectType)
forall t. Object t => Tagged t (Maybe ObjectType)
staticObjectType
where
f :: Tagged t a -> t -> a
f :: forall t a. Tagged t a -> t -> a
f = a -> t -> a
forall a b. a -> b -> a
const (a -> t -> a) -> (Tagged t a -> a) -> Tagged t a -> t -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tagged t a -> a
forall {k} (s :: k) b. Tagged s b -> b
unTagged
objectTypeOf1 :: Object t => c t -> Maybe ObjectType
objectTypeOf1 :: forall t (c :: * -> *). Object t => c t -> Maybe ObjectType
objectTypeOf1 = Tagged t (Maybe ObjectType) -> c t -> Maybe ObjectType
forall t a (c :: * -> *). Tagged t a -> c t -> a
f Tagged t (Maybe ObjectType)
forall t. Object t => Tagged t (Maybe ObjectType)
staticObjectType
where
f :: Tagged t a -> c t -> a
f :: forall t a (c :: * -> *). Tagged t a -> c t -> a
f = a -> c t -> a
forall a b. a -> b -> a
const (a -> c t -> a) -> (Tagged t a -> a) -> Tagged t a -> c t -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tagged t a -> a
forall {k} (s :: k) b. Tagged s b -> b
unTagged
uncheckedCastObject :: (Object a, Object b) => a -> b
uncheckedCastObject :: forall a b. (Object a, Object b) => a -> b
uncheckedCastObject = HId_t -> b
forall t. FromHId t => HId_t -> t
uncheckedFromHId (HId_t -> b) -> (a -> HId_t) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> HId_t
forall t. HId t => t -> HId_t
hid
castObject :: (Object src, Object dst) => src -> IO (Maybe dst)
castObject :: forall src dst. (Object src, Object dst) => src -> IO (Maybe dst)
castObject = Tagged dst (Maybe ObjectType) -> src -> IO (Maybe dst)
forall a b.
(Object a, Object b) =>
Tagged b (Maybe ObjectType) -> a -> IO (Maybe b)
castTo Tagged dst (Maybe ObjectType)
forall t. Object t => Tagged t (Maybe ObjectType)
staticObjectType
where
castTo :: (Object a, Object b) => Tagged b (Maybe ObjectType) -> a -> IO (Maybe b)
castTo :: forall a b.
(Object a, Object b) =>
Tagged b (Maybe ObjectType) -> a -> IO (Maybe b)
castTo (Tagged Maybe ObjectType
Nothing) a
src = Maybe b -> IO (Maybe b)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b
forall a. a -> Maybe a
Just (a -> b
forall a b. (Object a, Object b) => a -> b
uncheckedCastObject a
src))
castTo (Tagged (Just ObjectType
dstType)) a
src = do
ObjectType
srcType <- a -> IO ObjectType
forall obj. Object obj => obj -> IO ObjectType
getObjectType a
src
Maybe b -> IO (Maybe b)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe b -> IO (Maybe b)) -> Maybe b -> IO (Maybe b)
forall a b. (a -> b) -> a -> b
$! if ObjectType
srcType ObjectType -> ObjectType -> Bool
forall a. Eq a => a -> a -> Bool
== ObjectType
dstType
then b -> Maybe b
forall a. a -> Maybe a
Just (a -> b
forall a b. (Object a, Object b) => a -> b
uncheckedCastObject a
src)
else Maybe b
forall a. Maybe a
Nothing
openObject :: Location loc => loc -> BS.ByteString -> Maybe LAPL -> IO ObjectId
openObject :: forall loc.
Location loc =>
loc -> ByteString -> Maybe LAPL -> IO ObjectId
openObject loc
loc ByteString
name Maybe LAPL
lapl =
(HId_t -> ObjectId) -> IO HId_t -> IO ObjectId
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HId_t -> ObjectId
ObjectId (IO HId_t -> IO ObjectId) -> IO HId_t -> IO ObjectId
forall a b. (a -> b) -> a -> b
$
ByteString -> (CString -> IO HId_t) -> IO HId_t
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString ByteString
name ((CString -> IO HId_t) -> IO HId_t)
-> (CString -> IO HId_t) -> IO HId_t
forall a b. (a -> b) -> a -> b
$ \CString
cname ->
IO HId_t -> IO HId_t
forall t. HDFResultType t => IO t -> IO t
withErrorCheck (IO HId_t -> IO HId_t) -> IO HId_t -> IO HId_t
forall a b. (a -> b) -> a -> b
$
HId_t -> CString -> HId_t -> IO HId_t
h5o_open (loc -> HId_t
forall t. HId t => t -> HId_t
hid loc
loc) CString
cname (HId_t -> (LAPL -> HId_t) -> Maybe LAPL -> HId_t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HId_t
h5p_DEFAULT LAPL -> HId_t
forall t. HId t => t -> HId_t
hid Maybe LAPL
lapl)
data ObjectType
= FileObj
| GroupObj
| DatatypeObj
| DataspaceObj
| DatasetObj
| AttrObj
deriving (ObjectType -> ObjectType -> Bool
(ObjectType -> ObjectType -> Bool)
-> (ObjectType -> ObjectType -> Bool) -> Eq ObjectType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectType -> ObjectType -> Bool
== :: ObjectType -> ObjectType -> Bool
$c/= :: ObjectType -> ObjectType -> Bool
/= :: ObjectType -> ObjectType -> Bool
Eq, Eq ObjectType
Eq ObjectType =>
(ObjectType -> ObjectType -> Ordering)
-> (ObjectType -> ObjectType -> Bool)
-> (ObjectType -> ObjectType -> Bool)
-> (ObjectType -> ObjectType -> Bool)
-> (ObjectType -> ObjectType -> Bool)
-> (ObjectType -> ObjectType -> ObjectType)
-> (ObjectType -> ObjectType -> ObjectType)
-> Ord ObjectType
ObjectType -> ObjectType -> Bool
ObjectType -> ObjectType -> Ordering
ObjectType -> ObjectType -> ObjectType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectType -> ObjectType -> Ordering
compare :: ObjectType -> ObjectType -> Ordering
$c< :: ObjectType -> ObjectType -> Bool
< :: ObjectType -> ObjectType -> Bool
$c<= :: ObjectType -> ObjectType -> Bool
<= :: ObjectType -> ObjectType -> Bool
$c> :: ObjectType -> ObjectType -> Bool
> :: ObjectType -> ObjectType -> Bool
$c>= :: ObjectType -> ObjectType -> Bool
>= :: ObjectType -> ObjectType -> Bool
$cmax :: ObjectType -> ObjectType -> ObjectType
max :: ObjectType -> ObjectType -> ObjectType
$cmin :: ObjectType -> ObjectType -> ObjectType
min :: ObjectType -> ObjectType -> ObjectType
Ord, ReadPrec [ObjectType]
ReadPrec ObjectType
Int -> ReadS ObjectType
ReadS [ObjectType]
(Int -> ReadS ObjectType)
-> ReadS [ObjectType]
-> ReadPrec ObjectType
-> ReadPrec [ObjectType]
-> Read ObjectType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectType
readsPrec :: Int -> ReadS ObjectType
$creadList :: ReadS [ObjectType]
readList :: ReadS [ObjectType]
$creadPrec :: ReadPrec ObjectType
readPrec :: ReadPrec ObjectType
$creadListPrec :: ReadPrec [ObjectType]
readListPrec :: ReadPrec [ObjectType]
Read, Int -> ObjectType -> ShowS
[ObjectType] -> ShowS
ObjectType -> String
(Int -> ObjectType -> ShowS)
-> (ObjectType -> String)
-> ([ObjectType] -> ShowS)
-> Show ObjectType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectType -> ShowS
showsPrec :: Int -> ObjectType -> ShowS
$cshow :: ObjectType -> String
show :: ObjectType -> String
$cshowList :: [ObjectType] -> ShowS
showList :: [ObjectType] -> ShowS
Show, Int -> ObjectType
ObjectType -> Int
ObjectType -> [ObjectType]
ObjectType -> ObjectType
ObjectType -> ObjectType -> [ObjectType]
ObjectType -> ObjectType -> ObjectType -> [ObjectType]
(ObjectType -> ObjectType)
-> (ObjectType -> ObjectType)
-> (Int -> ObjectType)
-> (ObjectType -> Int)
-> (ObjectType -> [ObjectType])
-> (ObjectType -> ObjectType -> [ObjectType])
-> (ObjectType -> ObjectType -> [ObjectType])
-> (ObjectType -> ObjectType -> ObjectType -> [ObjectType])
-> Enum ObjectType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ObjectType -> ObjectType
succ :: ObjectType -> ObjectType
$cpred :: ObjectType -> ObjectType
pred :: ObjectType -> ObjectType
$ctoEnum :: Int -> ObjectType
toEnum :: Int -> ObjectType
$cfromEnum :: ObjectType -> Int
fromEnum :: ObjectType -> Int
$cenumFrom :: ObjectType -> [ObjectType]
enumFrom :: ObjectType -> [ObjectType]
$cenumFromThen :: ObjectType -> ObjectType -> [ObjectType]
enumFromThen :: ObjectType -> ObjectType -> [ObjectType]
$cenumFromTo :: ObjectType -> ObjectType -> [ObjectType]
enumFromTo :: ObjectType -> ObjectType -> [ObjectType]
$cenumFromThenTo :: ObjectType -> ObjectType -> ObjectType -> [ObjectType]
enumFromThenTo :: ObjectType -> ObjectType -> ObjectType -> [ObjectType]
Enum, ObjectType
ObjectType -> ObjectType -> Bounded ObjectType
forall a. a -> a -> Bounded a
$cminBound :: ObjectType
minBound :: ObjectType
$cmaxBound :: ObjectType
maxBound :: ObjectType
Bounded)
objectTypeCode :: ObjectType -> H5I_type_t
objectTypeCode :: ObjectType -> H5I_type_t
objectTypeCode ObjectType
FileObj = H5I_type_t
h5i_FILE
objectTypeCode ObjectType
GroupObj = H5I_type_t
h5i_GROUP
objectTypeCode ObjectType
DatatypeObj = H5I_type_t
h5i_DATATYPE
objectTypeCode ObjectType
DataspaceObj = H5I_type_t
h5i_DATASPACE
objectTypeCode ObjectType
DatasetObj = H5I_type_t
h5i_DATASET
objectTypeCode ObjectType
AttrObj = H5I_type_t
h5i_ATTR
objectTypeFromCode :: H5I_type_t -> ObjectType
objectTypeFromCode :: H5I_type_t -> ObjectType
objectTypeFromCode H5I_type_t
c =
ObjectType -> Maybe ObjectType -> ObjectType
forall a. a -> Maybe a -> a
fromMaybe (String -> ObjectType
forall a. HasCallStack => String -> a
error (String
"Unknown object type code: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5I_type_t -> String
forall a. Show a => a -> String
show H5I_type_t
c))
(H5I_type_t -> [(H5I_type_t, ObjectType)] -> Maybe ObjectType
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup H5I_type_t
c [(H5I_type_t, ObjectType)]
codes)
where
codes :: [(H5I_type_t, ObjectType)]
codes = [ (ObjectType -> H5I_type_t
objectTypeCode ObjectType
x, ObjectType
x) | ObjectType
x <- [ObjectType
forall a. Bounded a => a
minBound .. ObjectType
forall a. Bounded a => a
maxBound]]
getObjectType :: Object obj => obj -> IO ObjectType
getObjectType :: forall obj. Object obj => obj -> IO ObjectType
getObjectType obj
obj =
(H5I_type_t -> ObjectType) -> IO H5I_type_t -> IO ObjectType
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap H5I_type_t -> ObjectType
objectTypeFromCode (IO H5I_type_t -> IO ObjectType) -> IO H5I_type_t -> IO ObjectType
forall a b. (a -> b) -> a -> b
$
IO H5I_type_t -> IO H5I_type_t
forall t. HDFResultType t => IO t -> IO t
withErrorCheck (IO H5I_type_t -> IO H5I_type_t) -> IO H5I_type_t -> IO H5I_type_t
forall a b. (a -> b) -> a -> b
$
HId_t -> IO H5I_type_t
h5i_get_type (obj -> HId_t
forall t. HId t => t -> HId_t
hid obj
obj)
linkObject :: (Object obj, Location loc) => obj -> loc -> BS.ByteString -> Maybe LCPL -> Maybe LAPL -> IO ()
linkObject :: forall obj loc.
(Object obj, Location loc) =>
obj -> loc -> ByteString -> Maybe LCPL -> Maybe LAPL -> IO ()
linkObject obj
obj loc
loc ByteString
name Maybe LCPL
lcpl Maybe LAPL
lapl =
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
$
ByteString -> (CString -> IO HErr_t) -> IO HErr_t
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString ByteString
name ((CString -> IO HErr_t) -> IO HErr_t)
-> (CString -> IO HErr_t) -> IO HErr_t
forall a b. (a -> b) -> a -> b
$ \CString
cname ->
HId_t -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
h5o_link (obj -> HId_t
forall t. HId t => t -> HId_t
hid obj
obj) (loc -> HId_t
forall t. HId t => t -> HId_t
hid loc
loc) CString
cname (HId_t -> (LCPL -> HId_t) -> Maybe LCPL -> HId_t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HId_t
h5p_DEFAULT LCPL -> HId_t
forall t. HId t => t -> HId_t
hid Maybe LCPL
lcpl) (HId_t -> (LAPL -> HId_t) -> Maybe LAPL -> HId_t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HId_t
h5p_DEFAULT LAPL -> HId_t
forall t. HId t => t -> HId_t
hid Maybe LAPL
lapl)
closeObject :: Object obj => obj -> IO ()
closeObject :: forall obj. Object obj => obj -> IO ()
closeObject obj
obj =
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 -> IO HErr_t
h5o_close (obj -> HId_t
forall t. HId t => t -> HId_t
hid obj
obj)
copyObject :: (Location src, Location dst) => src -> BS.ByteString -> dst -> BS.ByteString -> Maybe OCPYPL -> Maybe LCPL -> IO ()
copyObject :: forall src dst.
(Location src, Location dst) =>
src
-> ByteString
-> dst
-> ByteString
-> Maybe OCPYPL
-> Maybe LCPL
-> IO ()
copyObject src
src ByteString
srcName dst
dst ByteString
dstName Maybe OCPYPL
ocpypl Maybe LCPL
lcpl =
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
$
ByteString -> (CString -> IO HErr_t) -> IO HErr_t
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString ByteString
srcName ((CString -> IO HErr_t) -> IO HErr_t)
-> (CString -> IO HErr_t) -> IO HErr_t
forall a b. (a -> b) -> a -> b
$ \CString
csrcName ->
ByteString -> (CString -> IO HErr_t) -> IO HErr_t
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString ByteString
dstName ((CString -> IO HErr_t) -> IO HErr_t)
-> (CString -> IO HErr_t) -> IO HErr_t
forall a b. (a -> b) -> a -> b
$ \CString
cdstName ->
HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
h5o_copy (src -> HId_t
forall t. HId t => t -> HId_t
hid src
src) CString
csrcName (dst -> HId_t
forall t. HId t => t -> HId_t
hid dst
dst) CString
cdstName
(HId_t -> (OCPYPL -> HId_t) -> Maybe OCPYPL -> HId_t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HId_t
h5p_DEFAULT OCPYPL -> HId_t
forall t. HId t => t -> HId_t
hid Maybe OCPYPL
ocpypl)
(HId_t -> (LCPL -> HId_t) -> Maybe LCPL -> HId_t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HId_t
h5p_DEFAULT LCPL -> HId_t
forall t. HId t => t -> HId_t
hid Maybe LCPL
lcpl)
doesObjectExist :: Location loc => loc -> BS.ByteString -> Maybe LAPL -> IO Bool
doesObjectExist :: forall loc.
Location loc =>
loc -> ByteString -> Maybe LAPL -> IO Bool
doesObjectExist loc
loc ByteString
name Maybe LAPL
lapl =
IO HTri_t -> IO Bool
htriToBool (IO HTri_t -> IO Bool) -> IO HTri_t -> IO Bool
forall a b. (a -> b) -> a -> b
$
ByteString -> (CString -> IO HTri_t) -> IO HTri_t
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString ByteString
name ((CString -> IO HTri_t) -> IO HTri_t)
-> (CString -> IO HTri_t) -> IO HTri_t
forall a b. (a -> b) -> a -> b
$ \CString
cname ->
HId_t -> CString -> HId_t -> IO HTri_t
h5o_exists_by_name (loc -> HId_t
forall t. HId t => t -> HId_t
hid loc
loc) CString
cname (HId_t -> (LAPL -> HId_t) -> Maybe LAPL -> HId_t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HId_t
h5p_DEFAULT LAPL -> HId_t
forall t. HId t => t -> HId_t
hid Maybe LAPL
lapl)