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



-- |The POSIX unbuffered file driver using only the HDF5 public
-- API and with a few optimizations: the lseek() call is made
-- only when the current file position is unknown or needs to be
-- changed based on previous I/O through this driver (don't mix
-- I/O from this driver with I/O from other parts of the
-- application to the same file).
module Bindings.HDF5.Raw.H5FD.Sec2 where

import Foreign.Ptr
import System.IO.Unsafe (unsafePerformIO)

import Bindings.HDF5.Raw.H5
import Bindings.HDF5.Raw.H5I

h5fd_SEC2
{-# LINE 19 "src/Bindings/HDF5/Raw/H5FD/Sec2.hsc" #-}
  :: HId_t
h5fd_SEC2 :: HId_t
h5fd_SEC2
{-# LINE 21 "src/Bindings/HDF5/Raw/H5FD/Sec2.hsc" #-}
    = unsafePerformIO (h5fd_sec2_init)
{-# LINE 22 "src/Bindings/HDF5/Raw/H5FD/Sec2.hsc" #-}

-- |Initialize this driver by registering the driver with the library.
--
-- > hid_t H5FD_sec2_init(void);
foreign import ccall "H5FD_sec2_init" h5fd_sec2_init
  :: IO HId_t
foreign import ccall "&H5FD_sec2_init" p_H5FD_sec2_init
  :: FunPtr (IO HId_t)

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


{-# LINE 34 "src/Bindings/HDF5/Raw/H5FD/Sec2.hsc" #-}
 
-- |Modify the file access property list to use the H5FD_SEC2
-- driver.  There are no driver-specific properties.
--
-- > herr_t H5Pset_fapl_sec2(hid_t fapl_id);
foreign import ccall "H5Pset_fapl_sec2" h5p_set_fapl_sec2
  :: HId_t -> IO HErr_t
foreign import ccall "&H5Pset_fapl_sec2" p_H5Pset_fapl_sec2
  :: FunPtr (HId_t -> IO HErr_t)

{-# LINE 40 "src/Bindings/HDF5/Raw/H5FD/Sec2.hsc" #-}