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