{-# LINE 1 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}




{-# LINE 7 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

module Bindings.HDF5.Raw.H5Z where

import Data.Int
import Data.Word
import Foreign.C.String
import Foreign.C.Types
import Foreign.Ptr
import Foreign.Storable

import Bindings.HDF5.Raw.H5
import Bindings.HDF5.Raw.H5I
import Foreign.Ptr.Conventions

-- |Filter identifiers.  Values 0 through 255 are for filters defined by the
-- HDF5 library.  Values 256 through 511 are available for testing new
-- filters.  Subsequent values should be obtained from the HDF5 development
-- team at <mailto:hdf5dev@ncsa.uiuc.edu>.  These values will never change
-- because they appear in the HDF5 files.
newtype H5Z_filter_t = H5Z_filter_t Int32 deriving (Ptr H5Z_filter_t -> IO H5Z_filter_t
Ptr H5Z_filter_t -> Int -> IO H5Z_filter_t
Ptr H5Z_filter_t -> Int -> H5Z_filter_t -> IO ()
Ptr H5Z_filter_t -> H5Z_filter_t -> IO ()
H5Z_filter_t -> Int
(H5Z_filter_t -> Int)
-> (H5Z_filter_t -> Int)
-> (Ptr H5Z_filter_t -> Int -> IO H5Z_filter_t)
-> (Ptr H5Z_filter_t -> Int -> H5Z_filter_t -> IO ())
-> (forall b. Ptr b -> Int -> IO H5Z_filter_t)
-> (forall b. Ptr b -> Int -> H5Z_filter_t -> IO ())
-> (Ptr H5Z_filter_t -> IO H5Z_filter_t)
-> (Ptr H5Z_filter_t -> H5Z_filter_t -> IO ())
-> Storable H5Z_filter_t
forall b. Ptr b -> Int -> IO H5Z_filter_t
forall b. Ptr b -> Int -> H5Z_filter_t -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: H5Z_filter_t -> Int
sizeOf :: H5Z_filter_t -> Int
$calignment :: H5Z_filter_t -> Int
alignment :: H5Z_filter_t -> Int
$cpeekElemOff :: Ptr H5Z_filter_t -> Int -> IO H5Z_filter_t
peekElemOff :: Ptr H5Z_filter_t -> Int -> IO H5Z_filter_t
$cpokeElemOff :: Ptr H5Z_filter_t -> Int -> H5Z_filter_t -> IO ()
pokeElemOff :: Ptr H5Z_filter_t -> Int -> H5Z_filter_t -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5Z_filter_t
peekByteOff :: forall b. Ptr b -> Int -> IO H5Z_filter_t
$cpokeByteOff :: forall b. Ptr b -> Int -> H5Z_filter_t -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5Z_filter_t -> IO ()
$cpeek :: Ptr H5Z_filter_t -> IO H5Z_filter_t
peek :: Ptr H5Z_filter_t -> IO H5Z_filter_t
$cpoke :: Ptr H5Z_filter_t -> H5Z_filter_t -> IO ()
poke :: Ptr H5Z_filter_t -> H5Z_filter_t -> IO ()
Storable, Int -> H5Z_filter_t -> ShowS
[H5Z_filter_t] -> ShowS
H5Z_filter_t -> String
(Int -> H5Z_filter_t -> ShowS)
-> (H5Z_filter_t -> String)
-> ([H5Z_filter_t] -> ShowS)
-> Show H5Z_filter_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5Z_filter_t -> ShowS
showsPrec :: Int -> H5Z_filter_t -> ShowS
$cshow :: H5Z_filter_t -> String
show :: H5Z_filter_t -> String
$cshowList :: [H5Z_filter_t] -> ShowS
showList :: [H5Z_filter_t] -> ShowS
Show, H5Z_filter_t -> H5Z_filter_t -> Bool
(H5Z_filter_t -> H5Z_filter_t -> Bool)
-> (H5Z_filter_t -> H5Z_filter_t -> Bool) -> Eq H5Z_filter_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5Z_filter_t -> H5Z_filter_t -> Bool
== :: H5Z_filter_t -> H5Z_filter_t -> Bool
$c/= :: H5Z_filter_t -> H5Z_filter_t -> Bool
/= :: H5Z_filter_t -> H5Z_filter_t -> Bool
Eq)

{-# LINE 27 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |no filter
h5z_FILTER_ERROR :: H5Z_filter_t
h5z_FILTER_ERROR :: H5Z_filter_t
h5z_FILTER_ERROR = Int32 -> H5Z_filter_t
H5Z_filter_t (-Int32
1)

{-# LINE 30 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |reserved indefinitely
h5z_FILTER_NONE :: H5Z_filter_t
h5z_FILTER_NONE :: H5Z_filter_t
h5z_FILTER_NONE = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
0)

{-# LINE 33 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |deflation like gzip
h5z_FILTER_DEFLATE :: H5Z_filter_t
h5z_FILTER_DEFLATE :: H5Z_filter_t
h5z_FILTER_DEFLATE = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
1)

{-# LINE 36 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |shuffle the data
h5z_FILTER_SHUFFLE :: H5Z_filter_t
h5z_FILTER_SHUFFLE :: H5Z_filter_t
h5z_FILTER_SHUFFLE = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
2)

{-# LINE 39 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |fletcher32 checksum of EDC
h5z_FILTER_FLETCHER32 :: H5Z_filter_t
h5z_FILTER_FLETCHER32 :: H5Z_filter_t
h5z_FILTER_FLETCHER32 = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
3)

{-# LINE 42 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |szip compression
h5z_FILTER_SZIP :: H5Z_filter_t
h5z_FILTER_SZIP :: H5Z_filter_t
h5z_FILTER_SZIP = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
4)

{-# LINE 45 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |nbit compression
h5z_FILTER_NBIT :: H5Z_filter_t
h5z_FILTER_NBIT :: H5Z_filter_t
h5z_FILTER_NBIT = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
5)

{-# LINE 48 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |scale+offset compression
h5z_FILTER_SCALEOFFSET :: H5Z_filter_t
h5z_FILTER_SCALEOFFSET :: H5Z_filter_t
h5z_FILTER_SCALEOFFSET = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
6)

{-# LINE 51 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |filter ids below this value are reserved for library use
h5z_FILTER_RESERVED :: H5Z_filter_t
h5z_FILTER_RESERVED :: H5Z_filter_t
h5z_FILTER_RESERVED = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
256)

{-# LINE 54 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |maximum filter id
h5z_FILTER_MAX :: H5Z_filter_t
h5z_FILTER_MAX :: H5Z_filter_t
h5z_FILTER_MAX = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
65535)

{-# LINE 57 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Symbol to remove all filters in 'h5p_remove_filter'
h5z_FILTER_ALL :: H5Z_filter_t
h5z_FILTER_ALL :: H5Z_filter_t
h5z_FILTER_ALL = Int32 -> H5Z_filter_t
H5Z_filter_t (Int32
0)

{-# LINE 60 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Maximum number of filters allowed in a pipeline
-- (should probably be allowed to be an unlimited amount, but
-- currently each filter uses a bit in a 32-bit field, so the
-- format would have to be changed to accomodate that)
h5z_MAX_NFILTERS :: forall a. Num a => a
h5z_MAX_NFILTERS = a
32
h5z_MAX_NFILTERS :: (Num a) => a

{-# LINE 66 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Flags for filter definition (stored)

-- |definition flag mask
h5z_FLAG_DEFMASK :: forall a. Num a => a
h5z_FLAG_DEFMASK = a
255
h5z_FLAG_DEFMASK :: (Num a) => a

{-# LINE 71 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |filter is mandatory
h5z_FLAG_MANDATORY = 0
h5z_FLAG_MANDATORY :: (Num a) => a

{-# LINE 74 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |filter is optional
h5z_FLAG_OPTIONAL = 1
h5z_FLAG_OPTIONAL :: (Num a) => a

{-# LINE 77 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Additional flags for filter invocation (not stored

-- |invocation flag mask
h5z_FLAG_INVMASK :: forall a. Num a => a
h5z_FLAG_INVMASK = a
65280
h5z_FLAG_INVMASK :: (Num a) => a

{-# LINE 82 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |reverse direction; read
h5z_FLAG_REVERSE = 256
h5z_FLAG_REVERSE :: (Num a) => a

{-# LINE 85 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |skip EDC filters for read
h5z_FLAG_SKIP_EDC = 512
h5z_FLAG_SKIP_EDC :: (Num a) => a

{-# LINE 88 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Special parameters for szip compression
-- [These are aliases for the similar definitions in szlib.h, which we can't
-- include directly due to the duplication of various symbols with the zlib.h
-- header file]
h5_SZIP_ALLOW_K13_OPTION_MASK :: forall a. Num a => a
h5_SZIP_ALLOW_K13_OPTION_MASK = a
1
h5_SZIP_ALLOW_K13_OPTION_MASK :: (Num a) => a

{-# LINE 94 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5_SZIP_CHIP_OPTION_MASK = 2
h5_SZIP_CHIP_OPTION_MASK :: (Num a) => a

{-# LINE 95 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5_SZIP_EC_OPTION_MASK = 4
h5_SZIP_EC_OPTION_MASK :: (Num a) => a

{-# LINE 96 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5_SZIP_NN_OPTION_MASK = 32
h5_SZIP_NN_OPTION_MASK :: (Num a) => a

{-# LINE 97 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5_SZIP_MAX_PIXELS_PER_BLOCK = 32
h5_SZIP_MAX_PIXELS_PER_BLOCK :: (Num a) => a

{-# LINE 98 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Macros for the shuffle filter

-- |Number of parameters that users can set
h5z_SHUFFLE_USER_NPARMS :: forall a. Num a => a
h5z_SHUFFLE_USER_NPARMS = a
0
h5z_SHUFFLE_USER_NPARMS :: (Num a) => a

{-# LINE 103 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Total number of parameters for filter
h5z_SHUFFLE_TOTAL_NPARMS = 1
h5z_SHUFFLE_TOTAL_NPARMS :: (Num a) => a

{-# LINE 106 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Macros for the szip filter

-- |Number of parameters that users can set
h5z_SZIP_USER_NPARMS :: forall a. Num a => a
h5z_SZIP_USER_NPARMS = a
2
h5z_SZIP_USER_NPARMS :: (Num a) => a

{-# LINE 111 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Total number of parameters for filter
h5z_SZIP_TOTAL_NPARMS = 4
h5z_SZIP_TOTAL_NPARMS :: (Num a) => a

{-# LINE 114 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |\"User\" parameter for option mask
h5z_SZIP_PARM_MASK = 0
h5z_SZIP_PARM_MASK :: (Num a) => a

{-# LINE 117 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |\"User\" parameter for pixels-per-block
h5z_SZIP_PARM_PPB = 1
h5z_SZIP_PARM_PPB :: (Num a) => a

{-# LINE 120 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |\"Local\" parameter for bits-per-pixel
h5z_SZIP_PARM_BPP = 2
h5z_SZIP_PARM_BPP :: (Num a) => a

{-# LINE 123 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |\"Local\" parameter for pixels-per-scanline
h5z_SZIP_PARM_PPS = 3
h5z_SZIP_PARM_PPS :: (Num a) => a

{-# LINE 126 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Macros for the nbit filter

-- |Number of parameters that users can set
h5z_NBIT_USER_NPARMS :: forall a. Num a => a
h5z_NBIT_USER_NPARMS = a
0
h5z_NBIT_USER_NPARMS :: (Num a) => a

{-# LINE 131 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Macros for the scale offset filter

-- |Number of parameters that users can set
h5z_SCALEOFFSET_USER_NPARMS :: forall a. Num a => a
h5z_SCALEOFFSET_USER_NPARMS = a
2
h5z_SCALEOFFSET_USER_NPARMS :: (Num a) => a

{-# LINE 136 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Special parameters for ScaleOffset filter
h5z_SO_INT_MINBITS_DEFAULT = 0
h5z_SO_INT_MINBITS_DEFAULT :: (Num a) => a

{-# LINE 139 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
newtype H5Z_SO_scale_type_t = H5Z_SO_scale_type_t Word32 deriving (Storable, Show)

{-# LINE 140 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_SO_FLOAT_DSCALE :: H5Z_SO_scale_type_t
h5z_SO_FLOAT_DSCALE = H5Z_SO_scale_type_t (0)

{-# LINE 141 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_SO_FLOAT_ESCALE :: H5Z_SO_scale_type_t
h5z_SO_FLOAT_ESCALE = H5Z_SO_scale_type_t (1)

{-# LINE 142 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_SO_INT :: H5Z_SO_scale_type_t
h5z_SO_INT = H5Z_SO_scale_type_t (2)

{-# LINE 143 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Current version of the H5Z_class_t struct
h5z_CLASS_T_VERS = 1
h5z_CLASS_T_VERS :: (Num a) => a

{-# LINE 146 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Values to decide if EDC is enabled for reading data
newtype H5Z_EDC_t = H5Z_EDC_t Int32 deriving (Storable, Show)

{-# LINE 149 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_ERROR_EDC :: H5Z_EDC_t
h5z_ERROR_EDC = H5Z_EDC_t (-1)

{-# LINE 150 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_DISABLE_EDC :: H5Z_EDC_t
h5z_DISABLE_EDC = H5Z_EDC_t (0)

{-# LINE 151 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_ENABLE_EDC :: H5Z_EDC_t
h5z_ENABLE_EDC = H5Z_EDC_t (1)

{-# LINE 152 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_NO_EDC :: H5Z_EDC_t
h5z_NO_EDC = H5Z_EDC_t (2)

{-# LINE 153 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- ** Bit flags for H5Zget_filter_info
h5z_FILTER_CONFIG_ENCODE_ENABLED = 1
h5z_FILTER_CONFIG_DECODE_ENABLED :: forall a. Num a => a
h5z_FILTER_CONFIG_ENCODE_ENABLED :: (Num a) => a

{-# LINE 156 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}
h5z_FILTER_CONFIG_DECODE_ENABLED = 2
h5z_FILTER_CONFIG_DECODE_ENABLED :: (Num a) => a

{-# LINE 157 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Return values for filter callback function
newtype H5Z_cb_return_t = H5Z_cb_return_t Int32 deriving (Storable, Show)

{-# LINE 160 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

h5z_CB_ERROR :: H5Z_cb_return_t
h5z_CB_ERROR :: H5Z_cb_return_t
h5z_CB_ERROR = Int32 -> H5Z_cb_return_t
H5Z_cb_return_t (-Int32
1)

{-# LINE 162 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |I/O should fail if filter fails.
h5z_CB_FAIL :: H5Z_cb_return_t
h5z_CB_FAIL :: H5Z_cb_return_t
h5z_CB_FAIL = Int32 -> H5Z_cb_return_t
H5Z_cb_return_t (Int32
0)

{-# LINE 165 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |I/O continues if filter fails.
h5z_CB_CONT :: H5Z_cb_return_t
h5z_CB_CONT :: H5Z_cb_return_t
h5z_CB_CONT = Int32 -> H5Z_cb_return_t
H5Z_cb_return_t (Int32
1)

{-# LINE 168 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

h5z_CB_NO :: H5Z_cb_return_t
h5z_CB_NO = H5Z_cb_return_t (2)

{-# LINE 170 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Filter callback function definition
--
-- > typedef H5Z_cb_return_t (*H5Z_filter_func_t)(H5Z_filter_t filter, void* buf,
-- >        size_t buf_size, void* op_data);
type H5Z_filter_func_t a b = FunPtr (H5Z_filter_t -> InOutArray a -> CSize -> InOut b -> IO H5Z_cb_return_t)

-- |Before a dataset gets created, the \"can_apply\" callbacks for any filters used
-- in the dataset creation property list are called
-- with the dataset's dataset creation property list, the dataset's datatype and
-- a dataspace describing a chunk (for chunked dataset storage).
--
-- The \"can_apply\" callback must determine if the combination of the dataset
-- creation property list setting, the datatype and the dataspace represent a
-- valid combination to apply this filter to.  For example, some cases of
-- invalid combinations may involve the filter not operating correctly on
-- certain datatypes (or certain datatype sizes), or certain sizes of the chunk
-- dataspace.
--
-- The \"can_apply\" callback can be the NULL pointer, in which case, the library
-- will assume that it can apply to any combination of dataset creation
-- property list values, datatypes and dataspaces.
--
-- The \"can_apply\" callback returns positive a valid combination, zero for an
-- invalid combination and negative for an error.
--
-- > typedef htri_t (*H5Z_can_apply_func_t)(hid_t dcpl_id, hid_t type_id, hid_t space_id);
type H5Z_can_apply_func_t = FunPtr (HId_t -> HId_t -> HId_t -> IO HTri_t)
foreign import ccall "wrapper" mk_H5Z_can_apply_func_t
  :: (HId_t -> HId_t -> HId_t -> IO HTri_t) -> IO H5Z_can_apply_func_t
foreign import ccall "dynamic" mK_H5Z_can_apply_func_t
  :: H5Z_can_apply_func_t -> (HId_t -> HId_t -> HId_t -> IO HTri_t)

{-# LINE 198 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |After the \"can_apply\" callbacks are checked for new datasets, the \"set_local\"
-- callbacks for any filters used in the dataset creation property list are
-- called.  These callbacks receive the dataset's private copy of the dataset
-- creation property list passed in to H5Dcreate (i.e. not the actual property
-- list passed in to H5Dcreate) and the datatype ID passed in to H5Dcreate
-- (which is not copied and should not be modified) and a dataspace describing
-- the chunk (for chunked dataset storage) (which should also not be modified).
--
-- The \"set_local\" callback must set any parameters that are specific to this
-- dataset, based on the combination of the dataset creation property list
-- values, the datatype and the dataspace.  For example, some filters perform
-- different actions based on different datatypes (or datatype sizes) or
-- different number of dimensions or dataspace sizes.
--
-- The \"set_local\" callback can be the NULL pointer, in which case, the library
-- will assume that there are no dataset-specific settings for this filter.
--
-- The \"set_local\" callback must return non-negative on success and negative
-- for an error.
--
-- > typedef herr_t (*H5Z_set_local_func_t)(hid_t dcpl_id, hid_t type_id, hid_t space_id);
type H5Z_set_local_func_t = FunPtr (HId_t -> HId_t -> HId_t -> IO HErr_t)
foreign import ccall "wrapper" mk_H5Z_set_local_func_t
  :: (HId_t -> HId_t -> HId_t -> IO HErr_t) -> IO H5Z_set_local_func_t
foreign import ccall "dynamic" mK_H5Z_set_local_func_t
  :: H5Z_set_local_func_t -> (HId_t -> HId_t -> HId_t -> IO HErr_t)

{-# LINE 221 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |A filter gets definition flags and invocation flags (defined above), the
-- client data array and size defined when the filter was added to the
-- pipeline, the size in bytes of the data on which to operate, and pointers
-- to a buffer and its allocated size.
--
-- The filter should store the result in the supplied buffer if possible,
-- otherwise it can allocate a new buffer, freeing the original.  The
-- allocated size of the new buffer should be returned through the 'buf_size'
-- pointer and the new buffer through the BUF pointer.
--
-- The return value from the filter is the number of bytes in the output
-- buffer.  If an error occurs then the function should return zero and leave
-- all pointer arguments unchanged.
--
-- > typedef size_t (*H5Z_func_t)(unsigned int flags, size_t cd_nelmts,
-- >        const unsigned int cd_values[], size_t nbytes,
-- >        size_t *buf_size, void **buf);
type H5Z_func_t a = FunPtr (CUInt -> CSize -> InArray CUInt -> CSize -> InOut CSize -> InOut (Ptr a) -> IO CSize)

-- | The filter table maps filter identification numbers to structs that
-- contain a pointers to the filter function and timing statistics.

{-# LINE 244 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | Version number of the H5Z_class_t struct

{-# LINE 247 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | Filter ID number

{-# LINE 250 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | Does this filter have an encoder?

{-# LINE 253 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | Does this filter have a decoder?

{-# LINE 256 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | Comment for debugging

{-# LINE 259 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | The \"can apply\" callback for a filter

{-# LINE 262 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | The \"set local\" callback for a filter

{-# LINE 265 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- | The actual filter function

{-# LINE 268 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

data H5Z_class2_t = H5Z_class2_t{
  H5Z_class2_t -> CInt
h5z_class2_t'version :: CInt,
  h5z_class2_t'id :: H5Z_filter_t,
  h5z_class2_t'encoder_present :: CUInt,
  h5z_class2_t'decoder_present :: CUInt,
  h5z_class2_t'name :: CString,
  h5z_class2_t'can_apply :: H5Z_can_apply_func_t,
  h5z_class2_t'set_local :: H5Z_set_local_func_t,
  h5z_class2_t'filter :: H5Z_func_t ()
} deriving (H5Z_class2_t -> H5Z_class2_t -> Bool
(H5Z_class2_t -> H5Z_class2_t -> Bool)
-> (H5Z_class2_t -> H5Z_class2_t -> Bool) -> Eq H5Z_class2_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5Z_class2_t -> H5Z_class2_t -> Bool
== :: H5Z_class2_t -> H5Z_class2_t -> Bool
$c/= :: H5Z_class2_t -> H5Z_class2_t -> Bool
/= :: H5Z_class2_t -> H5Z_class2_t -> Bool
Eq,Int -> H5Z_class2_t -> ShowS
[H5Z_class2_t] -> ShowS
H5Z_class2_t -> String
(Int -> H5Z_class2_t -> ShowS)
-> (H5Z_class2_t -> String)
-> ([H5Z_class2_t] -> ShowS)
-> Show H5Z_class2_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5Z_class2_t -> ShowS
showsPrec :: Int -> H5Z_class2_t -> ShowS
$cshow :: H5Z_class2_t -> String
show :: H5Z_class2_t -> String
$cshowList :: [H5Z_class2_t] -> ShowS
showList :: [H5Z_class2_t] -> ShowS
Show)
p'H5Z_class2_t'version :: Ptr H5Z_class2_t -> Ptr CInt
p'H5Z_class2_t'version Ptr H5Z_class2_t
p = Ptr H5Z_class2_t -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5Z_class2_t
p Int
0
p'H5Z_class2_t'version :: Ptr (H5Z_class2_t) -> Ptr (CInt)
p'H5Z_class2_t'id :: Ptr H5Z_class2_t -> Ptr H5Z_filter_t
p'H5Z_class2_t'id Ptr H5Z_class2_t
p = Ptr H5Z_class2_t -> Int -> Ptr H5Z_filter_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5Z_class2_t
p Int
4
p'H5Z_class2_t'id :: Ptr (H5Z_class2_t) -> Ptr (H5Z_filter_t)
p'H5Z_class2_t'encoder_present :: Ptr H5Z_class2_t -> Ptr CUInt
p'H5Z_class2_t'encoder_present Ptr H5Z_class2_t
p = Ptr H5Z_class2_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5Z_class2_t
p Int
8
p'H5Z_class2_t'encoder_present :: Ptr (H5Z_class2_t) -> Ptr (CUInt)
p'H5Z_class2_t'decoder_present :: Ptr H5Z_class2_t -> Ptr CUInt
p'H5Z_class2_t'decoder_present Ptr H5Z_class2_t
p = Ptr H5Z_class2_t -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5Z_class2_t
p Int
12
p'H5Z_class2_t'decoder_present :: Ptr (H5Z_class2_t) -> Ptr (CUInt)
p'H5Z_class2_t'name :: Ptr H5Z_class2_t -> Ptr CString
p'H5Z_class2_t'name Ptr H5Z_class2_t
p = Ptr H5Z_class2_t -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5Z_class2_t
p Int
16
p'H5Z_class2_t'name :: Ptr (H5Z_class2_t) -> Ptr (CString)
p'H5Z_class2_t'can_apply p = plusPtr p 24
p'H5Z_class2_t'can_apply :: Ptr (H5Z_class2_t) -> Ptr (H5Z_can_apply_func_t)
p'H5Z_class2_t'set_local p = plusPtr p 32
p'H5Z_class2_t'set_local :: Ptr (H5Z_class2_t) -> Ptr (H5Z_set_local_func_t)
p'H5Z_class2_t'filter :: Ptr H5Z_class2_t -> Ptr (H5Z_func_t ())
p'H5Z_class2_t'filter Ptr H5Z_class2_t
p = Ptr H5Z_class2_t -> Int -> Ptr (H5Z_func_t ())
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5Z_class2_t
p Int
40
p'H5Z_class2_t'filter :: Ptr (H5Z_class2_t) -> Ptr (H5Z_func_t ())
instance Storable H5Z_class2_t where
  sizeOf _ = 48
  alignment _ = 8
  peek _p = do
    v0 <- peekByteOff _p 0
    v1 <- peekByteOff _p 4
    v2 <- peekByteOff _p 8
    v3 <- peekByteOff _p 12
    v4 <- peekByteOff _p 16
    v5 <- peekByteOff _p 24
    v6 <- peekByteOff _p 32
    v7 <- peekByteOff _p 40
    return $ H5Z_class2_t v0 v1 v2 v3 v4 v5 v6 v7
  poke _p (H5Z_class2_t v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff _p 0 v0
    pokeByteOff _p 4 v1
    pokeByteOff _p 8 v2
    pokeByteOff _p 12 v3
    pokeByteOff _p 16 v4
    pokeByteOff _p 24 v5
    pokeByteOff _p 32 v6
    pokeByteOff _p 40 v7
    return ()

{-# LINE 270 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |This function registers a new filter.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Zregister(const void *cls);
foreign import ccall "H5Zregister" h5z_register
  :: In H5Z_class2_t -> IO HErr_t
foreign import ccall "&H5Zregister" p_H5Zregister
  :: FunPtr (In H5Z_class2_t -> IO HErr_t)

{-# LINE 277 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |This function unregisters a filter.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Zunregister(H5Z_filter_t id);
foreign import ccall "H5Zunregister" h5z_unregister
  :: H5Z_filter_t -> IO HErr_t
foreign import ccall "&H5Zunregister" p_H5Zunregister
  :: FunPtr (H5Z_filter_t -> IO HErr_t)

{-# LINE 284 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Check if a filter is available
--
-- > htri_t H5Zfilter_avail(H5Z_filter_t id);
foreign import ccall "H5Zfilter_avail" h5z_filter_avail
  :: H5Z_filter_t -> IO HTri_t
foreign import ccall "&H5Zfilter_avail" p_H5Zfilter_avail
  :: FunPtr (H5Z_filter_t -> IO HTri_t)

{-# LINE 289 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}

-- |Gets information about a pipeline data filter and stores it
-- in 'filter_config_flags'.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Zget_filter_info(H5Z_filter_t filter, unsigned int *filter_config_flags);
foreign import ccall "H5Zget_filter_info" h5z_get_filter_info
  :: H5Z_filter_t -> Out CUInt -> IO HErr_t
foreign import ccall "&H5Zget_filter_info" p_H5Zget_filter_info
  :: FunPtr (H5Z_filter_t -> Out CUInt -> IO HErr_t)

{-# LINE 297 "src/Bindings/HDF5/Raw/H5Z.hsc" #-}