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



import Foreign.C.Types
import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable

import Bindings.HDF5.Raw.H5
import Bindings.HDF5.Raw.H5C

-- |'H5AC_cache_config_t' is a public structure intended for use in public APIs.
-- At least in its initial incarnation, it is basicaly a copy of struct
-- 'H5C_auto_size_ctl_t', minus the 'report_fcn' field, and plus the
-- 'dirty_bytes_threshold' field.
--
-- The 'report_fcn' field is omitted, as including it would require us to
-- make 'H5C_t' structure public.
--
-- The 'dirty_bytes_threshold' field does not appear in 'H5C_auto_size_ctl_t',
-- as synchronization between caches on different processes is handled at
-- the H5AC level, not at the level of H5C.  Note however that there is
-- considerable interaction between this value and the other fields in this
-- structure.
--
-- Similarly, the 'open_trace_file', 'close_trace_file', and 'trace_file_name'
-- fields do not appear in 'H5C_auto_size_ctl_t', as most trace file
-- issues are handled at the H5AC level.  The one exception is storage of
-- the pointer to the trace file, which is handled by H5C.
--
-- The structure is in H5ACpublic.h as we may wish to allow different
-- configuration options for metadata and raw data caches.
--
-- The fields of the structure are discussed individually below.
--

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

-- |Integer field containing the version number of this version
-- of the H5AC_cache_config_t structure.  Any instance of
-- H5AC_cache_config_t passed to the cache must have a known
-- version number, or an error will be flagged.

