{-# LINE 1 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
module Bindings.HDF5.Raw.H5C where



import Data.Word
import Foreign.Storable


newtype H5C_cache_incr_mode = H5C_cache_incr_mode Word32 deriving (Ptr H5C_cache_incr_mode -> IO H5C_cache_incr_mode
Ptr H5C_cache_incr_mode -> Int -> IO H5C_cache_incr_mode
Ptr H5C_cache_incr_mode -> Int -> H5C_cache_incr_mode -> IO ()
Ptr H5C_cache_incr_mode -> H5C_cache_incr_mode -> IO ()
H5C_cache_incr_mode -> Int
(H5C_cache_incr_mode -> Int)
-> (H5C_cache_incr_mode -> Int)
-> (Ptr H5C_cache_incr_mode -> Int -> IO H5C_cache_incr_mode)
-> (Ptr H5C_cache_incr_mode -> Int -> H5C_cache_incr_mode -> IO ())
-> (forall b. Ptr b -> Int -> IO H5C_cache_incr_mode)
-> (forall b. Ptr b -> Int -> H5C_cache_incr_mode -> IO ())
-> (Ptr H5C_cache_incr_mode -> IO H5C_cache_incr_mode)
-> (Ptr H5C_cache_incr_mode -> H5C_cache_incr_mode -> IO ())
-> Storable H5C_cache_incr_mode
forall b. Ptr b -> Int -> IO H5C_cache_incr_mode
forall b. Ptr b -> Int -> H5C_cache_incr_mode -> 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 :: H5C_cache_incr_mode -> Int
sizeOf :: H5C_cache_incr_mode -> Int
$calignment :: H5C_cache_incr_mode -> Int
alignment :: H5C_cache_incr_mode -> Int
$cpeekElemOff :: Ptr H5C_cache_incr_mode -> Int -> IO H5C_cache_incr_mode
peekElemOff :: Ptr H5C_cache_incr_mode -> Int -> IO H5C_cache_incr_mode
$cpokeElemOff :: Ptr H5C_cache_incr_mode -> Int -> H5C_cache_incr_mode -> IO ()
pokeElemOff :: Ptr H5C_cache_incr_mode -> Int -> H5C_cache_incr_mode -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO H5C_cache_incr_mode
peekByteOff :: forall b. Ptr b -> Int -> IO H5C_cache_incr_mode
$cpokeByteOff :: forall b. Ptr b -> Int -> H5C_cache_incr_mode -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> H5C_cache_incr_mode -> IO ()
$cpeek :: Ptr H5C_cache_incr_mode -> IO H5C_cache_incr_mode
peek :: Ptr H5C_cache_incr_mode -> IO H5C_cache_incr_mode
$cpoke :: Ptr H5C_cache_incr_mode -> H5C_cache_incr_mode -> IO ()
poke :: Ptr H5C_cache_incr_mode -> H5C_cache_incr_mode -> IO ()
Storable, Int -> H5C_cache_incr_mode -> ShowS
[H5C_cache_incr_mode] -> ShowS
H5C_cache_incr_mode -> String
(Int -> H5C_cache_incr_mode -> ShowS)
-> (H5C_cache_incr_mode -> String)
-> ([H5C_cache_incr_mode] -> ShowS)
-> Show H5C_cache_incr_mode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5C_cache_incr_mode -> ShowS
showsPrec :: Int -> H5C_cache_incr_mode -> ShowS
$cshow :: H5C_cache_incr_mode -> String
show :: H5C_cache_incr_mode -> String
$cshowList :: [H5C_cache_incr_mode] -> ShowS
showList :: [H5C_cache_incr_mode] -> ShowS
Show, H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool
(H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool)
-> (H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool)
-> Eq H5C_cache_incr_mode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool
== :: H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool
$c/= :: H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool
/= :: H5C_cache_incr_mode -> H5C_cache_incr_mode -> Bool
Eq)

{-# LINE 10 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_incr__off :: H5C_cache_incr_mode
h5c_incr__off = H5C_cache_incr_mode (0)

{-# LINE 11 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_incr__threshold :: H5C_cache_incr_mode
h5c_incr__threshold = H5C_cache_incr_mode (1)

{-# LINE 12 "src/Bindings/HDF5/Raw/H5C.hsc" #-}


newtype H5C_cache_flash_incr_mode = H5C_cache_flash_incr_mode Word32 deriving (Storable, Show, Eq)

{-# LINE 15 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_flash_incr__off :: H5C_cache_flash_incr_mode
h5c_flash_incr__off = H5C_cache_flash_incr_mode (0)

{-# LINE 16 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_flash_incr__add_space :: H5C_cache_flash_incr_mode
h5c_flash_incr__add_space = H5C_cache_flash_incr_mode (1)

{-# LINE 17 "src/Bindings/HDF5/Raw/H5C.hsc" #-}


newtype H5C_cache_decr_mode = H5C_cache_decr_mode Word32 deriving (Storable, Show, Eq)

{-# LINE 20 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_decr__off :: H5C_cache_decr_mode
h5c_decr__off = H5C_cache_decr_mode (0)

{-# LINE 21 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_decr__threshold :: H5C_cache_decr_mode
h5c_decr__threshold = H5C_cache_decr_mode (1)

{-# LINE 22 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_decr__age_out :: H5C_cache_decr_mode
h5c_decr__age_out = H5C_cache_decr_mode (2)

{-# LINE 23 "src/Bindings/HDF5/Raw/H5C.hsc" #-}
h5c_decr__age_out_with_threshold :: H5C_cache_decr_mode
h5c_decr__age_out_with_threshold = H5C_cache_decr_mode (3)

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