{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Bindings.HDF5.PropertyList.DCPL
( module Bindings.HDF5.PropertyList.OCPL
, DCPL
, DatasetCreationPropertyList
, Layout(..)
, setLayout
, getLayout
, setChunk
, getChunk
, setExternal
, getExternalCount
, getExternalN
, getExternal
, setSZip
, setShuffle
, setNBit
, ScaleType(..)
, setScaleOffset
, setFillValue
, getFillValue
, FillValueDefaultType(..)
, fillValueDefined
, AllocTime(..)
, setAllocTime
, getAllocTime
, FillTime(..)
, setFillTime
, getFillTime
) where
import Bindings.HDF5.Core
import Bindings.HDF5.Error
import Bindings.HDF5.PropertyList
import Bindings.HDF5.PropertyList.OCPL
import Bindings.HDF5.Datatype.Internal
import Bindings.HDF5.Raw.H5D
import Bindings.HDF5.Raw.H5P
import Bindings.HDF5.Raw.H5Z
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as BS
import Data.List
import Foreign
import Foreign.C
import Foreign.Ptr.Conventions
import System.Posix.Types
newtype DCPL = DCPL OCPL
deriving (DCPL -> DCPL -> Bool
(DCPL -> DCPL -> Bool) -> (DCPL -> DCPL -> Bool) -> Eq DCPL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DCPL -> DCPL -> Bool
== :: DCPL -> DCPL -> Bool
$c/= :: DCPL -> DCPL -> Bool
/= :: DCPL -> DCPL -> Bool
Eq, DCPL -> HId_t
(DCPL -> HId_t) -> HId DCPL
forall t. (t -> HId_t) -> HId t
$chid :: DCPL -> HId_t
hid :: DCPL -> HId_t
HId, HId_t -> DCPL
(HId_t -> DCPL) -> FromHId DCPL
forall t. (HId_t -> t) -> FromHId t
$cuncheckedFromHId :: HId_t -> DCPL
uncheckedFromHId :: HId_t -> DCPL
FromHId, DCPL -> Bool
(DCPL -> Bool) -> HDFResultType DCPL
forall t. (t -> Bool) -> HDFResultType t
$cisError :: DCPL -> Bool
isError :: DCPL -> Bool
HDFResultType, FromHId DCPL
HId DCPL
(HId DCPL, FromHId DCPL) => PropertyListOrClass DCPL
forall t. (HId t, FromHId t) => PropertyListOrClass t
PropertyListOrClass, PropertyList DCPL
PropertyList DCPL => ObjectCreationPropertyList DCPL
forall t. PropertyList t => ObjectCreationPropertyList t
ObjectCreationPropertyList)
instance PropertyList DCPL where
staticPlistClass :: Tagged DCPL PropertyListClassID
staticPlistClass = PropertyListClassID -> Tagged DCPL PropertyListClassID
forall {k} (s :: k) b. b -> Tagged s b
Tagged PropertyListClassID
datasetCreate
class ObjectCreationPropertyList t => DatasetCreationPropertyList t where
instance DatasetCreationPropertyList DCPL
data Layout
= CompactLayout
| ContiguousLayout
| ChunkedLayout
deriving (Layout -> Layout -> Bool
(Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool) -> Eq Layout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Layout -> Layout -> Bool
== :: Layout -> Layout -> Bool
$c/= :: Layout -> Layout -> Bool
/= :: Layout -> Layout -> Bool
Eq, Eq Layout
Eq Layout =>
(Layout -> Layout -> Ordering)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Layout)
-> (Layout -> Layout -> Layout)
-> Ord Layout
Layout -> Layout -> Bool
Layout -> Layout -> Ordering
Layout -> Layout -> Layout
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 :: Layout -> Layout -> Ordering
compare :: Layout -> Layout -> Ordering
$c< :: Layout -> Layout -> Bool
< :: Layout -> Layout -> Bool
$c<= :: Layout -> Layout -> Bool
<= :: Layout -> Layout -> Bool
$c> :: Layout -> Layout -> Bool
> :: Layout -> Layout -> Bool
$c>= :: Layout -> Layout -> Bool
>= :: Layout -> Layout -> Bool
$cmax :: Layout -> Layout -> Layout
max :: Layout -> Layout -> Layout
$cmin :: Layout -> Layout -> Layout
min :: Layout -> Layout -> Layout
Ord, Layout
Layout -> Layout -> Bounded Layout
forall a. a -> a -> Bounded a
$cminBound :: Layout
minBound :: Layout
$cmaxBound :: Layout
maxBound :: Layout
Bounded, Int -> Layout
Layout -> Int
Layout -> [Layout]
Layout -> Layout
Layout -> Layout -> [Layout]
Layout -> Layout -> Layout -> [Layout]
(Layout -> Layout)
-> (Layout -> Layout)
-> (Int -> Layout)
-> (Layout -> Int)
-> (Layout -> [Layout])
-> (Layout -> Layout -> [Layout])
-> (Layout -> Layout -> [Layout])
-> (Layout -> Layout -> Layout -> [Layout])
-> Enum Layout
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 :: Layout -> Layout
succ :: Layout -> Layout
$cpred :: Layout -> Layout
pred :: Layout -> Layout
$ctoEnum :: Int -> Layout
toEnum :: Int -> Layout
$cfromEnum :: Layout -> Int
fromEnum :: Layout -> Int
$cenumFrom :: Layout -> [Layout]
enumFrom :: Layout -> [Layout]
$cenumFromThen :: Layout -> Layout -> [Layout]
enumFromThen :: Layout -> Layout -> [Layout]
$cenumFromTo :: Layout -> Layout -> [Layout]
enumFromTo :: Layout -> Layout -> [Layout]
$cenumFromThenTo :: Layout -> Layout -> Layout -> [Layout]
enumFromThenTo :: Layout -> Layout -> Layout -> [Layout]
Enum, ReadPrec [Layout]
ReadPrec Layout
Int -> ReadS Layout
ReadS [Layout]
(Int -> ReadS Layout)
-> ReadS [Layout]
-> ReadPrec Layout
-> ReadPrec [Layout]
-> Read Layout
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Layout
readsPrec :: Int -> ReadS Layout
$creadList :: ReadS [Layout]
readList :: ReadS [Layout]
$creadPrec :: ReadPrec Layout
readPrec :: ReadPrec Layout
$creadListPrec :: ReadPrec [Layout]
readListPrec :: ReadPrec [Layout]
Read, Int -> Layout -> ShowS
[Layout] -> ShowS
Layout -> String
(Int -> Layout -> ShowS)
-> (Layout -> String) -> ([Layout] -> ShowS) -> Show Layout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Layout -> ShowS
showsPrec :: Int -> Layout -> ShowS
$cshow :: Layout -> String
show :: Layout -> String
$cshowList :: [Layout] -> ShowS
showList :: [Layout] -> ShowS
Show)
layoutCode :: Layout -> H5D_layout_t
layoutCode :: Layout -> H5D_layout_t
layoutCode Layout
CompactLayout = H5D_layout_t
h5d_COMPACT
layoutCode Layout
ContiguousLayout = H5D_layout_t
h5d_CONTIGUOUS
layoutCode Layout
ChunkedLayout = H5D_layout_t
h5d_CHUNKED
layout :: H5D_layout_t -> Layout
layout :: H5D_layout_t -> Layout
layout H5D_layout_t
c
| H5D_layout_t
c H5D_layout_t -> H5D_layout_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_layout_t
h5d_COMPACT = Layout
CompactLayout
| H5D_layout_t
c H5D_layout_t -> H5D_layout_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_layout_t
h5d_CONTIGUOUS = Layout
ContiguousLayout
| H5D_layout_t
c H5D_layout_t -> H5D_layout_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_layout_t
h5d_CHUNKED = Layout
ChunkedLayout
| Bool
otherwise = String -> Layout
forall a. HasCallStack => String -> a
error (String
"unknown H5D_layout_t: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5D_layout_t -> String
forall a. Show a => a -> String
show H5D_layout_t
c)
setLayout :: DatasetCreationPropertyList t => t -> Layout -> IO ()
setLayout :: forall t. DatasetCreationPropertyList t => t -> Layout -> IO ()
setLayout t
plist Layout
l =
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 -> H5D_layout_t -> IO HErr_t
h5p_set_layout (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) (Layout -> H5D_layout_t
layoutCode Layout
l)
getLayout :: DatasetCreationPropertyList t => t -> IO Layout
getLayout :: forall t. DatasetCreationPropertyList t => t -> IO Layout
getLayout t
plist =
(H5D_layout_t -> Layout) -> IO H5D_layout_t -> IO Layout
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap H5D_layout_t -> Layout
layout (IO H5D_layout_t -> IO Layout) -> IO H5D_layout_t -> IO Layout
forall a b. (a -> b) -> a -> b
$
(H5D_layout_t -> Bool) -> IO H5D_layout_t -> IO H5D_layout_t
forall t. (t -> Bool) -> IO t -> IO t
withErrorWhen (\(H5D_layout_t Int32
c) -> Int32
c Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
< Int32
0) (IO H5D_layout_t -> IO H5D_layout_t)
-> IO H5D_layout_t -> IO H5D_layout_t
forall a b. (a -> b) -> a -> b
$
HId_t -> IO H5D_layout_t
h5p_get_layout (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist)
setChunk :: DatasetCreationPropertyList t => t -> [HSize] -> IO ()
setChunk :: forall t. DatasetCreationPropertyList t => t -> [HSize] -> IO ()
setChunk t
plist [HSize]
chunkSizes =
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
$
[HSize_t] -> (InArray HSize_t -> IO HErr_t) -> IO HErr_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m) =>
[a] -> (InArray a -> m b) -> m b
withInList ((HSize -> HSize_t) -> [HSize] -> [HSize_t]
forall a b. (a -> b) -> [a] -> [b]
map HSize -> HSize_t
hSize [HSize]
chunkSizes) ((InArray HSize_t -> IO HErr_t) -> IO HErr_t)
-> (InArray HSize_t -> IO HErr_t) -> IO HErr_t
forall a b. (a -> b) -> a -> b
$ \InArray HSize_t
cchunkSizes ->
HId_t -> CInt -> InArray HSize_t -> IO HErr_t
h5p_set_chunk (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) CInt
n InArray HSize_t
cchunkSizes
where n :: CInt
n = [HSize] -> CInt
forall i a. Num i => [a] -> i
genericLength [HSize]
chunkSizes
getChunk :: DatasetCreationPropertyList t => t -> IO [HSize]
getChunk :: forall t. DatasetCreationPropertyList t => t -> IO [HSize]
getChunk t
plist = do
CInt
n <- (CInt -> Bool) -> IO CInt -> IO CInt
forall t. (t -> Bool) -> IO t -> IO t
withErrorWhen (CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0) (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$
HId_t -> CInt -> OutArray HSize_t -> IO CInt
h5p_get_chunk (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) CInt
0 (Ptr HSize_t -> OutArray HSize_t
forall a. Ptr a -> OutArray a
OutArray Ptr HSize_t
forall a. Ptr a
nullPtr)
([HSize_t] -> [HSize]) -> IO [HSize_t] -> IO [HSize]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((HSize_t -> HSize) -> [HSize_t] -> [HSize]
forall a b. (a -> b) -> [a] -> [b]
map HSize_t -> HSize
HSize) (IO [HSize_t] -> IO [HSize]) -> IO [HSize_t] -> IO [HSize]
forall a b. (a -> b) -> a -> b
$
Int -> (OutArray HSize_t -> IO ()) -> IO [HSize_t]
forall a (m :: * -> *) b.
(Storable a, MonadIO m) =>
Int -> (OutArray a -> m b) -> m [a]
withOutList_ (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
n) ((OutArray HSize_t -> IO ()) -> IO [HSize_t])
-> (OutArray HSize_t -> IO ()) -> IO [HSize_t]
forall a b. (a -> b) -> a -> b
$ \OutArray HSize_t
buf ->
(CInt -> Bool) -> IO CInt -> IO ()
forall t. (t -> Bool) -> IO t -> IO ()
withErrorWhen_ (CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0) (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
HId_t -> CInt -> OutArray HSize_t -> IO CInt
h5p_get_chunk (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) CInt
n OutArray HSize_t
buf
setExternal :: DatasetCreationPropertyList t => t -> BS.ByteString -> COff -> HSize -> IO ()
setExternal :: forall t.
DatasetCreationPropertyList t =>
t -> ByteString -> COff -> HSize -> IO ()
setExternal t
plist ByteString
name COff
offset HSize
size =
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 -> CString -> COff -> HSize_t -> IO HErr_t
h5p_set_external (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) CString
cname COff
offset (HSize -> HSize_t
hSize HSize
size)
getExternalCount :: DatasetCreationPropertyList t => t -> IO CInt
getExternalCount :: forall t. DatasetCreationPropertyList t => t -> IO CInt
getExternalCount t
plist =
(CInt -> Bool) -> IO CInt -> IO CInt
forall t. (t -> Bool) -> IO t -> IO t
withErrorWhen (CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0) (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$
HId_t -> IO CInt
h5p_get_external_count (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist)
getExternalN :: DatasetCreationPropertyList t => t -> CUInt -> CSize -> IO (BS.ByteString, COff, HSize)
getExternalN :: forall t.
DatasetCreationPropertyList t =>
t -> CUInt -> CSize -> IO (ByteString, COff, HSize)
getExternalN t
plist CUInt
idx CSize
name_size = do
let sz :: Int
sz = CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
name_size
CString
name1 <- Int -> IO CString
forall a. Int -> IO (Ptr a)
mallocBytes Int
sz
(COff
offset, HSize_t
size) <-
(Out COff -> IO HSize_t) -> IO (COff, HSize_t)
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m (a, b)
withOut ((Out COff -> IO HSize_t) -> IO (COff, HSize_t))
-> (Out COff -> IO HSize_t) -> IO (COff, HSize_t)
forall a b. (a -> b) -> a -> b
$ \Out COff
offset ->
(Out HSize_t -> IO ()) -> IO HSize_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out HSize_t -> IO ()) -> IO HSize_t)
-> (Out HSize_t -> IO ()) -> IO HSize_t
forall a b. (a -> b) -> a -> b
$ \Out HSize_t
size ->
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
-> CUInt
-> CSize
-> OutArray CChar
-> Out COff
-> Out HSize_t
-> IO HErr_t
h5p_get_external (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) CUInt
idx CSize
name_size (CString -> OutArray CChar
forall a. Ptr a -> OutArray a
OutArray CString
name1) Out COff
offset Out HSize_t
size
ByteString
name2 <- CStringLen -> IO ByteString
BS.unsafePackCStringLen (CString
name1, Int
sz)
(ByteString, COff, HSize) -> IO (ByteString, COff, HSize)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word8 -> Bool) -> ByteString -> ByteString
BS.takeWhile (Word8
0 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/=) ByteString
name2, COff
offset, HSize_t -> HSize
HSize HSize_t
size)
getExternal :: DatasetCreationPropertyList t => t -> CUInt -> IO (BS.ByteString, COff, HSize)
getExternal :: forall t.
DatasetCreationPropertyList t =>
t -> CUInt -> IO (ByteString, COff, HSize)
getExternal t
plist CUInt
idx = CSize -> IO (ByteString, COff, HSize)
loop CSize
255
where
loop :: CSize -> IO (ByteString, COff, HSize)
loop CSize
sz = do
result :: (ByteString, COff, HSize)
result@(ByteString
name, COff
_, HSize
_) <- t -> CUInt -> CSize -> IO (ByteString, COff, HSize)
forall t.
DatasetCreationPropertyList t =>
t -> CUInt -> CSize -> IO (ByteString, COff, HSize)
getExternalN t
plist CUInt
idx CSize
sz
if ByteString -> Int
BS.length ByteString
name Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
sz
then (ByteString, COff, HSize) -> IO (ByteString, COff, HSize)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString, COff, HSize)
result
else do
let sz' :: CSize
sz' = CSize
2CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
*CSize
sz CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
+ CSize
1
if CSize
sz' CSize -> CSize -> Bool
forall a. Ord a => a -> a -> Bool
> CSize
sz
then CSize -> IO (ByteString, COff, HSize)
loop CSize
sz'
else String -> IO (ByteString, COff, HSize)
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"getExternal: name_size overflow, this is almost certainly a programming error in getExternal"
setSZip :: DatasetCreationPropertyList t => t -> CUInt -> CUInt -> IO ()
setSZip :: forall t.
DatasetCreationPropertyList t =>
t -> CUInt -> CUInt -> IO ()
setSZip t
plist CUInt
options_mask CUInt
pixels_per_block =
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 -> CUInt -> CUInt -> IO HErr_t
h5p_set_szip (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) CUInt
options_mask CUInt
pixels_per_block
setShuffle :: DatasetCreationPropertyList t => t -> IO ()
setShuffle :: forall t. DatasetCreationPropertyList t => t -> IO ()
setShuffle t
plist =
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
h5p_set_shuffle (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist)
setNBit :: DatasetCreationPropertyList t => t -> IO ()
setNBit :: forall t. DatasetCreationPropertyList t => t -> IO ()
setNBit t
plist =
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
h5p_set_nbit (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist)
data ScaleType
= FloatDScale
| FloatEScale
| IntScale
deriving (ScaleType -> ScaleType -> Bool
(ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool) -> Eq ScaleType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScaleType -> ScaleType -> Bool
== :: ScaleType -> ScaleType -> Bool
$c/= :: ScaleType -> ScaleType -> Bool
/= :: ScaleType -> ScaleType -> Bool
Eq, Eq ScaleType
Eq ScaleType =>
(ScaleType -> ScaleType -> Ordering)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> ScaleType)
-> (ScaleType -> ScaleType -> ScaleType)
-> Ord ScaleType
ScaleType -> ScaleType -> Bool
ScaleType -> ScaleType -> Ordering
ScaleType -> ScaleType -> ScaleType
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 :: ScaleType -> ScaleType -> Ordering
compare :: ScaleType -> ScaleType -> Ordering
$c< :: ScaleType -> ScaleType -> Bool
< :: ScaleType -> ScaleType -> Bool
$c<= :: ScaleType -> ScaleType -> Bool
<= :: ScaleType -> ScaleType -> Bool
$c> :: ScaleType -> ScaleType -> Bool
> :: ScaleType -> ScaleType -> Bool
$c>= :: ScaleType -> ScaleType -> Bool
>= :: ScaleType -> ScaleType -> Bool
$cmax :: ScaleType -> ScaleType -> ScaleType
max :: ScaleType -> ScaleType -> ScaleType
$cmin :: ScaleType -> ScaleType -> ScaleType
min :: ScaleType -> ScaleType -> ScaleType
Ord, ScaleType
ScaleType -> ScaleType -> Bounded ScaleType
forall a. a -> a -> Bounded a
$cminBound :: ScaleType
minBound :: ScaleType
$cmaxBound :: ScaleType
maxBound :: ScaleType
Bounded, Int -> ScaleType
ScaleType -> Int
ScaleType -> [ScaleType]
ScaleType -> ScaleType
ScaleType -> ScaleType -> [ScaleType]
ScaleType -> ScaleType -> ScaleType -> [ScaleType]
(ScaleType -> ScaleType)
-> (ScaleType -> ScaleType)
-> (Int -> ScaleType)
-> (ScaleType -> Int)
-> (ScaleType -> [ScaleType])
-> (ScaleType -> ScaleType -> [ScaleType])
-> (ScaleType -> ScaleType -> [ScaleType])
-> (ScaleType -> ScaleType -> ScaleType -> [ScaleType])
-> Enum ScaleType
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 :: ScaleType -> ScaleType
succ :: ScaleType -> ScaleType
$cpred :: ScaleType -> ScaleType
pred :: ScaleType -> ScaleType
$ctoEnum :: Int -> ScaleType
toEnum :: Int -> ScaleType
$cfromEnum :: ScaleType -> Int
fromEnum :: ScaleType -> Int
$cenumFrom :: ScaleType -> [ScaleType]
enumFrom :: ScaleType -> [ScaleType]
$cenumFromThen :: ScaleType -> ScaleType -> [ScaleType]
enumFromThen :: ScaleType -> ScaleType -> [ScaleType]
$cenumFromTo :: ScaleType -> ScaleType -> [ScaleType]
enumFromTo :: ScaleType -> ScaleType -> [ScaleType]
$cenumFromThenTo :: ScaleType -> ScaleType -> ScaleType -> [ScaleType]
enumFromThenTo :: ScaleType -> ScaleType -> ScaleType -> [ScaleType]
Enum, ReadPrec [ScaleType]
ReadPrec ScaleType
Int -> ReadS ScaleType
ReadS [ScaleType]
(Int -> ReadS ScaleType)
-> ReadS [ScaleType]
-> ReadPrec ScaleType
-> ReadPrec [ScaleType]
-> Read ScaleType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScaleType
readsPrec :: Int -> ReadS ScaleType
$creadList :: ReadS [ScaleType]
readList :: ReadS [ScaleType]
$creadPrec :: ReadPrec ScaleType
readPrec :: ReadPrec ScaleType
$creadListPrec :: ReadPrec [ScaleType]
readListPrec :: ReadPrec [ScaleType]
Read, Int -> ScaleType -> ShowS
[ScaleType] -> ShowS
ScaleType -> String
(Int -> ScaleType -> ShowS)
-> (ScaleType -> String)
-> ([ScaleType] -> ShowS)
-> Show ScaleType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScaleType -> ShowS
showsPrec :: Int -> ScaleType -> ShowS
$cshow :: ScaleType -> String
show :: ScaleType -> String
$cshowList :: [ScaleType] -> ShowS
showList :: [ScaleType] -> ShowS
Show)
scaleTypeCode :: ScaleType -> H5Z_SO_scale_type_t
scaleTypeCode :: ScaleType -> H5Z_SO_scale_type_t
scaleTypeCode ScaleType
FloatDScale = H5Z_SO_scale_type_t
h5z_SO_FLOAT_DSCALE
scaleTypeCode ScaleType
FloatEScale = H5Z_SO_scale_type_t
h5z_SO_FLOAT_ESCALE
scaleTypeCode ScaleType
IntScale = H5Z_SO_scale_type_t
h5z_SO_INT
setScaleOffset :: DatasetCreationPropertyList t => t -> ScaleType -> CInt -> IO ()
setScaleOffset :: forall t.
DatasetCreationPropertyList t =>
t -> ScaleType -> CInt -> IO ()
setScaleOffset t
plist ScaleType
scale_type CInt
scale_factor =
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 -> H5Z_SO_scale_type_t -> CInt -> IO HErr_t
h5p_set_scaleoffset (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) (ScaleType -> H5Z_SO_scale_type_t
scaleTypeCode ScaleType
scale_type) CInt
scale_factor
setFillValue :: (DatasetCreationPropertyList t, NativeType a) => t -> a -> IO ()
setFillValue :: forall t a.
(DatasetCreationPropertyList t, NativeType a) =>
t -> a -> IO ()
setFillValue t
plist a
value =
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
$
a -> (In a -> IO HErr_t) -> IO HErr_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m) =>
a -> (In a -> m b) -> m b
withIn a
value ((In a -> IO HErr_t) -> IO HErr_t)
-> (In a -> IO HErr_t) -> IO HErr_t
forall a b. (a -> b) -> a -> b
$ \In a
ivalue ->
HId_t -> HId_t -> In a -> IO HErr_t
forall a. HId_t -> HId_t -> In a -> IO HErr_t
h5p_set_fill_value (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) (In a -> HId_t
forall t (f :: * -> *). NativeType t => f t -> HId_t
hdfTypeOf1 In a
ivalue) In a
ivalue
getFillValue :: (DatasetCreationPropertyList t, NativeType a) => t -> IO a
getFillValue :: forall t a.
(DatasetCreationPropertyList t, NativeType a) =>
t -> IO a
getFillValue t
plist =
(Out a -> IO ()) -> IO a
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out a -> IO ()) -> IO a) -> (Out a -> IO ()) -> IO a
forall a b. (a -> b) -> a -> b
$ \Out a
value ->
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 -> HId_t -> Out a -> IO HErr_t
forall a. HId_t -> HId_t -> Out a -> IO HErr_t
h5p_get_fill_value (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) (Out a -> HId_t
forall t (f :: * -> *). NativeType t => f t -> HId_t
hdfTypeOf1 Out a
value) Out a
value
data FillValueDefaultType
= Undefined
| DefaultFillValue
| UserDefined
deriving (FillValueDefaultType -> FillValueDefaultType -> Bool
(FillValueDefaultType -> FillValueDefaultType -> Bool)
-> (FillValueDefaultType -> FillValueDefaultType -> Bool)
-> Eq FillValueDefaultType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FillValueDefaultType -> FillValueDefaultType -> Bool
== :: FillValueDefaultType -> FillValueDefaultType -> Bool
$c/= :: FillValueDefaultType -> FillValueDefaultType -> Bool
/= :: FillValueDefaultType -> FillValueDefaultType -> Bool
Eq, Eq FillValueDefaultType
Eq FillValueDefaultType =>
(FillValueDefaultType -> FillValueDefaultType -> Ordering)
-> (FillValueDefaultType -> FillValueDefaultType -> Bool)
-> (FillValueDefaultType -> FillValueDefaultType -> Bool)
-> (FillValueDefaultType -> FillValueDefaultType -> Bool)
-> (FillValueDefaultType -> FillValueDefaultType -> Bool)
-> (FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType)
-> (FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType)
-> Ord FillValueDefaultType
FillValueDefaultType -> FillValueDefaultType -> Bool
FillValueDefaultType -> FillValueDefaultType -> Ordering
FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType
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 :: FillValueDefaultType -> FillValueDefaultType -> Ordering
compare :: FillValueDefaultType -> FillValueDefaultType -> Ordering
$c< :: FillValueDefaultType -> FillValueDefaultType -> Bool
< :: FillValueDefaultType -> FillValueDefaultType -> Bool
$c<= :: FillValueDefaultType -> FillValueDefaultType -> Bool
<= :: FillValueDefaultType -> FillValueDefaultType -> Bool
$c> :: FillValueDefaultType -> FillValueDefaultType -> Bool
> :: FillValueDefaultType -> FillValueDefaultType -> Bool
$c>= :: FillValueDefaultType -> FillValueDefaultType -> Bool
>= :: FillValueDefaultType -> FillValueDefaultType -> Bool
$cmax :: FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType
max :: FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType
$cmin :: FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType
min :: FillValueDefaultType
-> FillValueDefaultType -> FillValueDefaultType
Ord, FillValueDefaultType
FillValueDefaultType
-> FillValueDefaultType -> Bounded FillValueDefaultType
forall a. a -> a -> Bounded a
$cminBound :: FillValueDefaultType
minBound :: FillValueDefaultType
$cmaxBound :: FillValueDefaultType
maxBound :: FillValueDefaultType
Bounded, Int -> FillValueDefaultType
FillValueDefaultType -> Int
FillValueDefaultType -> [FillValueDefaultType]
FillValueDefaultType -> FillValueDefaultType
FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType]
FillValueDefaultType
-> FillValueDefaultType
-> FillValueDefaultType
-> [FillValueDefaultType]
(FillValueDefaultType -> FillValueDefaultType)
-> (FillValueDefaultType -> FillValueDefaultType)
-> (Int -> FillValueDefaultType)
-> (FillValueDefaultType -> Int)
-> (FillValueDefaultType -> [FillValueDefaultType])
-> (FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType])
-> (FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType])
-> (FillValueDefaultType
-> FillValueDefaultType
-> FillValueDefaultType
-> [FillValueDefaultType])
-> Enum FillValueDefaultType
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 :: FillValueDefaultType -> FillValueDefaultType
succ :: FillValueDefaultType -> FillValueDefaultType
$cpred :: FillValueDefaultType -> FillValueDefaultType
pred :: FillValueDefaultType -> FillValueDefaultType
$ctoEnum :: Int -> FillValueDefaultType
toEnum :: Int -> FillValueDefaultType
$cfromEnum :: FillValueDefaultType -> Int
fromEnum :: FillValueDefaultType -> Int
$cenumFrom :: FillValueDefaultType -> [FillValueDefaultType]
enumFrom :: FillValueDefaultType -> [FillValueDefaultType]
$cenumFromThen :: FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType]
enumFromThen :: FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType]
$cenumFromTo :: FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType]
enumFromTo :: FillValueDefaultType
-> FillValueDefaultType -> [FillValueDefaultType]
$cenumFromThenTo :: FillValueDefaultType
-> FillValueDefaultType
-> FillValueDefaultType
-> [FillValueDefaultType]
enumFromThenTo :: FillValueDefaultType
-> FillValueDefaultType
-> FillValueDefaultType
-> [FillValueDefaultType]
Enum, ReadPrec [FillValueDefaultType]
ReadPrec FillValueDefaultType
Int -> ReadS FillValueDefaultType
ReadS [FillValueDefaultType]
(Int -> ReadS FillValueDefaultType)
-> ReadS [FillValueDefaultType]
-> ReadPrec FillValueDefaultType
-> ReadPrec [FillValueDefaultType]
-> Read FillValueDefaultType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FillValueDefaultType
readsPrec :: Int -> ReadS FillValueDefaultType
$creadList :: ReadS [FillValueDefaultType]
readList :: ReadS [FillValueDefaultType]
$creadPrec :: ReadPrec FillValueDefaultType
readPrec :: ReadPrec FillValueDefaultType
$creadListPrec :: ReadPrec [FillValueDefaultType]
readListPrec :: ReadPrec [FillValueDefaultType]
Read, Int -> FillValueDefaultType -> ShowS
[FillValueDefaultType] -> ShowS
FillValueDefaultType -> String
(Int -> FillValueDefaultType -> ShowS)
-> (FillValueDefaultType -> String)
-> ([FillValueDefaultType] -> ShowS)
-> Show FillValueDefaultType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FillValueDefaultType -> ShowS
showsPrec :: Int -> FillValueDefaultType -> ShowS
$cshow :: FillValueDefaultType -> String
show :: FillValueDefaultType -> String
$cshowList :: [FillValueDefaultType] -> ShowS
showList :: [FillValueDefaultType] -> ShowS
Show)
fillValueDefaultType :: H5D_fill_value_t -> FillValueDefaultType
fillValueDefaultType :: H5D_fill_value_t -> FillValueDefaultType
fillValueDefaultType H5D_fill_value_t
c
| H5D_fill_value_t
c H5D_fill_value_t -> H5D_fill_value_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_value_t
h5d_FILL_VALUE_UNDEFINED = FillValueDefaultType
Undefined
| H5D_fill_value_t
c H5D_fill_value_t -> H5D_fill_value_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_value_t
h5d_FILL_VALUE_DEFAULT = FillValueDefaultType
DefaultFillValue
| H5D_fill_value_t
c H5D_fill_value_t -> H5D_fill_value_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_value_t
h5d_FILL_VALUE_USER_DEFINED = FillValueDefaultType
UserDefined
| H5D_fill_value_t
c H5D_fill_value_t -> H5D_fill_value_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_value_t
h5d_FILL_VALUE_ERROR = String -> FillValueDefaultType
forall a. HasCallStack => String -> a
error String
"fillValueDefined: h5d_FILL_VALUE_ERROR"
| Bool
otherwise = String -> FillValueDefaultType
forall a. HasCallStack => String -> a
error (String
"fillValueDefined: unknown H5D_fill_value_t " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5D_fill_value_t -> String
forall a. Show a => a -> String
show H5D_fill_value_t
c)
fillValueDefined :: DatasetCreationPropertyList t => t -> IO FillValueDefaultType
fillValueDefined :: forall t.
DatasetCreationPropertyList t =>
t -> IO FillValueDefaultType
fillValueDefined t
plist =
(H5D_fill_value_t -> FillValueDefaultType)
-> IO H5D_fill_value_t -> IO FillValueDefaultType
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap H5D_fill_value_t -> FillValueDefaultType
fillValueDefaultType (IO H5D_fill_value_t -> IO FillValueDefaultType)
-> IO H5D_fill_value_t -> IO FillValueDefaultType
forall a b. (a -> b) -> a -> b
$
(Out H5D_fill_value_t -> IO ()) -> IO H5D_fill_value_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out H5D_fill_value_t -> IO ()) -> IO H5D_fill_value_t)
-> (Out H5D_fill_value_t -> IO ()) -> IO H5D_fill_value_t
forall a b. (a -> b) -> a -> b
$ \Out H5D_fill_value_t
status ->
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 -> Out H5D_fill_value_t -> IO HErr_t
h5p_fill_value_defined (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) Out H5D_fill_value_t
status
data AllocTime
= DefaultAllocTime
| Early
| Late
| Incr
deriving (AllocTime -> AllocTime -> Bool
(AllocTime -> AllocTime -> Bool)
-> (AllocTime -> AllocTime -> Bool) -> Eq AllocTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AllocTime -> AllocTime -> Bool
== :: AllocTime -> AllocTime -> Bool
$c/= :: AllocTime -> AllocTime -> Bool
/= :: AllocTime -> AllocTime -> Bool
Eq, Eq AllocTime
Eq AllocTime =>
(AllocTime -> AllocTime -> Ordering)
-> (AllocTime -> AllocTime -> Bool)
-> (AllocTime -> AllocTime -> Bool)
-> (AllocTime -> AllocTime -> Bool)
-> (AllocTime -> AllocTime -> Bool)
-> (AllocTime -> AllocTime -> AllocTime)
-> (AllocTime -> AllocTime -> AllocTime)
-> Ord AllocTime
AllocTime -> AllocTime -> Bool
AllocTime -> AllocTime -> Ordering
AllocTime -> AllocTime -> AllocTime
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 :: AllocTime -> AllocTime -> Ordering
compare :: AllocTime -> AllocTime -> Ordering
$c< :: AllocTime -> AllocTime -> Bool
< :: AllocTime -> AllocTime -> Bool
$c<= :: AllocTime -> AllocTime -> Bool
<= :: AllocTime -> AllocTime -> Bool
$c> :: AllocTime -> AllocTime -> Bool
> :: AllocTime -> AllocTime -> Bool
$c>= :: AllocTime -> AllocTime -> Bool
>= :: AllocTime -> AllocTime -> Bool
$cmax :: AllocTime -> AllocTime -> AllocTime
max :: AllocTime -> AllocTime -> AllocTime
$cmin :: AllocTime -> AllocTime -> AllocTime
min :: AllocTime -> AllocTime -> AllocTime
Ord, AllocTime
AllocTime -> AllocTime -> Bounded AllocTime
forall a. a -> a -> Bounded a
$cminBound :: AllocTime
minBound :: AllocTime
$cmaxBound :: AllocTime
maxBound :: AllocTime
Bounded, Int -> AllocTime
AllocTime -> Int
AllocTime -> [AllocTime]
AllocTime -> AllocTime
AllocTime -> AllocTime -> [AllocTime]
AllocTime -> AllocTime -> AllocTime -> [AllocTime]
(AllocTime -> AllocTime)
-> (AllocTime -> AllocTime)
-> (Int -> AllocTime)
-> (AllocTime -> Int)
-> (AllocTime -> [AllocTime])
-> (AllocTime -> AllocTime -> [AllocTime])
-> (AllocTime -> AllocTime -> [AllocTime])
-> (AllocTime -> AllocTime -> AllocTime -> [AllocTime])
-> Enum AllocTime
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 :: AllocTime -> AllocTime
succ :: AllocTime -> AllocTime
$cpred :: AllocTime -> AllocTime
pred :: AllocTime -> AllocTime
$ctoEnum :: Int -> AllocTime
toEnum :: Int -> AllocTime
$cfromEnum :: AllocTime -> Int
fromEnum :: AllocTime -> Int
$cenumFrom :: AllocTime -> [AllocTime]
enumFrom :: AllocTime -> [AllocTime]
$cenumFromThen :: AllocTime -> AllocTime -> [AllocTime]
enumFromThen :: AllocTime -> AllocTime -> [AllocTime]
$cenumFromTo :: AllocTime -> AllocTime -> [AllocTime]
enumFromTo :: AllocTime -> AllocTime -> [AllocTime]
$cenumFromThenTo :: AllocTime -> AllocTime -> AllocTime -> [AllocTime]
enumFromThenTo :: AllocTime -> AllocTime -> AllocTime -> [AllocTime]
Enum, ReadPrec [AllocTime]
ReadPrec AllocTime
Int -> ReadS AllocTime
ReadS [AllocTime]
(Int -> ReadS AllocTime)
-> ReadS [AllocTime]
-> ReadPrec AllocTime
-> ReadPrec [AllocTime]
-> Read AllocTime
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AllocTime
readsPrec :: Int -> ReadS AllocTime
$creadList :: ReadS [AllocTime]
readList :: ReadS [AllocTime]
$creadPrec :: ReadPrec AllocTime
readPrec :: ReadPrec AllocTime
$creadListPrec :: ReadPrec [AllocTime]
readListPrec :: ReadPrec [AllocTime]
Read, Int -> AllocTime -> ShowS
[AllocTime] -> ShowS
AllocTime -> String
(Int -> AllocTime -> ShowS)
-> (AllocTime -> String)
-> ([AllocTime] -> ShowS)
-> Show AllocTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AllocTime -> ShowS
showsPrec :: Int -> AllocTime -> ShowS
$cshow :: AllocTime -> String
show :: AllocTime -> String
$cshowList :: [AllocTime] -> ShowS
showList :: [AllocTime] -> ShowS
Show)
allocTimeCode :: AllocTime -> H5D_alloc_time_t
allocTimeCode :: AllocTime -> H5D_alloc_time_t
allocTimeCode AllocTime
DefaultAllocTime = H5D_alloc_time_t
h5d_ALLOC_TIME_DEFAULT
allocTimeCode AllocTime
Early = H5D_alloc_time_t
h5d_ALLOC_TIME_EARLY
allocTimeCode AllocTime
Late = H5D_alloc_time_t
h5d_ALLOC_TIME_LATE
allocTimeCode AllocTime
Incr = H5D_alloc_time_t
h5d_ALLOC_TIME_INCR
allocTime :: H5D_alloc_time_t -> AllocTime
allocTime :: H5D_alloc_time_t -> AllocTime
allocTime H5D_alloc_time_t
c
| H5D_alloc_time_t
c H5D_alloc_time_t -> H5D_alloc_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_alloc_time_t
h5d_ALLOC_TIME_DEFAULT = AllocTime
DefaultAllocTime
| H5D_alloc_time_t
c H5D_alloc_time_t -> H5D_alloc_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_alloc_time_t
h5d_ALLOC_TIME_EARLY = AllocTime
Early
| H5D_alloc_time_t
c H5D_alloc_time_t -> H5D_alloc_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_alloc_time_t
h5d_ALLOC_TIME_LATE = AllocTime
Late
| H5D_alloc_time_t
c H5D_alloc_time_t -> H5D_alloc_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_alloc_time_t
h5d_ALLOC_TIME_INCR = AllocTime
Incr
| H5D_alloc_time_t
c H5D_alloc_time_t -> H5D_alloc_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_alloc_time_t
h5d_ALLOC_TIME_ERROR = String -> AllocTime
forall a. HasCallStack => String -> a
error String
"h5d_ALLOC_TIME_ERROR"
| Bool
otherwise = String -> AllocTime
forall a. HasCallStack => String -> a
error (String
"unknown H5D_alloc_time_t " String -> ShowS
forall a. [a] -> [a] -> [a]
++ H5D_alloc_time_t -> String
forall a. Show a => a -> String
show H5D_alloc_time_t
c)
setAllocTime :: DatasetCreationPropertyList t => t -> AllocTime -> IO ()
setAllocTime :: forall t. DatasetCreationPropertyList t => t -> AllocTime -> IO ()
setAllocTime t
plist AllocTime
alloc_time =
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 -> H5D_alloc_time_t -> IO HErr_t
h5p_set_alloc_time (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) (AllocTime -> H5D_alloc_time_t
allocTimeCode AllocTime
alloc_time)
getAllocTime :: DatasetCreationPropertyList t => t -> IO AllocTime
getAllocTime :: forall t. DatasetCreationPropertyList t => t -> IO AllocTime
getAllocTime t
plist =
(H5D_alloc_time_t -> AllocTime)
-> IO H5D_alloc_time_t -> IO AllocTime
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap H5D_alloc_time_t -> AllocTime
allocTime (IO H5D_alloc_time_t -> IO AllocTime)
-> IO H5D_alloc_time_t -> IO AllocTime
forall a b. (a -> b) -> a -> b
$
(Out H5D_alloc_time_t -> IO ()) -> IO H5D_alloc_time_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out H5D_alloc_time_t -> IO ()) -> IO H5D_alloc_time_t)
-> (Out H5D_alloc_time_t -> IO ()) -> IO H5D_alloc_time_t
forall a b. (a -> b) -> a -> b
$ \Out H5D_alloc_time_t
alloc_time ->
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 -> Out H5D_alloc_time_t -> IO HErr_t
h5p_get_alloc_time (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) Out H5D_alloc_time_t
alloc_time
data FillTime
= Alloc
| Never
| IfSet
deriving (FillTime -> FillTime -> Bool
(FillTime -> FillTime -> Bool)
-> (FillTime -> FillTime -> Bool) -> Eq FillTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FillTime -> FillTime -> Bool
== :: FillTime -> FillTime -> Bool
$c/= :: FillTime -> FillTime -> Bool
/= :: FillTime -> FillTime -> Bool
Eq, Eq FillTime
Eq FillTime =>
(FillTime -> FillTime -> Ordering)
-> (FillTime -> FillTime -> Bool)
-> (FillTime -> FillTime -> Bool)
-> (FillTime -> FillTime -> Bool)
-> (FillTime -> FillTime -> Bool)
-> (FillTime -> FillTime -> FillTime)
-> (FillTime -> FillTime -> FillTime)
-> Ord FillTime
FillTime -> FillTime -> Bool
FillTime -> FillTime -> Ordering
FillTime -> FillTime -> FillTime
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 :: FillTime -> FillTime -> Ordering
compare :: FillTime -> FillTime -> Ordering
$c< :: FillTime -> FillTime -> Bool
< :: FillTime -> FillTime -> Bool
$c<= :: FillTime -> FillTime -> Bool
<= :: FillTime -> FillTime -> Bool
$c> :: FillTime -> FillTime -> Bool
> :: FillTime -> FillTime -> Bool
$c>= :: FillTime -> FillTime -> Bool
>= :: FillTime -> FillTime -> Bool
$cmax :: FillTime -> FillTime -> FillTime
max :: FillTime -> FillTime -> FillTime
$cmin :: FillTime -> FillTime -> FillTime
min :: FillTime -> FillTime -> FillTime
Ord, FillTime
FillTime -> FillTime -> Bounded FillTime
forall a. a -> a -> Bounded a
$cminBound :: FillTime
minBound :: FillTime
$cmaxBound :: FillTime
maxBound :: FillTime
Bounded, Int -> FillTime
FillTime -> Int
FillTime -> [FillTime]
FillTime -> FillTime
FillTime -> FillTime -> [FillTime]
FillTime -> FillTime -> FillTime -> [FillTime]
(FillTime -> FillTime)
-> (FillTime -> FillTime)
-> (Int -> FillTime)
-> (FillTime -> Int)
-> (FillTime -> [FillTime])
-> (FillTime -> FillTime -> [FillTime])
-> (FillTime -> FillTime -> [FillTime])
-> (FillTime -> FillTime -> FillTime -> [FillTime])
-> Enum FillTime
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 :: FillTime -> FillTime
succ :: FillTime -> FillTime
$cpred :: FillTime -> FillTime
pred :: FillTime -> FillTime
$ctoEnum :: Int -> FillTime
toEnum :: Int -> FillTime
$cfromEnum :: FillTime -> Int
fromEnum :: FillTime -> Int
$cenumFrom :: FillTime -> [FillTime]
enumFrom :: FillTime -> [FillTime]
$cenumFromThen :: FillTime -> FillTime -> [FillTime]
enumFromThen :: FillTime -> FillTime -> [FillTime]
$cenumFromTo :: FillTime -> FillTime -> [FillTime]
enumFromTo :: FillTime -> FillTime -> [FillTime]
$cenumFromThenTo :: FillTime -> FillTime -> FillTime -> [FillTime]
enumFromThenTo :: FillTime -> FillTime -> FillTime -> [FillTime]
Enum, ReadPrec [FillTime]
ReadPrec FillTime
Int -> ReadS FillTime
ReadS [FillTime]
(Int -> ReadS FillTime)
-> ReadS [FillTime]
-> ReadPrec FillTime
-> ReadPrec [FillTime]
-> Read FillTime
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FillTime
readsPrec :: Int -> ReadS FillTime
$creadList :: ReadS [FillTime]
readList :: ReadS [FillTime]
$creadPrec :: ReadPrec FillTime
readPrec :: ReadPrec FillTime
$creadListPrec :: ReadPrec [FillTime]
readListPrec :: ReadPrec [FillTime]
Read, Int -> FillTime -> ShowS
[FillTime] -> ShowS
FillTime -> String
(Int -> FillTime -> ShowS)
-> (FillTime -> String) -> ([FillTime] -> ShowS) -> Show FillTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FillTime -> ShowS
showsPrec :: Int -> FillTime -> ShowS
$cshow :: FillTime -> String
show :: FillTime -> String
$cshowList :: [FillTime] -> ShowS
showList :: [FillTime] -> ShowS
Show)
fillTimeCode :: FillTime -> H5D_fill_time_t
fillTimeCode :: FillTime -> H5D_fill_time_t
fillTimeCode FillTime
Alloc = H5D_fill_time_t
h5d_FILL_TIME_ALLOC
fillTimeCode FillTime
Never = H5D_fill_time_t
h5d_FILL_TIME_NEVER
fillTimeCode FillTime
IfSet = H5D_fill_time_t
h5d_FILL_TIME_IFSET
fillTime :: H5D_fill_time_t -> FillTime
fillTime :: H5D_fill_time_t -> FillTime
fillTime H5D_fill_time_t
c
| H5D_fill_time_t
c H5D_fill_time_t -> H5D_fill_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_time_t
h5d_FILL_TIME_ALLOC = FillTime
Alloc
| H5D_fill_time_t
c H5D_fill_time_t -> H5D_fill_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_time_t
h5d_FILL_TIME_NEVER = FillTime
Never
| H5D_fill_time_t
c H5D_fill_time_t -> H5D_fill_time_t -> Bool
forall a. Eq a => a -> a -> Bool
== H5D_fill_time_t
h5d_FILL_TIME_IFSET = FillTime
IfSet
| Bool
otherwise = String -> FillTime
forall a. HasCallStack => String -> a
error String
"unknown h5d_FILL_TIME value"
setFillTime :: DatasetCreationPropertyList t => t -> FillTime -> IO ()
setFillTime :: forall t. DatasetCreationPropertyList t => t -> FillTime -> IO ()
setFillTime t
plist FillTime
fill_time =
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 -> H5D_fill_time_t -> IO HErr_t
h5p_set_fill_time (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) (FillTime -> H5D_fill_time_t
fillTimeCode FillTime
fill_time)
getFillTime :: DatasetCreationPropertyList t => t -> IO FillTime
getFillTime :: forall t. DatasetCreationPropertyList t => t -> IO FillTime
getFillTime t
plist =
(H5D_fill_time_t -> FillTime) -> IO H5D_fill_time_t -> IO FillTime
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap H5D_fill_time_t -> FillTime
fillTime (IO H5D_fill_time_t -> IO FillTime)
-> IO H5D_fill_time_t -> IO FillTime
forall a b. (a -> b) -> a -> b
$
(Out H5D_fill_time_t -> IO ()) -> IO H5D_fill_time_t
forall a (m :: * -> *) b.
(Storable a, MonadBaseControl IO m, MonadIO m) =>
(Out a -> m b) -> m a
withOut_ ((Out H5D_fill_time_t -> IO ()) -> IO H5D_fill_time_t)
-> (Out H5D_fill_time_t -> IO ()) -> IO H5D_fill_time_t
forall a b. (a -> b) -> a -> b
$ \Out H5D_fill_time_t
fill_time ->
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 -> Out H5D_fill_time_t -> IO HErr_t
h5p_get_fill_time (t -> HId_t
forall t. HId t => t -> HId_t
hid t
plist) Out H5D_fill_time_t
fill_time