{-# LINE 44 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Boolean field used to enable and disable the default
-- reporting function.  This function is invoked every time the
-- automatic cache resize code is run, and reports on its activities.
--
-- This is a debugging function, and should normally be turned off.

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

-- |Boolean field indicating whether the trace_file_name
-- field should be used to open a trace file for the cache.
--
-- The trace file is a debuging feature that allow the capture of
-- top level metadata cache requests for purposes of debugging and/or
-- optimization.  This field should normally be set to FALSE, as
-- trace file collection imposes considerable overhead.
--
-- This field should only be set to TRUE when the trace_file_name
-- contains the full path of the desired trace file, and either
-- there is no open trace file on the cache, or the close_trace_file
-- field is also TRUE.

{-# LINE 65 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Boolean field indicating whether the current trace
-- file (if any) should be closed.
--
-- See the above comments on the open_trace_file field.  This field
-- should be set to FALSE unless there is an open trace file on the
-- cache that you wish to close.

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

-- |Full path of the trace file to be opened if the 'open_trace_file' field is TRUE.
--
-- In the parallel case, an ascii representation of the mpi rank of
-- the process will be appended to the file name to yield a unique
-- trace file name for each process.
--
-- The length of the path must not exceed 'h5ac__MAX_TRACE_FILE_NAME_LEN'
-- characters.

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

-- |Boolean field used to either report the current
-- evictions enabled status of the cache, or to set the cache's
-- evictions enabled status.
--
-- In general, the metadata cache should always be allowed to
-- evict entries.  However, in some cases it is advantageous to
-- disable evictions briefly, and thereby postpone metadata
-- writes.  However, this must be done with care, as the cache
-- can grow quickly.  If you do this, re-enable evictions as
-- soon as possible and monitor cache size.
--
-- At present, evictions can only be disabled if automatic
-- cache resizing is also disabled (that is, @( 'incr_mode' ==
-- 'h5c_incr__off' ) && ( 'decr_mode' == 'h5c_decr__off' )@).  There
-- is no logical reason why this should be so, but it simplifies
-- implementation and testing, and I can't think of any reason
-- why it would be desireable.  If you can think of one, I'll
-- revisit the issue.

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

-- |Boolean flag indicating whether the size of the
-- initial size of the cache is to be set to the value given in
-- the initial_size field.  If 'set_initial_size' is FALSE, the
-- 'initial_size' field is ignored.

{-# LINE 109 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |If enabled, this field contain the size the cache is
-- to be set to upon receipt of this structure.  Needless to say,
-- 'initial_size' must lie in the closed interval @['min_size' .. 'max_size']@.

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

-- |double in the range 0 to 1 indicating the fraction
-- of the cache that is to be kept clean.  This field is only used
-- in parallel mode.  Typical values are 0.1 to 0.5.

{-# LINE 119 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- TODO: figure out where MIN_MAX_CACHE_SIZE and MAX_MAX_CACHE_SIZE come from.  They don't seem to be in any public headers
-- |Maximum size to which the cache can be adjusted.  The
-- supplied value must fall in the closed interval
-- @['MIN_MAX_CACHE_SIZE' .. 'MAX_MAX_CACHE_SIZE']@.  Also, 'max_size' must
-- be greater than or equal to 'min_size'.

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

-- TODO: figure out where H5C__MIN_MAX_CACHE_SIZE and H5C__MAX_MAX_CACHE_SIZE come from.  They don't seem to be in any public headers
-- |Minimum size to which the cache can be adjusted.  The
-- supplied value must fall in the closed interval
-- @['H5C__MIN_MAX_CACHE_SIZE' .. 'H5C__MAX_MAX_CACHE_SIZE']@.  Also, 'min_size'
-- must be less than or equal to 'max_size'.

{-# LINE 133 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- TODO: figure out where H5C__MIN_AR_EPOCH_LENGTH and H5C__MAX_AR_EPOCH_LENGTH come from.  They don't seem to be in any public headers
-- |Number of accesses on the cache over which to collect
-- hit rate stats before running the automatic cache resize code,
-- if it is enabled.
--
-- At the end of an epoch, we discard prior hit rate data and start
-- collecting afresh.  The epoch_length must lie in the closed
-- interval @['H5C__MIN_AR_EPOCH_LENGTH' .. 'H5C__MAX_AR_EPOCH_LENGTH']@.

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

-- |Instance of the 'H5C_cache_incr_mode' enumerated type whose
-- value indicates how we determine whether the cache size should be
-- increased.  At present there are two possible values:
--
-- * 'h5c_incr__off':
--         Don't attempt to increase the size of the cache
--         automatically.
--         When this increment mode is selected, the remaining fields
--         in the cache size increase section ar ignored.
--
-- * 'h5c_incr__threshold':
--         Attempt to increase the size of the cache
--         whenever the average hit rate over the last epoch drops
--         below the value supplied in the lower_hr_threshold
--         field.
--         Note that this attempt will fail if the cache is already
--         at its maximum size, or if the cache is not already using
--         all available space.
--
-- Note that you must set 'decr_mode' to 'h5c_incr__off' if you
-- disable metadata cache entry evictions.

{-# LINE 166 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Lower hit rate threshold.  If the increment mode
-- ('incr_mode') is 'h5c_incr__threshold' and the hit rate drops below the
-- value supplied in this field in an epoch, increment the cache size by
-- 'size_increment'.  Note that cache size may not be incremented above
-- 'max_size', and that the increment may be further restricted by the
-- 'max_increment' field if it is enabled.
--
-- When enabled, this field must contain a value in the range [0.0, 1.0].
-- Depending on the 'incr_mode' selected, it may also have to be less than
-- 'upper_hr_threshold'.

{-# LINE 178 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Double containing the multiplier used to derive the new
-- cache size from the old if a cache size increment is triggered.
-- The increment must be greater than 1.0, and should not exceed 2.0.
--
-- The new cache size is obtained my multiplying the current max cache
-- size by the increment, and then clamping to max_size and to stay
-- within the max_increment as necessary.

{-# LINE 187 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Boolean flag indicating whether the max_increment
-- field should be used to limit the maximum cache size increment.

{-# LINE 191 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |If enabled by the 'apply_max_increment' field described
-- above, this field contains the maximum number of bytes by which the
-- cache size can be increased in a single re-size.

{-# LINE 196 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Instance of the 'H5C_cache_flash_incr_mode' enumerated
-- type whose value indicates whether and by which algorithm we should
-- make flash increases in the size of the cache to accomodate insertion
-- of large entries and large increases in the size of a single entry.
--
-- The addition of the flash increment mode was occasioned by performance
-- problems that appear when a local heap is increased to a size in excess
-- of the current cache size.  While the existing re-size code dealt with
-- this eventually, performance was very bad for the remainder of the
-- epoch.
--
-- At present, there are two possible values for the 'flash_incr_mode':
--
-- * 'h5c_flash_incr__off':  Don't perform flash increases in the size of
--         the cache.
--
-- * 'h5c_flash_incr__add_space':  Let @x@ be either the size of a newly
--         newly inserted entry, or the number of bytes by which the
--         size of an existing entry has been increased.
--         If @x > flash_threshold * current max cache size@,
--         increase the current maximum cache size by @x * flash_multiple@
--         less any free space in the cache, and start a new epoch.  For
--         now at least, pay no attention to the maximum increment.
--
-- In both of the above cases, the flash increment pays no attention to
-- the maximum increment (at least in this first incarnation), but DOES
-- stay within 'max_size'.
--
-- With a little thought, it should be obvious that the above flash
-- cache size increase algorithm is not sufficient for all circumstances.
-- For example, suppose the user round robins through
-- @(1/flash_threshold) + 1@ groups, adding one data set to each on each
-- pass.  Then all will increase in size at about the same time, requiring
-- the max cache size to at least double to maintain acceptable
-- performance, however the above flash increment algorithm will not be
-- triggered.
--
-- Hopefully, the add space algorithms detailed above will be sufficient
-- for the performance problems encountered to date.  However, we should
-- expect to revisit the issue.

{-# LINE 238 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Double containing the multiple described above in the
-- 'h5c_flash_incr__add_space' section of the discussion of the
-- 'flash_incr_mode' section.  This field is ignored unless 'flash_incr_mode'
-- is 'h5c_flash_incr__add_space'.

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

-- |Double containing the factor by which current max cache
-- size is multiplied to obtain the size threshold for the 'add_space' flash
-- increment algorithm.  The field is ignored unless 'flash_incr_mode' is
-- 'h5c_flash_incr__add_space'.

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

-- |Instance of the 'H5C_cache_decr_mode' enumerated type whose
-- value indicates how we determine whether the cache size should be
-- decreased.  At present there are four possibilities.
--
-- * 'h5c_decr__off':  Don't attempt to decrease the size of the cache
--         automatically. When this increment mode is selected, the remaining
--         fields in the cache size decrease section are ignored.
--
-- * 'h5c_decr__threshold': Attempt to decrease the size of the cache
--         whenever the average hit rate over the last epoch rises
--         above the value supplied in the upper_hr_threshold
--         field.
--
-- * 'h5c_decr__age_out':  At the end of each epoch, search the cache for
--         entries that have not been accessed for at least the number
--         of epochs specified in the 'epochs_before_eviction' field, and
--         evict these entries.  Conceptually, the maximum cache size
--         is then decreased to match the new actual cache size.  However,
--         this reduction may be modified by the 'min_size', the
--         'max_decrement', and/or the 'empty_reserve'.
--
-- * 'h5c_decr__age_out_with_threshold':  Same as 'age_out', but we only
--         attempt to reduce the cache size when the hit rate observed
--         over the last epoch exceeds the value provided in the
--         'upper_hr_threshold' field.
--
-- Note that you must set 'decr_mode' to 'h5c_decr__off' if you
-- disable metadata cache entry evictions.

{-# LINE 280 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Upper hit rate threshold.  The use of this field varies according to
-- the current 'decr_mode':
--
-- * 'h5c_decr__off' or 'h5c_decr__age_out':  The value of this field is
--         ignored.
--
-- * 'h5c_decr__threshold':  If the hit rate exceeds this threshold in any
--         epoch, attempt to decrement the cache size by 'size_decrement'.
--
--         Note that cache size may not be decremented below 'min_size'.
--
--         Note also that if the 'upper_threshold' is 1.0, the cache size
--         will never be reduced.
--
-- * 'h5c_decr__age_out_with_threshold':  If the hit rate exceeds this
--         threshold in any epoch, attempt to reduce the cache size
--         by evicting entries that have not been accessed for more
--         than the specified number of epochs.

{-# LINE 300 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |This field is only used when the decr_mode is 'h5c_decr__threshold'.
--
-- The field is a double containing the multiplier used to derive the
-- new cache size from the old if a cache size decrement is triggered.
-- The decrement must be in the range 0.0 (in which case the cache will
-- try to contract to its minimum size) to 1.0 (in which case the
-- cache will never shrink).

{-# LINE 309 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Boolean flag used to determine whether decrements
-- in cache size are to be limited by the 'max_decrement' field.

{-# LINE 313 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Maximum number of bytes by which the cache size can be
-- decreased in a single re-size.  Note that decrements may also be
-- restricted by the min_size of the cache, and (in age out modes) by
-- the 'empty_reserve' field.

{-# LINE 319 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- TODO: figure out where H5C__MAX_EPOCH_MARKERS comes from
-- |Integer field used in H5C_decr__age_out and
-- 'h5c_decr__age_out_with_threshold' decrement modes.
--
-- This field contains the number of epochs an entry must remain
-- unaccessed before it is evicted in an attempt to reduce the
-- cache size.  If applicable, this field must lie in the range
-- @[1 .. 'H5C__MAX_EPOCH_MARKERS']@.

{-# LINE 329 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Boolean field controlling whether the 'empty_reserve'
-- field is to be used in computing the new cache size when the
-- 'decr_mode' is 'h5c_decr__age_out' or 'h5c_decr__age_out_with_threshold'.

{-# LINE 334 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |To avoid a constant racheting down of cache size by small
-- amounts in the 'h5c_decr__age_out' and 'h5c_decr__age_out_with_threshold'
-- modes, this field allows one to require that any cache size
-- reductions leave the specified fraction of unused space in the cache.
--
-- The value of this field must be in the range [0.0, 1.0].  I would
-- expect typical values to be in the range of 0.01 to 0.1.

{-# LINE 343 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Threshold of dirty byte creation used to
-- synchronize updates between caches. (See above for outline and
-- motivation.)
--
-- This value MUST be consistant across all processes accessing the
-- file.  This field is ignored unless HDF5 has been compiled for
-- parallel.

{-# LINE 352 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |Integer field containing a code indicating the
-- desired metadata write strategy.  The valid values of this field
-- are enumerated and discussed below:

{-# LINE 357 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

data H5AC_cache_config_t = H5AC_cache_config_t{
  H5AC_cache_config_t -> CInt
h5ac_cache_config_t'version :: CInt,
  h5ac_cache_config_t'rpt_fcn_enabled :: HBool_t,
  h5ac_cache_config_t'open_trace_file :: HBool_t,
  h5ac_cache_config_t'close_trace_file :: HBool_t,
  h5ac_cache_config_t'trace_file_name :: [CChar],
  h5ac_cache_config_t'evictions_enabled :: HBool_t,
  h5ac_cache_config_t'set_initial_size :: HBool_t,
  h5ac_cache_config_t'initial_size :: CSize,
  h5ac_cache_config_t'min_clean_fraction :: CDouble,
  h5ac_cache_config_t'max_size :: CSize,
  h5ac_cache_config_t'min_size :: CSize,
  h5ac_cache_config_t'epoch_length :: CLong,
  h5ac_cache_config_t'incr_mode :: H5C_cache_incr_mode,
  h5ac_cache_config_t'lower_hr_threshold :: CDouble,
  h5ac_cache_config_t'increment :: CDouble,
  h5ac_cache_config_t'apply_max_increment :: HBool_t,
  h5ac_cache_config_t'max_increment :: CSize,
  h5ac_cache_config_t'flash_incr_mode :: H5C_cache_flash_incr_mode,
  h5ac_cache_config_t'flash_multiple :: CDouble,
  h5ac_cache_config_t'flash_threshold :: CDouble,
  h5ac_cache_config_t'decr_mode :: H5C_cache_decr_mode,
  H5AC_cache_config_t -> CDouble
h5ac_cache_config_t'upper_hr_threshold :: CDouble,
  H5AC_cache_config_t -> CDouble
h5ac_cache_config_t'decrement :: CDouble,
  H5AC_cache_config_t -> HBool_t
h5ac_cache_config_t'apply_max_decrement :: HBool_t,
  H5AC_cache_config_t -> CSize
h5ac_cache_config_t'max_decrement :: CSize,
  H5AC_cache_config_t -> CInt
h5ac_cache_config_t'epochs_before_eviction :: CInt,
  H5AC_cache_config_t -> HBool_t
h5ac_cache_config_t'apply_empty_reserve :: HBool_t,
  H5AC_cache_config_t -> CDouble
h5ac_cache_config_t'empty_reserve :: CDouble,
  H5AC_cache_config_t -> CSize
h5ac_cache_config_t'dirty_bytes_threshold :: CSize,
  H5AC_cache_config_t -> CInt
h5ac_cache_config_t'metadata_write_strategy :: CInt
} deriving (H5AC_cache_config_t -> H5AC_cache_config_t -> Bool
(H5AC_cache_config_t -> H5AC_cache_config_t -> Bool)
-> (H5AC_cache_config_t -> H5AC_cache_config_t -> Bool)
-> Eq H5AC_cache_config_t
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: H5AC_cache_config_t -> H5AC_cache_config_t -> Bool
== :: H5AC_cache_config_t -> H5AC_cache_config_t -> Bool
$c/= :: H5AC_cache_config_t -> H5AC_cache_config_t -> Bool
/= :: H5AC_cache_config_t -> H5AC_cache_config_t -> Bool
Eq,Int -> H5AC_cache_config_t -> ShowS
[H5AC_cache_config_t] -> ShowS
H5AC_cache_config_t -> String
(Int -> H5AC_cache_config_t -> ShowS)
-> (H5AC_cache_config_t -> String)
-> ([H5AC_cache_config_t] -> ShowS)
-> Show H5AC_cache_config_t
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> H5AC_cache_config_t -> ShowS
showsPrec :: Int -> H5AC_cache_config_t -> ShowS
$cshow :: H5AC_cache_config_t -> String
show :: H5AC_cache_config_t -> String
$cshowList :: [H5AC_cache_config_t] -> ShowS
showList :: [H5AC_cache_config_t] -> ShowS
Show)
p'H5AC_cache_config_t'version :: Ptr H5AC_cache_config_t -> Ptr CInt
p'H5AC_cache_config_t'version Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
0
p'H5AC_cache_config_t'version :: Ptr (H5AC_cache_config_t) -> Ptr (CInt)
p'H5AC_cache_config_t'rpt_fcn_enabled :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'rpt_fcn_enabled Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
4
p'H5AC_cache_config_t'rpt_fcn_enabled :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'open_trace_file :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'open_trace_file Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
5
p'H5AC_cache_config_t'open_trace_file :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'close_trace_file :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'close_trace_file Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
6
p'H5AC_cache_config_t'close_trace_file :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'trace_file_name :: Ptr H5AC_cache_config_t -> Ptr CChar
p'H5AC_cache_config_t'trace_file_name Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
7
p'H5AC_cache_config_t'trace_file_name :: Ptr (H5AC_cache_config_t) -> Ptr (CChar)
p'H5AC_cache_config_t'evictions_enabled :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'evictions_enabled Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1032
p'H5AC_cache_config_t'evictions_enabled :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'set_initial_size :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'set_initial_size Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1033
p'H5AC_cache_config_t'set_initial_size :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'initial_size :: Ptr H5AC_cache_config_t -> Ptr CSize
p'H5AC_cache_config_t'initial_size Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1040
p'H5AC_cache_config_t'initial_size :: Ptr (H5AC_cache_config_t) -> Ptr (CSize)
p'H5AC_cache_config_t'min_clean_fraction :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'min_clean_fraction Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1048
p'H5AC_cache_config_t'min_clean_fraction :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'max_size :: Ptr H5AC_cache_config_t -> Ptr CSize
p'H5AC_cache_config_t'max_size Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1056
p'H5AC_cache_config_t'max_size :: Ptr (H5AC_cache_config_t) -> Ptr (CSize)
p'H5AC_cache_config_t'min_size :: Ptr H5AC_cache_config_t -> Ptr CSize
p'H5AC_cache_config_t'min_size Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1064
p'H5AC_cache_config_t'min_size :: Ptr (H5AC_cache_config_t) -> Ptr (CSize)
p'H5AC_cache_config_t'epoch_length :: Ptr H5AC_cache_config_t -> Ptr CLong
p'H5AC_cache_config_t'epoch_length Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CLong
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1072
p'H5AC_cache_config_t'epoch_length :: Ptr (H5AC_cache_config_t) -> Ptr (CLong)
p'H5AC_cache_config_t'incr_mode :: Ptr H5AC_cache_config_t -> Ptr H5C_cache_incr_mode
p'H5AC_cache_config_t'incr_mode Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr H5C_cache_incr_mode
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1080
p'H5AC_cache_config_t'incr_mode :: Ptr (H5AC_cache_config_t) -> Ptr (H5C_cache_incr_mode)
p'H5AC_cache_config_t'lower_hr_threshold :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'lower_hr_threshold Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1088
p'H5AC_cache_config_t'lower_hr_threshold :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'increment :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'increment Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1096
p'H5AC_cache_config_t'increment :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'apply_max_increment :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'apply_max_increment Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1104
p'H5AC_cache_config_t'apply_max_increment :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'max_increment :: Ptr H5AC_cache_config_t -> Ptr CSize
p'H5AC_cache_config_t'max_increment Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1112
p'H5AC_cache_config_t'max_increment :: Ptr (H5AC_cache_config_t) -> Ptr (CSize)
p'H5AC_cache_config_t'flash_incr_mode :: Ptr H5AC_cache_config_t -> Ptr H5C_cache_flash_incr_mode
p'H5AC_cache_config_t'flash_incr_mode Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr H5C_cache_flash_incr_mode
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1120
p'H5AC_cache_config_t'flash_incr_mode :: Ptr (H5AC_cache_config_t) -> Ptr (H5C_cache_flash_incr_mode)
p'H5AC_cache_config_t'flash_multiple :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'flash_multiple Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1128
p'H5AC_cache_config_t'flash_multiple :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'flash_threshold :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'flash_threshold Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1136
p'H5AC_cache_config_t'flash_threshold :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'decr_mode :: Ptr H5AC_cache_config_t -> Ptr H5C_cache_decr_mode
p'H5AC_cache_config_t'decr_mode Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr H5C_cache_decr_mode
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1144
p'H5AC_cache_config_t'decr_mode :: Ptr (H5AC_cache_config_t) -> Ptr (H5C_cache_decr_mode)
p'H5AC_cache_config_t'upper_hr_threshold :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'upper_hr_threshold Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1152
p'H5AC_cache_config_t'upper_hr_threshold :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'decrement :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'decrement Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1160
p'H5AC_cache_config_t'decrement :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'apply_max_decrement :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'apply_max_decrement Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1168
p'H5AC_cache_config_t'apply_max_decrement :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'max_decrement :: Ptr H5AC_cache_config_t -> Ptr CSize
p'H5AC_cache_config_t'max_decrement Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1176
p'H5AC_cache_config_t'max_decrement :: Ptr (H5AC_cache_config_t) -> Ptr (CSize)
p'H5AC_cache_config_t'epochs_before_eviction :: Ptr H5AC_cache_config_t -> Ptr CInt
p'H5AC_cache_config_t'epochs_before_eviction Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1184
p'H5AC_cache_config_t'epochs_before_eviction :: Ptr (H5AC_cache_config_t) -> Ptr (CInt)
p'H5AC_cache_config_t'apply_empty_reserve :: Ptr H5AC_cache_config_t -> Ptr HBool_t
p'H5AC_cache_config_t'apply_empty_reserve Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr HBool_t
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1188
p'H5AC_cache_config_t'apply_empty_reserve :: Ptr (H5AC_cache_config_t) -> Ptr (HBool_t)
p'H5AC_cache_config_t'empty_reserve :: Ptr H5AC_cache_config_t -> Ptr CDouble
p'H5AC_cache_config_t'empty_reserve Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1192
p'H5AC_cache_config_t'empty_reserve :: Ptr (H5AC_cache_config_t) -> Ptr (CDouble)
p'H5AC_cache_config_t'dirty_bytes_threshold :: Ptr H5AC_cache_config_t -> Ptr CSize
p'H5AC_cache_config_t'dirty_bytes_threshold Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1200
p'H5AC_cache_config_t'dirty_bytes_threshold :: Ptr (H5AC_cache_config_t) -> Ptr (CSize)
p'H5AC_cache_config_t'metadata_write_strategy :: Ptr H5AC_cache_config_t -> Ptr CInt
p'H5AC_cache_config_t'metadata_write_strategy Ptr H5AC_cache_config_t
p = Ptr H5AC_cache_config_t -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
p Int
1208
p'H5AC_cache_config_t'metadata_write_strategy :: Ptr (H5AC_cache_config_t) -> Ptr (CInt)
instance Storable H5AC_cache_config_t where
  sizeOf :: H5AC_cache_config_t -> Int
sizeOf H5AC_cache_config_t
_ = Int
1216
  alignment :: H5AC_cache_config_t -> Int
alignment H5AC_cache_config_t
_ = Int
8
  peek :: Ptr H5AC_cache_config_t -> IO H5AC_cache_config_t
peek Ptr H5AC_cache_config_t
_p = do
    CInt
v0 <- Ptr H5AC_cache_config_t -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
0
    HBool_t
v1 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
4
    HBool_t
v2 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
5
    HBool_t
v3 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
6
    [CChar]
v4 <- let s4 :: Int
s4 = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
1025 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar -> Int) -> CChar -> Int
forall a b. (a -> b) -> a -> b
$ (CChar
forall a. HasCallStack => a
undefined :: CChar) in Int -> Ptr CChar -> IO [CChar]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
s4 (Ptr H5AC_cache_config_t -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
_p Int
7)
    HBool_t
v5 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1032
    HBool_t
v6 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1033
    CSize
v7 <- Ptr H5AC_cache_config_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1040
    CDouble
v8 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1048
    CSize
v9 <- Ptr H5AC_cache_config_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1056
    CSize
v10 <- Ptr H5AC_cache_config_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1064
    CLong
v11 <- Ptr H5AC_cache_config_t -> Int -> IO CLong
forall b. Ptr b -> Int -> IO CLong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1072
    H5C_cache_incr_mode
v12 <- Ptr H5AC_cache_config_t -> Int -> IO H5C_cache_incr_mode
forall b. Ptr b -> Int -> IO H5C_cache_incr_mode
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1080
    CDouble
v13 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1088
    CDouble
v14 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1096
    HBool_t
v15 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1104
    CSize
v16 <- Ptr H5AC_cache_config_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1112
    H5C_cache_flash_incr_mode
v17 <- Ptr H5AC_cache_config_t -> Int -> IO H5C_cache_flash_incr_mode
forall b. Ptr b -> Int -> IO H5C_cache_flash_incr_mode
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1120
    CDouble
v18 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1128
    CDouble
v19 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1136
    H5C_cache_decr_mode
v20 <- Ptr H5AC_cache_config_t -> Int -> IO H5C_cache_decr_mode
forall b. Ptr b -> Int -> IO H5C_cache_decr_mode
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1144
    CDouble
v21 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1152
    CDouble
v22 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1160
    HBool_t
v23 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1168
    CSize
v24 <- Ptr H5AC_cache_config_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1176
    CInt
v25 <- Ptr H5AC_cache_config_t -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1184
    HBool_t
v26 <- Ptr H5AC_cache_config_t -> Int -> IO HBool_t
forall b. Ptr b -> Int -> IO HBool_t
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1188
    CDouble
v27 <- Ptr H5AC_cache_config_t -> Int -> IO CDouble
forall b. Ptr b -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1192
    CSize
v28 <- Ptr H5AC_cache_config_t -> Int -> IO CSize
forall b. Ptr b -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1200
    CInt
v29 <- Ptr H5AC_cache_config_t -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr H5AC_cache_config_t
_p Int
1208
    H5AC_cache_config_t -> IO H5AC_cache_config_t
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (H5AC_cache_config_t -> IO H5AC_cache_config_t)
-> H5AC_cache_config_t -> IO H5AC_cache_config_t
forall a b. (a -> b) -> a -> b
$ CInt
-> HBool_t
-> HBool_t
-> HBool_t
-> [CChar]
-> HBool_t
-> HBool_t
-> CSize
-> CDouble
-> CSize
-> CSize
-> CLong
-> H5C_cache_incr_mode
-> CDouble
-> CDouble
-> HBool_t
-> CSize
-> H5C_cache_flash_incr_mode
-> CDouble
-> CDouble
-> H5C_cache_decr_mode
-> CDouble
-> CDouble
-> HBool_t
-> CSize
-> CInt
-> HBool_t
-> CDouble
-> CSize
-> CInt
-> H5AC_cache_config_t
H5AC_cache_config_t CInt
v0 HBool_t
v1 HBool_t
v2 HBool_t
v3 [CChar]
v4 HBool_t
v5 HBool_t
v6 CSize
v7 CDouble
v8 CSize
v9 CSize
v10 CLong
v11 H5C_cache_incr_mode
v12 CDouble
v13 CDouble
v14 HBool_t
v15 CSize
v16 H5C_cache_flash_incr_mode
v17 CDouble
v18 CDouble
v19 H5C_cache_decr_mode
v20 CDouble
v21 CDouble
v22 HBool_t
v23 CSize
v24 CInt
v25 HBool_t
v26 CDouble
v27 CSize
v28 CInt
v29
  poke :: Ptr H5AC_cache_config_t -> H5AC_cache_config_t -> IO ()
poke Ptr H5AC_cache_config_t
_p (H5AC_cache_config_t CInt
v0 HBool_t
v1 HBool_t
v2 HBool_t
v3 [CChar]
v4 HBool_t
v5 HBool_t
v6 CSize
v7 CDouble
v8 CSize
v9 CSize
v10 CLong
v11 H5C_cache_incr_mode
v12 CDouble
v13 CDouble
v14 HBool_t
v15 CSize
v16 H5C_cache_flash_incr_mode
v17 CDouble
v18 CDouble
v19 H5C_cache_decr_mode
v20 CDouble
v21 CDouble
v22 HBool_t
v23 CSize
v24 CInt
v25 HBool_t
v26 CDouble
v27 CSize
v28 CInt
v29) = do
    Ptr H5AC_cache_config_t -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
0 CInt
v0
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
4 HBool_t
v1
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
5 HBool_t
v2
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
6 HBool_t
v3
    let s4 :: Int
s4 = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
1025 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar -> Int) -> CChar -> Int
forall a b. (a -> b) -> a -> b
$ (CChar
forall a. HasCallStack => a
undefined :: CChar)
    Ptr CChar -> [CChar] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeArray (Ptr H5AC_cache_config_t -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr H5AC_cache_config_t
_p Int
7) (Int -> [CChar] -> [CChar]
forall a. Int -> [a] -> [a]
take Int
s4 [CChar]
v4)
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1032 HBool_t
v5
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1033 HBool_t
v6
    Ptr H5AC_cache_config_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1040 CSize
v7
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1048 CDouble
v8
    Ptr H5AC_cache_config_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1056 CSize
v9
    Ptr H5AC_cache_config_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1064 CSize
v10
    Ptr H5AC_cache_config_t -> Int -> CLong -> IO ()
forall b. Ptr b -> Int -> CLong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1072 CLong
v11
    Ptr H5AC_cache_config_t -> Int -> H5C_cache_incr_mode -> IO ()
forall b. Ptr b -> Int -> H5C_cache_incr_mode -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1080 H5C_cache_incr_mode
v12
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1088 CDouble
v13
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1096 CDouble
v14
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1104 HBool_t
v15
    Ptr H5AC_cache_config_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1112 CSize
v16
    Ptr H5AC_cache_config_t
-> Int -> H5C_cache_flash_incr_mode -> IO ()
forall b. Ptr b -> Int -> H5C_cache_flash_incr_mode -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1120 H5C_cache_flash_incr_mode
v17
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1128 CDouble
v18
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1136 CDouble
v19
    Ptr H5AC_cache_config_t -> Int -> H5C_cache_decr_mode -> IO ()
forall b. Ptr b -> Int -> H5C_cache_decr_mode -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1144 H5C_cache_decr_mode
v20
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1152 CDouble
v21
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1160 CDouble
v22
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1168 HBool_t
v23
    Ptr H5AC_cache_config_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1176 CSize
v24
    Ptr H5AC_cache_config_t -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1184 CInt
v25
    Ptr H5AC_cache_config_t -> Int -> HBool_t -> IO ()
forall b. Ptr b -> Int -> HBool_t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1188 HBool_t
v26
    Ptr H5AC_cache_config_t -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1192 CDouble
v27
    Ptr H5AC_cache_config_t -> Int -> CSize -> IO ()
forall b. Ptr b -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1200 CSize
v28
    Ptr H5AC_cache_config_t -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr H5AC_cache_config_t
_p Int
1208 CInt
v29
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{-# LINE 359 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

h5ac__CURR_CACHE_CONFIG_VERSION = 1
h5ac__CURR_CACHE_CONFIG_VERSION :: (Num a) => a

{-# LINE 361 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}
h5ac__MAX_TRACE_FILE_NAME_LEN = 1024
h5ac__MAX_TRACE_FILE_NAME_LEN :: (Num a) => a

{-# LINE 362 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |When 'metadata_write_strategy' is set to this value, only process
-- zero is allowed to write dirty metadata to disk.  All other
-- processes must retain dirty metadata until they are informed at
-- a sync point that the dirty metadata in question has been written
-- to disk.
--
-- When the sync point is reached (or when there is a user generated
-- flush), process zero flushes sufficient entries to bring it into
-- complience with its min clean size (or flushes all dirty entries in
-- the case of a user generated flush), broad casts the list of
-- entries just cleaned to all the other processes, and then exits
-- the sync point.
--
-- Upon receipt of the broadcast, the other processes mark the indicated
-- entries as clean, and leave the sync point as well.
h5ac_METADATA_WRITE_STRATEGY__PROCESS_0_ONLY = 0
h5ac_METADATA_WRITE_STRATEGY__PROCESS_0_ONLY :: (Num a) => a

{-# LINE 379 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}

-- |In the distributed metadata write strategy, process zero still makes
-- the decisions as to what entries should be flushed, but the actual
-- flushes are distributed across the processes in the computation to
-- the extent possible.
--
-- In this strategy, when a sync point is triggered (either by dirty
-- metadata creation or manual flush), all processes enter a barrier.
--
-- On the other side of the barrier, process 0 constructs an ordered
-- list of the entries to be flushed, and then broadcasts this list
-- to the caches in all the processes.
--
-- All processes then scan the list of entries to be flushed, flushing
-- some, and marking the rest as clean.  The algorithm for this purpose
-- ensures that each entry in the list is flushed exactly once, and
-- all are marked clean in each cache.
--
-- Note that in the case of a flush of the cache, no message passing
-- is necessary, as all processes have the same list of dirty entries,
-- and all of these entries must be flushed.  Thus in this case it is
-- sufficient for each process to sort its list of dirty entries after
-- leaving the initial barrier, and use this list as if it had been
-- received from process zero.
--
-- To avoid possible messages from the past/future, all caches must
-- wait until all caches are done before leaving the sync point.
h5ac_METADATA_WRITE_STRATEGY__DISTRIBUTED = 1
h5ac_METADATA_WRITE_STRATEGY__DISTRIBUTED :: (Num a) => a

{-# LINE 407 "src/Bindings/HDF5/Raw/H5AC.hsc" #-}