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