{-# LINE 1 "GHC/RTS/Flags.hsc" #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards   #-}

-- | Accessors to GHC RTS flags.
-- Descriptions of flags can be seen in
-- <https://www.haskell.org/ghc/docs/latest/html/users_guide/runtime_control.html GHC User's Guide>,
-- or by running RTS help message using @+RTS --help@.
--
-- @since 4.8.0.0
--
module GHC.RTS.Flags
  ( RtsTime
  , RTSFlags (..)
  , GiveGCStats (..)
  , GCFlags (..)
  , ConcFlags (..)
  , MiscFlags (..)
  , DebugFlags (..)
  , DoCostCentres (..)
  , CCFlags (..)
  , DoHeapProfile (..)
  , ProfFlags (..)
  , DoTrace (..)
  , TraceFlags (..)
  , TickyFlags (..)
  , ParFlags (..)
  , getRTSFlags
  , getGCFlags
  , getConcFlags
  , getMiscFlags
  , getDebugFlags
  , getCCFlags
  , getProfFlags
  , getTraceFlags
  , getTickyFlags
  , getParFlags
  ) where




import Control.Applicative
import Control.Monad

import Foreign
import Foreign.C

import GHC.Base
import GHC.Enum
import GHC.IO
import GHC.Real
import GHC.Show

-- | 'RtsTime' is defined as a @StgWord64@ in @stg/Types.h@
--
-- @since 4.8.2.0
type RtsTime = Word64

-- | Should we produce a summary of the garbage collector statistics after the
-- program has exited?
--
-- @since 4.8.2.0
data GiveGCStats
    = NoGCStats
    | CollectGCStats
    | OneLineGCStats
    | SummaryGCStats
    | VerboseGCStats
    deriving ( Show -- ^ @since 4.8.0.0
             )

-- | @since 4.8.0.0
instance Enum GiveGCStats where
    fromEnum :: GiveGCStats -> Int
fromEnum GiveGCStats
NoGCStats      = Int
0
{-# LINE 75 "GHC/RTS/Flags.hsc" #-}
    fromEnum CollectGCStats = 1
{-# LINE 76 "GHC/RTS/Flags.hsc" #-}
    fromEnum OneLineGCStats = 2
{-# LINE 77 "GHC/RTS/Flags.hsc" #-}
    fromEnum SummaryGCStats = 3
{-# LINE 78 "GHC/RTS/Flags.hsc" #-}
    fromEnum VerboseGCStats = 4
{-# LINE 79 "GHC/RTS/Flags.hsc" #-}

    toEnum :: Int -> GiveGCStats
toEnum Int
0      = GiveGCStats
NoGCStats
{-# LINE 81 "GHC/RTS/Flags.hsc" #-}
    toEnum 1 = CollectGCStats
{-# LINE 82 "GHC/RTS/Flags.hsc" #-}
    toEnum 2 = OneLineGCStats
{-# LINE 83 "GHC/RTS/Flags.hsc" #-}
    toEnum 3 = SummaryGCStats
{-# LINE 84 "GHC/RTS/Flags.hsc" #-}
    toEnum 4 = VerboseGCStats
{-# LINE 85 "GHC/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for GiveGCStats: " ++ show e)

-- | Parameters of the garbage collector.
--
-- @since 4.8.0.0
data GCFlags = GCFlags
    { GCFlags -> Maybe String
statsFile             :: Maybe FilePath
    , GCFlags -> GiveGCStats
giveStats             :: GiveGCStats
    , GCFlags -> Word32
maxStkSize            :: Word32
    , GCFlags -> Word32
initialStkSize        :: Word32
    , GCFlags -> Word32
stkChunkSize          :: Word32
    , GCFlags -> Word32
stkChunkBufferSize    :: Word32
    , GCFlags -> Word32
maxHeapSize           :: Word32
    , GCFlags -> Word32
minAllocAreaSize      :: Word32
    , GCFlags -> Word32
largeAllocLim         :: Word32
    , GCFlags -> Word32
nurseryChunkSize      :: Word32
    , GCFlags -> Word32
minOldGenSize         :: Word32
    , GCFlags -> Word32
heapSizeSuggestion    :: Word32
    , GCFlags -> Bool
heapSizeSuggestionAuto :: Bool
    , GCFlags -> Double
oldGenFactor          :: Double
    , GCFlags -> Double
pcFreeHeap            :: Double
    , GCFlags -> Word32
generations           :: Word32
    , GCFlags -> Bool
squeezeUpdFrames      :: Bool
    , GCFlags -> Bool
compact               :: Bool -- ^ True <=> "compact all the time"
    , GCFlags -> Double
compactThreshold      :: Double
    , GCFlags -> Bool
sweep                 :: Bool
      -- ^ use "mostly mark-sweep" instead of copying for the oldest generation
    , GCFlags -> Bool
ringBell              :: Bool
    , GCFlags -> RtsTime
idleGCDelayTime       :: RtsTime
    , GCFlags -> Bool
doIdleGC              :: Bool
    , GCFlags -> Word
heapBase              :: Word -- ^ address to ask the OS for memory
    , GCFlags -> Word
allocLimitGrace       :: Word
    , GCFlags -> Bool
numa                  :: Bool
    , GCFlags -> Word
numaMask              :: Word
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Parameters concerning context switching
--
-- @since 4.8.0.0
data ConcFlags = ConcFlags
    { ConcFlags -> RtsTime
ctxtSwitchTime  :: RtsTime
    , ConcFlags -> Int
ctxtSwitchTicks :: Int
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Miscellaneous parameters
--
-- @since 4.8.0.0
data MiscFlags = MiscFlags
    { MiscFlags -> RtsTime
tickInterval          :: RtsTime
    , MiscFlags -> Bool
installSignalHandlers :: Bool
    , MiscFlags -> Bool
installSEHHandlers    :: Bool
    , MiscFlags -> Bool
generateCrashDumpFile :: Bool
    , MiscFlags -> Bool
generateStackTrace    :: Bool
    , MiscFlags -> Bool
machineReadable       :: Bool
    , MiscFlags -> Bool
disableDelayedOsMemoryReturn :: Bool
    , MiscFlags -> Bool
internalCounters      :: Bool
    , MiscFlags -> Bool
linkerAlwaysPic       :: Bool
    , MiscFlags -> Word
linkerMemBase         :: Word
      -- ^ address to ask the OS for memory for the linker, 0 ==> off
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Flags to control debugging output & extra checking in various
-- subsystems.
--
-- @since 4.8.0.0
data DebugFlags = DebugFlags
    { DebugFlags -> Bool
scheduler      :: Bool -- ^ @s@
    , DebugFlags -> Bool
interpreter    :: Bool -- ^ @i@
    , DebugFlags -> Bool
weak           :: Bool -- ^ @w@
    , DebugFlags -> Bool
gccafs         :: Bool -- ^ @G@
    , DebugFlags -> Bool
gc             :: Bool -- ^ @g@
    , DebugFlags -> Bool
nonmoving_gc   :: Bool -- ^ @n@
    , DebugFlags -> Bool
block_alloc    :: Bool -- ^ @b@
    , DebugFlags -> Bool
sanity         :: Bool -- ^ @S@
    , DebugFlags -> Bool
stable         :: Bool -- ^ @t@
    , DebugFlags -> Bool
prof           :: Bool -- ^ @p@
    , DebugFlags -> Bool
linker         :: Bool -- ^ @l@ the object linker
    , DebugFlags -> Bool
apply          :: Bool -- ^ @a@
    , DebugFlags -> Bool
stm            :: Bool -- ^ @m@
    , DebugFlags -> Bool
squeeze        :: Bool -- ^ @z@ stack squeezing & lazy blackholing
    , DebugFlags -> Bool
hpc            :: Bool -- ^ @c@ coverage
    , DebugFlags -> Bool
sparks         :: Bool -- ^ @r@
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Should the RTS produce a cost-center summary?
--
-- @since 4.8.2.0
data DoCostCentres
    = CostCentresNone
    | CostCentresSummary
    | CostCentresVerbose
    | CostCentresAll
    | CostCentresJSON
    deriving ( Show -- ^ @since 4.8.0.0
             )

-- | @since 4.8.0.0
instance Enum DoCostCentres where
    fromEnum :: DoCostCentres -> Int
fromEnum DoCostCentres
CostCentresNone    = Int
0
{-# LINE 188 "GHC/RTS/Flags.hsc" #-}
    fromEnum CostCentresSummary = 1
{-# LINE 189 "GHC/RTS/Flags.hsc" #-}
    fromEnum CostCentresVerbose = 2
{-# LINE 190 "GHC/RTS/Flags.hsc" #-}
    fromEnum CostCentresAll     = 3
{-# LINE 191 "GHC/RTS/Flags.hsc" #-}
    fromEnum CostCentresJSON    = 4
{-# LINE 192 "GHC/RTS/Flags.hsc" #-}

    toEnum :: Int -> DoCostCentres
toEnum Int
0    = DoCostCentres
CostCentresNone
{-# LINE 194 "GHC/RTS/Flags.hsc" #-}
    toEnum 1 = CostCentresSummary
{-# LINE 195 "GHC/RTS/Flags.hsc" #-}
    toEnum 2 = CostCentresVerbose
{-# LINE 196 "GHC/RTS/Flags.hsc" #-}
    toEnum 3     = CostCentresAll
{-# LINE 197 "GHC/RTS/Flags.hsc" #-}
    toEnum 4    = CostCentresJSON
{-# LINE 198 "GHC/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for DoCostCentres: " ++ show e)

-- | Parameters pertaining to the cost-center profiler.
--
-- @since 4.8.0.0
data CCFlags = CCFlags
    { CCFlags -> DoCostCentres
doCostCentres :: DoCostCentres
    , CCFlags -> Int
profilerTicks :: Int
    , CCFlags -> Int
msecsPerTick  :: Int
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | What sort of heap profile are we collecting?
--
-- @since 4.8.2.0
data DoHeapProfile
    = NoHeapProfiling
    | HeapByCCS
    | HeapByMod
    | HeapByDescr
    | HeapByType
    | HeapByRetainer
    | HeapByLDV
    | HeapByClosureType
    deriving ( Show -- ^ @since 4.8.0.0
             )

-- | @since 4.8.0.0
instance Enum DoHeapProfile where
    fromEnum :: DoHeapProfile -> Int
fromEnum DoHeapProfile
NoHeapProfiling   = Int
0
{-# LINE 228 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByCCS         = 1
{-# LINE 229 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByMod         = 2
{-# LINE 230 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByDescr       = 4
{-# LINE 231 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByType        = 5
{-# LINE 232 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByRetainer    = 6
{-# LINE 233 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByLDV         = 7
{-# LINE 234 "GHC/RTS/Flags.hsc" #-}
    fromEnum HeapByClosureType = 8
{-# LINE 235 "GHC/RTS/Flags.hsc" #-}

    toEnum :: Int -> DoHeapProfile
toEnum Int
0    = DoHeapProfile
NoHeapProfiling
{-# LINE 237 "GHC/RTS/Flags.hsc" #-}
    toEnum 1          = HeapByCCS
{-# LINE 238 "GHC/RTS/Flags.hsc" #-}
    toEnum 2          = HeapByMod
{-# LINE 239 "GHC/RTS/Flags.hsc" #-}
    toEnum 4        = HeapByDescr
{-# LINE 240 "GHC/RTS/Flags.hsc" #-}
    toEnum 5         = HeapByType
{-# LINE 241 "GHC/RTS/Flags.hsc" #-}
    toEnum 6     = HeapByRetainer
{-# LINE 242 "GHC/RTS/Flags.hsc" #-}
    toEnum 7          = HeapByLDV
{-# LINE 243 "GHC/RTS/Flags.hsc" #-}
    toEnum 8 = HeapByClosureType
{-# LINE 244 "GHC/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for DoHeapProfile: " ++ show e)

-- | Parameters of the cost-center profiler
--
-- @since 4.8.0.0
data ProfFlags = ProfFlags
    { ProfFlags -> DoHeapProfile
doHeapProfile            :: DoHeapProfile
    , ProfFlags -> RtsTime
heapProfileInterval      :: RtsTime -- ^ time between samples
    , ProfFlags -> Word
heapProfileIntervalTicks :: Word    -- ^ ticks between samples (derived)
    , ProfFlags -> Bool
includeTSOs              :: Bool
    , ProfFlags -> Bool
showCCSOnException       :: Bool
    , ProfFlags -> Word
maxRetainerSetSize       :: Word
    , ProfFlags -> Word
ccsLength                :: Word
    , ProfFlags -> Maybe String
modSelector              :: Maybe String
    , ProfFlags -> Maybe String
descrSelector            :: Maybe String
    , ProfFlags -> Maybe String
typeSelector             :: Maybe String
    , ProfFlags -> Maybe String
ccSelector               :: Maybe String
    , ProfFlags -> Maybe String
ccsSelector              :: Maybe String
    , ProfFlags -> Maybe String
retainerSelector         :: Maybe String
    , ProfFlags -> Maybe String
bioSelector              :: Maybe String
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Is event tracing enabled?
--
-- @since 4.8.2.0
data DoTrace
    = TraceNone      -- ^ no tracing
    | TraceEventLog  -- ^ send tracing events to the event log
    | TraceStderr    -- ^ send tracing events to @stderr@
    deriving ( Show -- ^ @since 4.8.0.0
             )

-- | @since 4.8.0.0
instance Enum DoTrace where
    fromEnum :: DoTrace -> Int
fromEnum DoTrace
TraceNone     = Int
0
{-# LINE 280 "GHC/RTS/Flags.hsc" #-}
    fromEnum TraceEventLog = 1
{-# LINE 281 "GHC/RTS/Flags.hsc" #-}
    fromEnum TraceStderr   = 2
{-# LINE 282 "GHC/RTS/Flags.hsc" #-}

    toEnum :: Int -> DoTrace
toEnum Int
0     = DoTrace
TraceNone
{-# LINE 284 "GHC/RTS/Flags.hsc" #-}
    toEnum 1 = TraceEventLog
{-# LINE 285 "GHC/RTS/Flags.hsc" #-}
    toEnum 2   = TraceStderr
{-# LINE 286 "GHC/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for DoTrace: " ++ show e)

-- | Parameters pertaining to event tracing
--
-- @since 4.8.0.0
data TraceFlags = TraceFlags
    { TraceFlags -> DoTrace
tracing        :: DoTrace
    , TraceFlags -> Bool
timestamp      :: Bool -- ^ show timestamp in stderr output
    , TraceFlags -> Bool
traceScheduler :: Bool -- ^ trace scheduler events
    , TraceFlags -> Bool
traceGc        :: Bool -- ^ trace GC events
    , TraceFlags -> Bool
traceNonmovingGc
                     :: Bool -- ^ trace nonmoving GC heap census samples
    , TraceFlags -> Bool
sparksSampled  :: Bool -- ^ trace spark events by a sampled method
    , TraceFlags -> Bool
sparksFull     :: Bool -- ^ trace spark events 100% accurately
    , TraceFlags -> Bool
user           :: Bool -- ^ trace user events (emitted from Haskell code)
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Parameters pertaining to ticky-ticky profiler
--
-- @since 4.8.0.0
data TickyFlags = TickyFlags
    { TickyFlags -> Bool
showTickyStats :: Bool
    , TickyFlags -> Maybe String
tickyFile      :: Maybe FilePath
    } deriving ( Show -- ^ @since 4.8.0.0
               )

-- | Parameters pertaining to parallelism
--
-- @since 4.8.0.0
data ParFlags = ParFlags
    { ParFlags -> Word32
nCapabilities :: Word32
    , ParFlags -> Bool
migrate :: Bool
    , ParFlags -> Word32
maxLocalSparks :: Word32
    , ParFlags -> Bool
parGcEnabled :: Bool
    , ParFlags -> Word32
parGcGen :: Word32
    , ParFlags -> Bool
parGcLoadBalancingEnabled :: Bool
    , ParFlags -> Word32
parGcLoadBalancingGen :: Word32
    , ParFlags -> Word32
parGcNoSyncWithIdle :: Word32
    , ParFlags -> Word32
parGcThreads :: Word32
    , ParFlags -> Bool
setAffinity :: Bool
    }
    deriving ( Show -- ^ @since 4.8.0.0
             )

-- | Parameters of the runtime system
--
-- @since 4.8.0.0
data RTSFlags = RTSFlags
    { RTSFlags -> GCFlags
gcFlags         :: GCFlags
    , RTSFlags -> ConcFlags
concurrentFlags :: ConcFlags
    , RTSFlags -> MiscFlags
miscFlags       :: MiscFlags
    , RTSFlags -> DebugFlags
debugFlags      :: DebugFlags
    , RTSFlags -> CCFlags
costCentreFlags :: CCFlags
    , RTSFlags -> ProfFlags
profilingFlags  :: ProfFlags
    , RTSFlags -> TraceFlags
traceFlags      :: TraceFlags
    , RTSFlags -> TickyFlags
tickyFlags      :: TickyFlags
    , RTSFlags -> ParFlags
parFlags        :: ParFlags
    } deriving ( Show -- ^ @since 4.8.0.0
               )

foreign import ccall "&RtsFlags" rtsFlagsPtr :: Ptr RTSFlags

getRTSFlags :: IO RTSFlags
getRTSFlags :: IO RTSFlags
getRTSFlags = do
  GCFlags
-> ConcFlags
-> MiscFlags
-> DebugFlags
-> CCFlags
-> ProfFlags
-> TraceFlags
-> TickyFlags
-> ParFlags
-> RTSFlags
RTSFlags (GCFlags
 -> ConcFlags
 -> MiscFlags
 -> DebugFlags
 -> CCFlags
 -> ProfFlags
 -> TraceFlags
 -> TickyFlags
 -> ParFlags
 -> RTSFlags)
-> IO GCFlags
-> IO
     (ConcFlags
      -> MiscFlags
      -> DebugFlags
      -> CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> RTSFlags)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO GCFlags
getGCFlags
           IO
  (ConcFlags
   -> MiscFlags
   -> DebugFlags
   -> CCFlags
   -> ProfFlags
   -> TraceFlags
   -> TickyFlags
   -> ParFlags
   -> RTSFlags)
-> IO ConcFlags
-> IO
     (MiscFlags
      -> DebugFlags
      -> CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO ConcFlags
getConcFlags
           IO
  (MiscFlags
   -> DebugFlags
   -> CCFlags
   -> ProfFlags
   -> TraceFlags
   -> TickyFlags
   -> ParFlags
   -> RTSFlags)
-> IO MiscFlags
-> IO
     (DebugFlags
      -> CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO MiscFlags
getMiscFlags
           IO
  (DebugFlags
   -> CCFlags
   -> ProfFlags
   -> TraceFlags
   -> TickyFlags
   -> ParFlags
   -> RTSFlags)
-> IO DebugFlags
-> IO
     (CCFlags
      -> ProfFlags -> TraceFlags -> TickyFlags -> ParFlags -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO DebugFlags
getDebugFlags
           IO
  (CCFlags
   -> ProfFlags -> TraceFlags -> TickyFlags -> ParFlags -> RTSFlags)
-> IO CCFlags
-> IO
     (ProfFlags -> TraceFlags -> TickyFlags -> ParFlags -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO CCFlags
getCCFlags
           IO (ProfFlags -> TraceFlags -> TickyFlags -> ParFlags -> RTSFlags)
-> IO ProfFlags
-> IO (TraceFlags -> TickyFlags -> ParFlags -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO ProfFlags
getProfFlags
           IO (TraceFlags -> TickyFlags -> ParFlags -> RTSFlags)
-> IO TraceFlags -> IO (TickyFlags -> ParFlags -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO TraceFlags
getTraceFlags
           IO (TickyFlags -> ParFlags -> RTSFlags)
-> IO TickyFlags -> IO (ParFlags -> RTSFlags)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO TickyFlags
getTickyFlags
           IO (ParFlags -> RTSFlags) -> IO ParFlags -> IO RTSFlags
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO ParFlags
getParFlags

peekFilePath :: Ptr () -> IO (Maybe FilePath)
peekFilePath :: Ptr () -> IO (Maybe String)
peekFilePath Ptr ()
ptr
  | Ptr ()
ptr Ptr () -> Ptr () -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr ()
forall a. Ptr a
nullPtr = Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
  | Bool
otherwise      = Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just String
"<filepath>")

-- | Read a NUL terminated string. Return Nothing in case of a NULL pointer.
peekCStringOpt :: Ptr CChar -> IO (Maybe String)
peekCStringOpt :: Ptr CChar -> IO (Maybe String)
peekCStringOpt Ptr CChar
ptr
  | Ptr CChar
ptr Ptr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CChar
forall a. Ptr a
nullPtr = Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
  | Bool
otherwise      = String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> IO String -> IO (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CChar -> IO String
peekCString Ptr CChar
ptr

getGCFlags :: IO GCFlags
getGCFlags :: IO GCFlags
getGCFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 375 "GHC/RTS/Flags.hsc" #-}
  GCFlags <$> (peekFilePath =<< (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr)
{-# LINE 376 "GHC/RTS/Flags.hsc" #-}
          <*> (toEnum . fromIntegral <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO Word32))
{-# LINE 378 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr
{-# LINE 379 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 380 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 20) ptr
{-# LINE 381 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 382 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 383 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 384 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 36) ptr
{-# LINE 385 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr
{-# LINE 386 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 44) ptr
{-# LINE 387 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr
{-# LINE 388 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 52) ptr :: IO CBool))
{-# LINE 390 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr
{-# LINE 391 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr
{-# LINE 392 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 76) ptr
{-# LINE 393 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 80) ptr :: IO CBool))
{-# LINE 395 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 81) ptr :: IO CBool))
{-# LINE 397 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 88) ptr
{-# LINE 398 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 96) ptr :: IO CBool))
{-# LINE 400 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 97) ptr :: IO CBool))
{-# LINE 402 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 104) ptr
{-# LINE 403 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 120) ptr :: IO CBool))
{-# LINE 405 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 136) ptr
{-# LINE 406 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 144) ptr
{-# LINE 407 "GHC/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 160) ptr :: IO CBool))
{-# LINE 409 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 168) ptr
{-# LINE 410 "GHC/RTS/Flags.hsc" #-}

getParFlags :: IO ParFlags
getParFlags :: IO ParFlags
getParFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
392)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 414 "GHC/RTS/Flags.hsc" #-}
  ParFlags
    <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 416 "GHC/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 418 "GHC/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 419 "GHC/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 421 "GHC/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 422 "GHC/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr :: IO CBool))
{-# LINE 424 "GHC/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 425 "GHC/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 426 "GHC/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 427 "GHC/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 36) ptr :: IO CBool))
{-# LINE 429 "GHC/RTS/Flags.hsc" #-}

getConcFlags :: IO ConcFlags
getConcFlags :: IO ConcFlags
getConcFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 433 "GHC/RTS/Flags.hsc" #-}
  ConcFlags <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 434 "GHC/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 435 "GHC/RTS/Flags.hsc" #-}

getMiscFlags :: IO MiscFlags
getMiscFlags :: IO MiscFlags
getMiscFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 439 "GHC/RTS/Flags.hsc" #-}
  MiscFlags <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 440 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 442 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 444 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 446 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 448 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 450 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 13) ptr :: IO CBool))
{-# LINE 452 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 14) ptr :: IO CBool))
{-# LINE 454 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 15) ptr :: IO CBool))
{-# LINE 456 "GHC/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 457 "GHC/RTS/Flags.hsc" #-}

getDebugFlags :: IO DebugFlags
getDebugFlags :: IO DebugFlags
getDebugFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
216)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 461 "GHC/RTS/Flags.hsc" #-}
  DebugFlags <$> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 463 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 1) ptr :: IO CBool))
{-# LINE 465 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 2) ptr :: IO CBool))
{-# LINE 467 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 3) ptr :: IO CBool))
{-# LINE 469 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 471 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 5) ptr :: IO CBool))
{-# LINE 473 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO CBool))
{-# LINE 475 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 7) ptr :: IO CBool))
{-# LINE 477 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 479 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 481 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 483 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 485 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 13) ptr :: IO CBool))
{-# LINE 487 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 14) ptr :: IO CBool))
{-# LINE 489 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 15) ptr :: IO CBool))
{-# LINE 491 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 16) ptr :: IO CBool))
{-# LINE 493 "GHC/RTS/Flags.hsc" #-}

getCCFlags :: IO CCFlags
getCCFlags :: IO CCFlags
getCCFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 497 "GHC/RTS/Flags.hsc" #-}
  CCFlags <$> (toEnum . fromIntegral
                <$> ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO Word32))
{-# LINE 499 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 500 "GHC/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 501 "GHC/RTS/Flags.hsc" #-}

getProfFlags :: IO ProfFlags
getProfFlags :: IO ProfFlags
getProfFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
264)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 505 "GHC/RTS/Flags.hsc" #-}
  ProfFlags <$> (toEnum <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr)
{-# LINE 506 "GHC/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 507 "GHC/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 508 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr :: IO CBool))
{-# LINE 510 "GHC/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 21) ptr :: IO CBool))
{-# LINE 512 "GHC/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 513 "GHC/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 514 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr)
{-# LINE 515 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr)
{-# LINE 516 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr)
{-# LINE 517 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr)
{-# LINE 518 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr)
{-# LINE 519 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr)
{-# LINE 520 "GHC/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 80) ptr)
{-# LINE 521 "GHC/RTS/Flags.hsc" #-}

getTraceFlags :: IO TraceFlags
getTraceFlags :: IO TraceFlags
getTraceFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
352)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 525 "GHC/RTS/Flags.hsc" #-}
  TraceFlags <$> (toEnum . fromIntegral
                   <$> ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CInt))
{-# LINE 527 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 529 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 5) ptr :: IO CBool))
{-# LINE 531 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO CBool))
{-# LINE 533 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 7) ptr :: IO CBool))
{-# LINE 535 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 537 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 539 "GHC/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 541 "GHC/RTS/Flags.hsc" #-}

getTickyFlags :: IO TickyFlags
getTickyFlags :: IO TickyFlags
getTickyFlags = do
  let ptr :: Ptr b
ptr = ((\Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
376)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 545 "GHC/RTS/Flags.hsc" #-}
  TickyFlags <$> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 547 "GHC/RTS/Flags.hsc" #-}
             <*> (peekFilePath =<< (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr)
{-# LINE 548 "GHC/RTS/Flags.hsc" #-}