{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Bindings.HDF5.PropertyList.LCPL
( module Bindings.HDF5.PropertyList.STRCPL
, LCPL
, LinkCreationPropertyList
) where
import Bindings.HDF5.Core
import Bindings.HDF5.PropertyList.STRCPL
class StringCreationPropertyList t => LinkCreationPropertyList t where
newtype LCPL = LCPL STRCPL
deriving (LCPL -> LCPL -> Bool
(LCPL -> LCPL -> Bool) -> (LCPL -> LCPL -> Bool) -> Eq LCPL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LCPL -> LCPL -> Bool
== :: LCPL -> LCPL -> Bool
$c/= :: LCPL -> LCPL -> Bool
/= :: LCPL -> LCPL -> Bool
Eq, LCPL -> HId_t
(LCPL -> HId_t) -> HId LCPL
forall t. (t -> HId_t) -> HId t
$chid :: LCPL -> HId_t
hid :: LCPL -> HId_t
HId, HId_t -> LCPL
(HId_t -> LCPL) -> FromHId LCPL
forall t. (HId_t -> t) -> FromHId t
$cuncheckedFromHId :: HId_t -> LCPL
uncheckedFromHId :: HId_t -> LCPL
FromHId, LCPL -> Bool
(LCPL -> Bool) -> HDFResultType LCPL
forall t. (t -> Bool) -> HDFResultType t
$cisError :: LCPL -> Bool
isError :: LCPL -> Bool
HDFResultType, FromHId LCPL
HId LCPL
(HId LCPL, FromHId LCPL) => PropertyListOrClass LCPL
forall t. (HId t, FromHId t) => PropertyListOrClass t
PropertyListOrClass, PropertyList LCPL
PropertyList LCPL => StringCreationPropertyList LCPL
forall t. PropertyList t => StringCreationPropertyList t
StringCreationPropertyList)
instance PropertyList LCPL where
staticPlistClass :: Tagged LCPL PropertyListClassID
staticPlistClass = PropertyListClassID -> Tagged LCPL PropertyListClassID
forall {k} (s :: k) b. b -> Tagged s b
Tagged PropertyListClassID
linkCreate
instance LinkCreationPropertyList LCPL