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




module Bindings.HDF5.Raw.H5S where

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

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

h5s_ALL :: HId_t
h5s_ALL :: HId_t
h5s_ALL = HId_t (0)

{-# LINE 17 "src/Bindings/HDF5/Raw/H5S.hsc" #-}
h5s_UNLIMITED = 18446744073709551615
h5s_UNLIMITED :: (Num a) => a

{-# LINE 18 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Maximum number of dimensions
h5s_MAX_RANK = 32
h5s_MAX_RANK :: (Num a) => a

{-# LINE 21 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Different types of dataspaces
newtype H5S_class_t = H5S_class_t Int32 deriving (Storable, Show, Eq)

{-# LINE 24 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |error
h5s_NO_CLASS :: H5S_class_t
h5s_NO_CLASS :: H5S_class_t
h5s_NO_CLASS = Int32 -> H5S_class_t
H5S_class_t (-Int32
1)

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

-- |scalar variable
h5s_SCALAR :: H5S_class_t
h5s_SCALAR :: H5S_class_t
h5s_SCALAR = Int32 -> H5S_class_t
H5S_class_t (Int32
0)

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

-- |simple data space
h5s_SIMPLE :: H5S_class_t
h5s_SIMPLE :: H5S_class_t
h5s_SIMPLE = Int32 -> H5S_class_t
H5S_class_t (Int32
1)

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

-- |null data space
h5s_NULL :: H5S_class_t
h5s_NULL :: H5S_class_t
h5s_NULL = Int32 -> H5S_class_t
H5S_class_t (Int32
2)

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

-- |Different ways of combining selections
newtype H5S_seloper_t = H5S_seloper_t Int32 deriving (Storable, Show)

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

-- |error
h5s_SELECT_NOOP :: H5S_seloper_t
h5s_SELECT_NOOP :: H5S_seloper_t
h5s_SELECT_NOOP = Int32 -> H5S_seloper_t
H5S_seloper_t (-Int32
1)

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

-- |Select "set" operation
h5s_SELECT_SET :: H5S_seloper_t
h5s_SELECT_SET :: H5S_seloper_t
h5s_SELECT_SET = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
0)

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

-- |Binary "or" operation for hyperslabs
-- (add new selection to existing selection)
-- Original region:  AAAAAAAAAA
-- New region:             BBBBBBBBBB
-- A or B:           CCCCCCCCCCCCCCCC
h5s_SELECT_OR :: H5S_seloper_t
h5s_SELECT_OR :: H5S_seloper_t
h5s_SELECT_OR = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
1)

{-# LINE 52 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Binary "and" operation for hyperslabs
-- (only leave overlapped regions in selection)
-- Original region:  AAAAAAAAAA
-- New region:             BBBBBBBBBB
-- A and B:                CCCC
h5s_SELECT_AND :: H5S_seloper_t
h5s_SELECT_AND :: H5S_seloper_t
h5s_SELECT_AND = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
2)

{-# LINE 59 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Binary "xor" operation for hyperslabs
-- (only leave non-overlapped regions in selection)
-- Original region:  AAAAAAAAAA
-- New region:             BBBBBBBBBB
-- A xor B:          CCCCCC    CCCCCC
h5s_SELECT_XOR :: H5S_seloper_t
h5s_SELECT_XOR :: H5S_seloper_t
h5s_SELECT_XOR = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
3)

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

-- |Binary "not" operation for hyperslabs
-- (only leave non-overlapped regions in original selection)
-- Original region:  AAAAAAAAAA
-- New region:             BBBBBBBBBB
-- A not B:          CCCCCC
h5s_SELECT_NOTB :: H5S_seloper_t
h5s_SELECT_NOTB :: H5S_seloper_t
h5s_SELECT_NOTB = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
4)

{-# LINE 73 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Binary "not" operation for hyperslabs
-- (only leave non-overlapped regions in new selection)
-- Original region:  AAAAAAAAAA
-- New region:             BBBBBBBBBB
-- B not A:                    CCCCCC
h5s_SELECT_NOTA :: H5S_seloper_t
h5s_SELECT_NOTA :: H5S_seloper_t
h5s_SELECT_NOTA = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
5)

{-# LINE 80 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Append elements to end of point selection
h5s_SELECT_APPEND :: H5S_seloper_t
h5s_SELECT_APPEND :: H5S_seloper_t
h5s_SELECT_APPEND = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
6)

{-# LINE 83 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Prepend elements to beginning of point selection
h5s_SELECT_PREPEND :: H5S_seloper_t
h5s_SELECT_PREPEND :: H5S_seloper_t
h5s_SELECT_PREPEND = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
7)

{-# LINE 86 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Invalid upper bound on selection operations
h5s_SELECT_INVALID :: H5S_seloper_t
h5s_SELECT_INVALID :: H5S_seloper_t
h5s_SELECT_INVALID = Int32 -> H5S_seloper_t
H5S_seloper_t (Int32
8)

{-# LINE 89 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Enumerated type for the type of selection
newtype H5S_sel_type = H5S_sel_type Int32 deriving (Storable, Show, Eq)

{-# LINE 92 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Error
h5s_SEL_ERROR :: H5S_sel_type
h5s_SEL_ERROR :: H5S_sel_type
h5s_SEL_ERROR = Int32 -> H5S_sel_type
H5S_sel_type (-Int32
1)

{-# LINE 95 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Nothing selected
h5s_SEL_NONE :: H5S_sel_type
h5s_SEL_NONE :: H5S_sel_type
h5s_SEL_NONE = Int32 -> H5S_sel_type
H5S_sel_type (Int32
0)

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

-- |Sequence of points selected
h5s_SEL_POINTS :: H5S_sel_type
h5s_SEL_POINTS :: H5S_sel_type
h5s_SEL_POINTS = Int32 -> H5S_sel_type
H5S_sel_type (Int32
1)

{-# LINE 101 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |"New-style" hyperslab selection defined
h5s_SEL_HYPERSLABS :: H5S_sel_type
h5s_SEL_HYPERSLABS :: H5S_sel_type
h5s_SEL_HYPERSLABS = Int32 -> H5S_sel_type
H5S_sel_type (Int32
2)

{-# LINE 104 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Entire extent selected
h5s_SEL_ALL :: H5S_sel_type
h5s_SEL_ALL :: H5S_sel_type
h5s_SEL_ALL = Int32 -> H5S_sel_type
H5S_sel_type (Int32
3)

{-# LINE 107 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Number of selection types
h5s_SEL_N = 4
h5s_SEL_N :: (Num a) => a

{-# LINE 110 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Creates a new dataspace of a given type.  The extent & selection are
-- undefined
--
-- Parameters:
--
-- [@ type :: 'H5S_type_t' @]   Dataspace type to create
--
-- Returns valid dataspace ID on success, negative on failure
--
-- > hid_t H5Screate(H5S_class_t type);
foreign import ccall "H5Screate" h5s_create
  :: H5S_class_t -> IO HId_t
foreign import ccall "&H5Screate" p_H5Screate
  :: FunPtr (H5S_class_t -> IO HId_t)

{-# LINE 122 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Creates a new simple dataspace object and opens it for
-- access. The 'dims' argument is the size of the simple dataset
-- and the 'maxdims' argument is the upper limit on the size of
-- the dataset.  'maxdims' may be the null pointer in which case
-- the upper limit is the same as 'dims'.  If an element of
-- 'maxdims' is 'h5s_UNLIMITED' then the corresponding dimension is
-- unlimited, otherwise no element of 'maxdims' should be smaller
-- than the corresponding element of 'dims'.
--
-- On success, returns the ID for the new simple dataspace object.
-- Returns negative on failure.
--
-- > hid_t H5Screate_simple(int rank, const hsize_t dims[],
-- >        const hsize_t maxdims[]);
foreign import ccall "H5Screate_simple" h5s_create_simple
  :: CInt -> InArray HSize_t -> InArray HSize_t -> IO HId_t
foreign import ccall "&H5Screate_simple" p_H5Screate_simple
  :: FunPtr (CInt -> InArray HSize_t -> InArray HSize_t -> IO HId_t)

{-# LINE 138 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Determines if a simple dataspace's extent has been set (e.g.,
-- by 'h5s_set_extent_simple').  Helps avoid write errors.
--
-- Returns TRUE (C macro) if dataspace has extent set, FALSE (C macro)
-- if dataspace's extent is uninitialized.
--
-- > herr_t H5Sset_extent_simple(hid_t space_id, int rank,
-- >        const hsize_t dims[],
-- >        const hsize_t max[]);
foreign import ccall "H5Sset_extent_simple" h5s_set_extent_simple
  :: HId_t -> CInt -> InArray HSize_t -> InArray HSize_t -> IO HErr_t
foreign import ccall "&H5Sset_extent_simple" p_H5Sset_extent_simple
  :: FunPtr (HId_t -> CInt -> InArray HSize_t -> InArray HSize_t -> IO HErr_t)

{-# LINE 149 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Copies a dataspace.
--
-- On success, returns the ID of the new dataspace.  Returns negative on
-- failure.
--
-- > hid_t H5Scopy(hid_t space_id);
foreign import ccall "H5Scopy" h5s_copy
  :: HId_t -> IO HId_t
foreign import ccall "&H5Scopy" p_H5Scopy
  :: FunPtr (HId_t -> IO HId_t)

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

-- |Release access to a dataspace object.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sclose(hid_t space_id);
foreign import ccall "H5Sclose" h5s_close
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Sclose" p_H5Sclose
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 164 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Decode a binary object description of dataspace and
-- return a new object handle.
--
-- On success, returns the ID of the new dataspace.  Returns negative on
-- failure.
--
-- > hid_t H5Sdecode(const void *buf);
foreign import ccall "H5Sdecode" h5s_decode
  :: InArray CChar -> IO HId_t
foreign import ccall "&H5Sdecode" p_H5Sdecode
  :: FunPtr (InArray CChar -> IO HId_t)

{-# LINE 173 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Determines how many data points a dataset extent has.
--
-- On success, returns the number of data points in the dataset.  On
-- failure, returns a negative value.
--
-- > hssize_t H5Sget_simple_extent_npoints(hid_t space_id);
foreign import ccall "H5Sget_simple_extent_npoints" h5s_get_simple_extent_npoints
  :: HId_t -> IO HSSize_t
foreign import ccall "&H5Sget_simple_extent_npoints" p_H5Sget_simple_extent_npoints
  :: FunPtr (HId_t -> IO HSSize_t)

{-# LINE 181 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Determines the dimensionality of a dataspace.
--
-- On success, returns the number of dimensions in the dataset.  On
-- failure, returns a negative value.
--
-- > int H5Sget_simple_extent_ndims(hid_t space_id);
foreign import ccall "H5Sget_simple_extent_ndims" h5s_get_simple_extent_ndims
  :: HId_t -> IO CInt
foreign import ccall "&H5Sget_simple_extent_ndims" p_H5Sget_simple_extent_ndims
  :: FunPtr (HId_t -> IO CInt)

{-# LINE 189 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Returns the size and maximum sizes in each dimension of
-- a dataspace DS through	the DIMS and MAXDIMS arguments.
--
-- Returns the number of dimensions, the same value as returned
-- by 'h5s_get_simple_extent_ndims', or a negative value on failure..
--
-- > int H5Sget_simple_extent_dims(hid_t space_id, hsize_t dims[],
-- >        hsize_t maxdims[]);
foreign import ccall "H5Sget_simple_extent_dims" h5s_get_simple_extent_dims
  :: HId_t -> OutArray HSize_t -> OutArray HSize_t -> IO CInt
foreign import ccall "&H5Sget_simple_extent_dims" p_H5Sget_simple_extent_dims
  :: FunPtr (HId_t -> OutArray HSize_t -> OutArray HSize_t -> IO CInt)

{-# LINE 199 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Check if a dataspace is simple
--
-- Parameters:
--
-- [@ space_id :: 'HId_t' @]    ID of dataspace object to query
--
-- > htri_t H5Sis_simple(hid_t space_id);
foreign import ccall "H5Sis_simple" h5s_is_simple
  :: HId_t -> IO HTri_t
foreign import ccall "&H5Sis_simple" p_H5Sis_simple
  :: FunPtr (HId_t -> IO HTri_t)

{-# LINE 208 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Returns the number of elements in current selection for dataspace.
--
-- Parameters:
-- [@ dsid :: 'HId_t' @]    Dataspace ID of selection to query
--
-- Returns non-negative on success, negative on failure.
--
-- > hssize_t H5Sget_select_npoints(hid_t spaceid);
foreign import ccall "H5Sget_select_npoints" h5s_get_select_npoints
  :: HId_t -> IO HSSize_t
foreign import ccall "&H5Sget_select_npoints" p_H5Sget_select_npoints
  :: FunPtr (HId_t -> IO HSSize_t)

{-# LINE 218 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Combines a hyperslab selection with the current selection for a dataspace.
-- If the current selection is not a hyperslab, it is freed and the hyperslab
-- parameters passed in are combined with the 'h5s_SEL_ALL' hyperslab (ie. a
-- selection composing the entire current extent).  If 'stride' or 'block' is
-- NULL, they are assumed to be set to all '1'.
--
-- Parameters:
--
-- [@ dsid   :: 'HId_t'                   @]  Dataspace ID of selection to modify
--
-- [@ op     :: 'H5S_seloper_t'           @]  Operation to perform on current selection
--
-- [@ start  :: 'InArray' 'HSize_t'       @]  Offset of start of hyperslab
--
-- [@ stride :: 'InArray' 'HSize_t'       @]  Hyperslab stride
--
-- [@ count  :: 'InArray' 'HSize_t'       @]  Number of blocks included in hyperslab
--
-- [@ block  :: 'InArray' 'HSize_t'       @]  Size of block in hyperslab
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sselect_hyperslab(hid_t space_id, H5S_seloper_t op,
-- >        const hsize_t start[],
-- >        const hsize_t _stride[],
-- >        const hsize_t count[],
-- >        const hsize_t _block[]);
foreign import ccall "H5Sselect_hyperslab" h5s_select_hyperslab
  :: HId_t -> H5S_seloper_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> IO HErr_t
foreign import ccall "&H5Sselect_hyperslab" p_H5Sselect_hyperslab
  :: FunPtr (HId_t -> H5S_seloper_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> IO HErr_t)

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



{-# LINE 322 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |This function selects array elements to be included in the selection for
-- the dataspace.  The 'coord' array is a 2-D array of size \<dataspace rank\>
-- by 'num_elem' (ie. a list of coordinates in the dataspace).  The order of
-- the element coordinates in the 'coord' array specifies the order that the
-- array elements are iterated through when I/O is performed.  Duplicate
-- coordinates are not checked for.  The selection operator, 'op', determines
-- how the new selection is to be combined with the existing selection for
-- the dataspace.  Currently, only 'h5s_SELECT_SET' is supported, which replaces
-- the existing selection with the one defined in this call.  When operators
-- other than 'h5s_SELECT_SET' are used to combine a new selection with an
-- existing selection, the selection ordering is reset to 'C' array ordering.
--
-- Parameters:
--
-- [@ dsid     :: 'HId_t'             @]    Dataspace ID of selection to modify
--
-- [@ op       :: 'H5S_seloper_t'     @]    Operation to perform on current selection
--
-- [@ num_elem :: 'CSize'             @]    Number of elements in COORD array.
--
-- [@ coord    :: 'InArray' 'HSize_t' @]    The location of each element selected
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sselect_elements(hid_t space_id, H5S_seloper_t op,
-- >     size_t num_elem, const hsize_t *coord);
foreign import ccall "H5Sselect_elements" h5s_select_elements
  :: HId_t -> H5S_seloper_t -> CSize -> InArray HSize_t -> IO HErr_t
foreign import ccall "&H5Sselect_elements" p_H5Sselect_elements
  :: FunPtr (HId_t -> H5S_seloper_t -> CSize -> InArray HSize_t -> IO HErr_t)

{-# LINE 350 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Retrieves the type of extent for a dataspace object
--
-- Returns the class of the dataspace object on success, 'n5s_NO_CLASS'
-- on failure.
--
-- > H5S_class_t H5Sget_simple_extent_type(hid_t space_id);
foreign import ccall "H5Sget_simple_extent_type" h5s_get_simple_extent_type
  :: HId_t -> IO H5S_class_t
foreign import ccall "&H5Sget_simple_extent_type" p_H5Sget_simple_extent_type
  :: FunPtr (HId_t -> IO H5S_class_t)

{-# LINE 358 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Resets the extent of a dataspace back to \"none\"
--
-- This function resets the type of a dataspace back to \"none\" with no
-- extent information stored for the dataspace.
--
-- > herr_t H5Sset_extent_none(hid_t space_id);
foreign import ccall "H5Sset_extent_none" h5s_set_extent_none
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Sset_extent_none" p_H5Sset_extent_none
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 366 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |
-- > herr_t H5Sextent_copy(hid_t dst_id,hid_t src_id);
foreign import ccall "H5Sextent_copy" h5s_extent_copy
  :: HId_t -> HId_t -> IO HErr_t
foreign import ccall "&H5Sextent_copy" p_H5Sextent_copy
  :: FunPtr (HId_t -> HId_t -> IO HErr_t)

{-# LINE 370 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Determines if two dataspace extents are equal.
--
-- > htri_t H5Sextent_equal(hid_t sid1, hid_t sid2);
foreign import ccall "H5Sextent_equal" h5s_extent_equal
  :: HId_t -> HId_t -> IO HTri_t
foreign import ccall "&H5Sextent_equal" p_H5Sextent_equal
  :: FunPtr (HId_t -> HId_t -> IO HTri_t)

{-# LINE 375 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |This function selects the entire extent for a dataspace.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sselect_all(hid_t spaceid);
foreign import ccall "H5Sselect_all" h5s_select_all
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Sselect_all" p_H5Sselect_all
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 382 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |This function de-selects the entire extent for a dataspace.
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sselect_none(hid_t spaceid);
foreign import ccall "H5Sselect_none" h5s_select_none
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Sselect_none" p_H5Sselect_none
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 389 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Changes the offset of a selection within a simple dataspace extent
--
-- Parameters:
--
-- [@ space_id :: 'HId_t'              @]   Dataspace object to reset
--
-- [@ offset   :: 'InArray' 'HSsize_t' @]   Offset to position the selection at
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Soffset_simple(hid_t space_id, const hssize_t *offset);
foreign import ccall "H5Soffset_simple" h5s_offset_simple
  :: HId_t -> InArray HSSize_t -> IO HErr_t
foreign import ccall "&H5Soffset_simple" p_H5Soffset_simple
  :: FunPtr (HId_t -> InArray HSSize_t -> IO HErr_t)

{-# LINE 402 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Check whether the selection fits within the extent, with the current
-- offset defined.
--
-- Determines if the current selection at the current offet fits within the
-- extent for the dataspace.
--
-- > htri_t H5Sselect_valid(hid_t spaceid);
foreign import ccall "H5Sselect_valid" h5s_select_valid
  :: HId_t -> IO HTri_t
foreign import ccall "&H5Sselect_valid" p_H5Sselect_valid
  :: FunPtr (HId_t -> IO HTri_t)

{-# LINE 411 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- > htri_t H5Sis_regular_hyperslab(hid_t spaceid);
foreign import ccall "H5Sis_regular_hyperslab" h5s_is_regular_hyperslab
  :: HId_t -> IO HTri_t
foreign import ccall "&H5Sis_regular_hyperslab" p_H5Sis_regular_hyperslab
  :: FunPtr (HId_t -> IO HTri_t)

{-# LINE 414 "src/Bindings/HDF5/Raw/H5S.hsc" #-}
-- > htri_t H5Sget_regular_hyperslab(hid_t spaceid, hsize_t start[],
-- >     hsize_t stride[], hsize_t count[], hsize_t block[]);
foreign import ccall "H5Sget_regular_hyperslab" h5s_get_regular_hyperslab
  :: HId_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> IO HTri_t
foreign import ccall "&H5Sget_regular_hyperslab" p_H5Sget_regular_hyperslab
  :: FunPtr (HId_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> InArray HSize_t -> IO HTri_t)

{-# LINE 417 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Get the number of hyperslab blocks in current hyperslab selection
--
-- Returns negative on failure
--
-- > hssize_t H5Sget_select_hyper_nblocks(hid_t spaceid);
foreign import ccall "H5Sget_select_hyper_nblocks" h5s_get_select_hyper_nblocks
  :: HId_t -> IO HSSize_t
foreign import ccall "&H5Sget_select_hyper_nblocks" p_H5Sget_select_hyper_nblocks
  :: FunPtr (HId_t -> IO HSSize_t)

{-# LINE 424 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Get the number of points in current element selection
--
-- Returns negative on failure
--
-- > hssize_t H5Sget_select_elem_npoints(hid_t spaceid);
foreign import ccall "H5Sget_select_elem_npoints" h5s_get_select_elem_npoints
  :: HId_t -> IO HSSize_t
foreign import ccall "&H5Sget_select_elem_npoints" p_H5Sget_select_elem_npoints
  :: FunPtr (HId_t -> IO HSSize_t)

{-# LINE 431 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Puts a list of the hyperslab blocks into the user's buffer.  The blocks
-- start with the 'startblock'th block in the list of blocks and put
-- 'numblocks' number of blocks into the user's buffer (or until the end of
-- the list of blocks, whichever happen first)
--
-- The block coordinates have the same dimensionality (rank) as the
-- dataspace they are located within.  The list of blocks is formatted as
-- follows: \<\"start\" coordinate\> immediately followed by \<\"opposite\"
-- corner coordinate\>, followed by the next \"start\" and \"opposite\"
-- coordinate, etc.  until all the block information requested has been
-- put into the user's buffer.
--
-- No guarantee of any order of the blocks is implied.
--
-- Parameters:
--
-- [@ dsid       :: 'HId_t'               @]    Dataspace ID of selection to query
--
-- [@ startblock :: 'HSsize_t'            @]    Hyperslab block to start with
--
-- [@ numblocks  :: 'HSsize_t'            @]    Number of hyperslab blocks to get
--
-- [@ buf        :: 'OutArray' 'HSsize_t' @]    List of hyperslab blocks selected
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sget_select_hyper_blocklist(hid_t spaceid, hsize_t startblock,
-- >     hsize_t numblocks, hsize_t buf[/*numblocks*/]);
foreign import ccall "H5Sget_select_hyper_blocklist" h5s_get_select_hyper_blocklist
  :: HId_t -> HSize_t -> HSize_t -> OutArray HSize_t -> IO HErr_t
foreign import ccall "&H5Sget_select_hyper_blocklist" p_H5Sget_select_hyper_blocklist
  :: FunPtr (HId_t -> HSize_t -> HSize_t -> OutArray HSize_t -> IO HErr_t)

{-# LINE 461 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Puts a list of the element points into the user's buffer.  The points
-- start with the 'startpoint'th block in the list of points and put
-- 'numpoints' number of points into the user's buffer (or until the end of
-- the list of points, whichever happen first)
--
-- The point coordinates have the same dimensionality (rank) as the
-- dataspace they are located within.  The list of points is formatted as
-- follows: <coordinate> followed by the next coordinate, etc. until all the
-- point information in the selection have been put into the user's buffer.
--
-- The points are returned in the order they will be interated through
-- when a selection is read/written from/to disk.
--
-- Parameters:
--
-- [@ dsid       :: 'HId_t'   @]    Dataspace ID of selection to query
--
-- [@ startpoint :: 'HSize_t' @]    Element point to start with
--
-- [@ numpoints  :: 'HSize_t' @]    Number of element points to get
--
-- [@ buf        :: 'HSize_t' @]    List of element points selected
--
-- Returns non-negative on success, negative on failure.
--
-- > herr_t H5Sget_select_elem_pointlist(hid_t spaceid, hsize_t startpoint,
-- >     hsize_t numpoints, hsize_t buf[/*numpoints*/]);
foreign import ccall "H5Sget_select_elem_pointlist" h5s_get_select_elem_pointlist
  :: HId_t -> HSize_t -> HSize_t -> OutArray HSize_t -> IO HErr_t
foreign import ccall "&H5Sget_select_elem_pointlist" p_H5Sget_select_elem_pointlist
  :: FunPtr (HId_t -> HSize_t -> HSize_t -> OutArray HSize_t -> IO HErr_t)

{-# LINE 490 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- |Retrieves the bounding box containing the current selection and places
-- it into the user's buffers.  The start and end buffers must be large
-- enough to hold the dataspace rank number of coordinates.  The bounding box
-- exactly contains the selection, ie. if a 2-D element selection is currently
-- defined with the following points: (4,5), (6,8) (10,7), the bounding box
-- with be (4, 5), (10, 8).  Calling this function on a \"none\" selection
-- returns fail.
--
-- The bounding box calculations _does_ include the current offset of the
-- selection within the dataspace extent.
--
-- Parameters:
--
-- [@ dsid  :: 'HId_t'              @]  Dataspace ID of selection to query
--
-- [@ start :: 'OutArray' 'HSize_t' @]  Starting coordinate of bounding box
--
-- [@ end   :: 'OutArray' 'HSize_t' @]  Opposite coordinate of bounding box
--
-- Returns non-negative on success, negative on failure.
--
-- Weird warning in source: This routine participates in the
-- \"Inlining C function pointers\" pattern, don't call it directly,
-- use the appropriate macro defined in H5Sprivate.h.
--
-- > herr_t H5Sget_select_bounds(hid_t spaceid, hsize_t start[],
-- >     hsize_t end[]);
foreign import ccall "H5Sget_select_bounds" h5s_get_select_bounds
  :: HId_t -> OutArray HSize_t -> OutArray HSize_t -> IO HErr_t
foreign import ccall "&H5Sget_select_bounds" p_H5Sget_select_bounds
  :: FunPtr (HId_t -> OutArray HSize_t -> OutArray HSize_t -> IO HErr_t)

{-# LINE 519 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

-- H5S_sel_type H5Sget_select_type(hid_t spaceid);
foreign import ccall "H5Sget_select_type" h5s_get_select_type
  :: HId_t -> IO H5S_sel_type
foreign import ccall "&H5Sget_select_type" p_H5Sget_select_type
  :: FunPtr (HId_t -> IO H5S_sel_type)

{-# LINE 522 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

--------------------------
-- Compatibility Macros --
--------------------------


-- |Given a dataspace ID, converts the object description
-- (including selection) into binary in a buffer.
--
-- 'nalloc' is the size of the buffer on input, the size of the encoded
-- data on output.  If the buffer is not big enough, no data is written
-- to it (but nalloc is still updated with the size needed).
--
-- Returns non-negative on success, negative on failure.
--


{-# LINE 539 "src/Bindings/HDF5/Raw/H5S.hsc" #-}
foreign import ccall "H5Sencode1" h5s_encode1
  :: HId_t -> OutArray CChar -> InOut CSize -> IO HErr_t
foreign import ccall "&H5Sencode1" p_H5Sencode1
  :: FunPtr (HId_t -> OutArray CChar -> InOut CSize -> IO HErr_t)

{-# LINE 540 "src/Bindings/HDF5/Raw/H5S.hsc" #-}
foreign import ccall "H5Sencode2" h5s_encode2
  :: HId_t -> OutArray CChar -> InOut CSize -> HId_t -> IO HErr_t
foreign import ccall "&H5Sencode2" p_H5Sencode2
  :: FunPtr (HId_t -> OutArray CChar -> InOut CSize -> HId_t -> IO HErr_t)

{-# LINE 541 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

{-# LINE 542 "src/Bindings/HDF5/Raw/H5S.hsc" #-}
h5s_encode :: HId_t -> OutArray CChar -> InOut CSize -> IO HErr_t
h5s_encode = h5s_encode1

{-# LINE 550 "src/Bindings/HDF5/Raw/H5S.hsc" #-}

{-# LINE 555 "src/Bindings/HDF5/Raw/H5S.hsc" #-}