{-# LINE 1 "src/Bindings/HDF5/Raw/H5FD/Log.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).
--     With custom modifications...
module Bindings.HDF5.Raw.H5FD.Log where

import Foreign.C.String
import Foreign.C.Types
import Foreign.Ptr
import System.IO.Unsafe (unsafePerformIO)

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

h5fd_LOG
{-# LINE 22 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
  :: HId_t
h5fd_LOG :: HId_t
h5fd_LOG
{-# LINE 24 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
    = unsafePerformIO (h5fd_log_init)
{-# LINE 25 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}

-- * Flags for 'h5p_set_fapl_log'

-- ** Flags for tracking where reads/writes/seeks occur
h5fd_LOG_LOC_READ :: forall a. Num a => a
h5fd_LOG_LOC_READ = a
2
h5fd_LOG_LOC_READ :: (Num a) => a

{-# LINE 30 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_LOC_WRITE = 4
h5fd_LOG_LOC_WRITE :: (Num a) => a

{-# LINE 31 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_LOC_SEEK = 8
h5fd_LOG_LOC_SEEK :: (Num a) => a

{-# LINE 32 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_LOC_IO = 14
h5fd_LOG_LOC_IO :: (Num a) => a

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

-- ** Flags for tracking number of times each byte is read/written
h5fd_LOG_FILE_READ = 16
h5fd_LOG_FILE_READ :: (Num a) => a

{-# LINE 36 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_FILE_WRITE = 32
h5fd_LOG_FILE_WRITE :: (Num a) => a

{-# LINE 37 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_FILE_IO = 48
h5fd_LOG_FILE_IO :: (Num a) => a

{-# LINE 38 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}

-- ** Flag for tracking "flavor" (type) of information stored at each byte */
h5fd_LOG_FLAVOR = 64
h5fd_LOG_FLAVOR :: (Num a) => a

{-# LINE 41 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}

-- ** Flags for tracking total number of reads/writes/seeks */
h5fd_LOG_NUM_READ = 128
h5fd_LOG_NUM_READ :: (Num a) => a

{-# LINE 44 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_NUM_WRITE = 256
h5fd_LOG_NUM_WRITE :: (Num a) => a

{-# LINE 45 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_NUM_SEEK = 512
h5fd_LOG_NUM_SEEK :: (Num a) => a

{-# LINE 46 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_NUM_IO = 1920
h5fd_LOG_NUM_IO :: (Num a) => a

{-# LINE 47 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}

-- ** Flags for tracking time spent in open/read/write/seek/close */
h5fd_LOG_TIME_OPEN = 2048
h5fd_LOG_TIME_READ :: forall a. Num a => a
h5fd_LOG_TIME_OPEN :: (Num a) => a

{-# LINE 50 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_TIME_READ = 8192
h5fd_LOG_TIME_READ :: (Num a) => a

{-# LINE 51 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_TIME_WRITE = 16384
h5fd_LOG_TIME_WRITE :: (Num a) => a

{-# LINE 52 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_TIME_SEEK = 32768
h5fd_LOG_TIME_SEEK :: (Num a) => a

{-# LINE 53 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_TIME_CLOSE = 131072
h5fd_LOG_TIME_CLOSE :: (Num a) => a

{-# LINE 54 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_TIME_IO = 260096
h5fd_LOG_TIME_IO :: (Num a) => a

{-# LINE 55 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}

-- ** Flag for tracking allocation of space in file */
h5fd_LOG_ALLOC = 262144
h5fd_LOG_ALLOC :: (Num a) => a

{-# LINE 58 "src/Bindings/HDF5/Raw/H5FD/Log.hsc" #-}
h5fd_LOG_ALL = 1048575
h5fd_LOG_ALL :: (Num a) => a

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

-- * Functions

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

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


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

-- TODO: evaluate the claim that "There are no driver-specific properties."  It appears to be patently false.
-- |Modify the file access property list to use the H5FD_LOG
-- driver.  There are no driver-specific properties.
--
-- > herr_t H5Pset_fapl_log(hid_t fapl_id, const char *logfile, unsigned flags, size_t buf_size);
foreign import ccall "H5Pset_fapl_log" h5p_set_fapl_log
  :: HId_t -> CString -> CUInt -> CSize -> IO HErr_t
foreign import ccall "&H5Pset_fapl_log" p_H5Pset_fapl_log
  :: FunPtr (HId_t -> CString -> CUInt -> CSize -> IO HErr_t)

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