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