{-# LINE 1 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- |
-- Module      :  GHC.Internal.RTS.Flags
-- Copyright   :  (c) The University of Glasgow, 1994-2000
-- License     :  see libraries/base/LICENSE
--
-- Maintainer  :  ghc-devs@haskell.org
-- Stability   :  internal
-- Portability :  non-portable (GHC extensions)
--
-- /The API of this module is unstable and is tightly coupled to GHC's internals./
-- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather
-- than @base < 5@, because the interface can change rapidly without much warning.
--
-- 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 base-4.8.0.0
--
module GHC.Internal.RTS.Flags
  ( RtsTime
  , RTSFlags (..)
  , GiveGCStats (..)
  , GCFlags (..)
  , ConcFlags (..)
  , MiscFlags (..)
  , DebugFlags (..)
  , DoCostCentres (..)
  , CCFlags (..)
  , DoHeapProfile (..)
  , ProfFlags (..)
  , DoTrace (..)
  , TraceFlags (..)
  , TickyFlags (..)
  , ParFlags (..)
  , HpcFlags (..)
  , IoSubSystem (..)
  , getRTSFlags
  , getGCFlags
  , getConcFlags
  , getMiscFlags
  , getIoManagerFlag
  , getDebugFlags
  , getCCFlags
  , getProfFlags
  , getTraceFlags
  , getTickyFlags
  , getParFlags
  , getHpcFlags
  ) where




import GHC.Internal.Data.Functor ((<$>))
import GHC.Internal.Foreign.C.Types
import GHC.Internal.Foreign.C.String
import GHC.Internal.Foreign.Marshal.Utils
import GHC.Internal.Foreign.Storable
import GHC.Internal.Ptr
import GHC.Internal.Word
import GHC.Internal.Base
import GHC.Internal.Enum
import GHC.Internal.Generics (Generic)
import GHC.Internal.IO
import GHC.Internal.Real
import GHC.Internal.Show

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

-- | Should we produce a summary of the garbage collector statistics after the
-- program has exited?
--
-- @since base-4.8.2.0
data GiveGCStats
    = NoGCStats
    | CollectGCStats
    | OneLineGCStats
    | SummaryGCStats
    | VerboseGCStats
    deriving ( Int -> GiveGCStats -> ShowS
[GiveGCStats] -> ShowS
GiveGCStats -> String
(Int -> GiveGCStats -> ShowS)
-> (GiveGCStats -> String)
-> ([GiveGCStats] -> ShowS)
-> Show GiveGCStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GiveGCStats -> ShowS
showsPrec :: Int -> GiveGCStats -> ShowS
$cshow :: GiveGCStats -> String
show :: GiveGCStats -> String
$cshowList :: [GiveGCStats] -> ShowS
showList :: [GiveGCStats] -> ShowS
Show -- ^ @since base-4.8.0.0
             , (forall x. GiveGCStats -> Rep GiveGCStats x)
-> (forall x. Rep GiveGCStats x -> GiveGCStats)
-> Generic GiveGCStats
forall x. Rep GiveGCStats x -> GiveGCStats
forall x. GiveGCStats -> Rep GiveGCStats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GiveGCStats -> Rep GiveGCStats x
from :: forall x. GiveGCStats -> Rep GiveGCStats x
$cto :: forall x. Rep GiveGCStats x -> GiveGCStats
to :: forall x. Rep GiveGCStats x -> GiveGCStats
Generic -- ^ @since base-4.15.0.0
             )

-- | @since base-4.8.0.0
instance Enum GiveGCStats where
    fromEnum :: GiveGCStats -> Int
fromEnum GiveGCStats
NoGCStats      = Int
0
{-# LINE 94 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum CollectGCStats = 1
{-# LINE 95 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum OneLineGCStats = 2
{-# LINE 96 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum SummaryGCStats = 3
{-# LINE 97 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum VerboseGCStats = 4
{-# LINE 98 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

    toEnum :: Int -> GiveGCStats
toEnum Int
0      = GiveGCStats
NoGCStats
{-# LINE 100 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 1 = CollectGCStats
{-# LINE 101 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 2 = OneLineGCStats
{-# LINE 102 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 3 = SummaryGCStats
{-# LINE 103 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 4 = VerboseGCStats
{-# LINE 104 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for GiveGCStats: " ++ show e)

-- | The I/O SubSystem to use in the program.
--
-- @since base-4.9.0.0
data IoSubSystem
  = IoPOSIX   -- ^ Use a POSIX I/O Sub-System
  | IoNative  -- ^ Use platform native Sub-System. For unix OSes this is the
              --   same as IoPOSIX, but on Windows this means use the Windows
              --   native APIs for I/O, including IOCP and RIO.
  deriving (IoSubSystem -> IoSubSystem -> Bool
(IoSubSystem -> IoSubSystem -> Bool)
-> (IoSubSystem -> IoSubSystem -> Bool) -> Eq IoSubSystem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IoSubSystem -> IoSubSystem -> Bool
== :: IoSubSystem -> IoSubSystem -> Bool
$c/= :: IoSubSystem -> IoSubSystem -> Bool
/= :: IoSubSystem -> IoSubSystem -> Bool
Eq, Int -> IoSubSystem -> ShowS
[IoSubSystem] -> ShowS
IoSubSystem -> String
(Int -> IoSubSystem -> ShowS)
-> (IoSubSystem -> String)
-> ([IoSubSystem] -> ShowS)
-> Show IoSubSystem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IoSubSystem -> ShowS
showsPrec :: Int -> IoSubSystem -> ShowS
$cshow :: IoSubSystem -> String
show :: IoSubSystem -> String
$cshowList :: [IoSubSystem] -> ShowS
showList :: [IoSubSystem] -> ShowS
Show)

-- | @since base-4.9.0.0
instance Enum IoSubSystem where
    fromEnum :: IoSubSystem -> Int
fromEnum IoSubSystem
IoPOSIX  = Int
1
{-# LINE 119 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum IoNative = 0
{-# LINE 120 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

    toEnum :: Int -> IoSubSystem
toEnum Int
1  = IoSubSystem
IoPOSIX
{-# LINE 122 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 0 = IoNative
{-# LINE 123 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for IoSubSystem: " ++ show e)

-- | @since base-4.9.0.0
instance Storable IoSubSystem where
    sizeOf :: IoSubSystem -> Int
sizeOf = Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int -> Int) -> (IoSubSystem -> Int) -> IoSubSystem -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IoSubSystem -> Int
forall a. Enum a => a -> Int
fromEnum
    alignment :: IoSubSystem -> Int
alignment = Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int -> Int) -> (IoSubSystem -> Int) -> IoSubSystem -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IoSubSystem -> Int
forall a. Enum a => a -> Int
fromEnum
    peek :: Ptr IoSubSystem -> IO IoSubSystem
peek Ptr IoSubSystem
ptr = (Int -> IoSubSystem) -> IO Int -> IO IoSubSystem
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> IoSubSystem
forall a. Enum a => Int -> a
toEnum (IO Int -> IO IoSubSystem) -> IO Int -> IO IoSubSystem
forall a b. (a -> b) -> a -> b
$ Ptr Int -> IO Int
forall a. Storable a => Ptr a -> IO a
peek (Ptr IoSubSystem -> Ptr Int
forall a b. Ptr a -> Ptr b
castPtr Ptr IoSubSystem
ptr)
    poke :: Ptr IoSubSystem -> IoSubSystem -> IO ()
poke Ptr IoSubSystem
ptr IoSubSystem
v = Ptr Int -> Int -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr IoSubSystem -> Ptr Int
forall a b. Ptr a -> Ptr b
castPtr Ptr IoSubSystem
ptr) (IoSubSystem -> Int
forall a. Enum a => a -> Int
fromEnum IoSubSystem
v)

-- | Parameters of the garbage collector.
--
-- @since base-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
returnDecayFactor     :: 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 ( Int -> GCFlags -> ShowS
[GCFlags] -> ShowS
GCFlags -> String
(Int -> GCFlags -> ShowS)
-> (GCFlags -> String) -> ([GCFlags] -> ShowS) -> Show GCFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GCFlags -> ShowS
showsPrec :: Int -> GCFlags -> ShowS
$cshow :: GCFlags -> String
show :: GCFlags -> String
$cshowList :: [GCFlags] -> ShowS
showList :: [GCFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. GCFlags -> Rep GCFlags x)
-> (forall x. Rep GCFlags x -> GCFlags) -> Generic GCFlags
forall x. Rep GCFlags x -> GCFlags
forall x. GCFlags -> Rep GCFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GCFlags -> Rep GCFlags x
from :: forall x. GCFlags -> Rep GCFlags x
$cto :: forall x. Rep GCFlags x -> GCFlags
to :: forall x. Rep GCFlags x -> GCFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Parameters concerning context switching
--
-- @since base-4.8.0.0
data ConcFlags = ConcFlags
    { ConcFlags -> RtsTime
ctxtSwitchTime  :: RtsTime
    , ConcFlags -> Int
ctxtSwitchTicks :: Int
    } deriving ( Int -> ConcFlags -> ShowS
[ConcFlags] -> ShowS
ConcFlags -> String
(Int -> ConcFlags -> ShowS)
-> (ConcFlags -> String)
-> ([ConcFlags] -> ShowS)
-> Show ConcFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConcFlags -> ShowS
showsPrec :: Int -> ConcFlags -> ShowS
$cshow :: ConcFlags -> String
show :: ConcFlags -> String
$cshowList :: [ConcFlags] -> ShowS
showList :: [ConcFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. ConcFlags -> Rep ConcFlags x)
-> (forall x. Rep ConcFlags x -> ConcFlags) -> Generic ConcFlags
forall x. Rep ConcFlags x -> ConcFlags
forall x. ConcFlags -> Rep ConcFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConcFlags -> Rep ConcFlags x
from :: forall x. ConcFlags -> Rep ConcFlags x
$cto :: forall x. Rep ConcFlags x -> ConcFlags
to :: forall x. Rep ConcFlags x -> ConcFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Miscellaneous parameters
--
-- @since base-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
    , MiscFlags -> IoSubSystem
ioManager             :: IoSubSystem
    , MiscFlags -> Word32
numIoWorkerThreads    :: Word32
    } deriving ( Int -> MiscFlags -> ShowS
[MiscFlags] -> ShowS
MiscFlags -> String
(Int -> MiscFlags -> ShowS)
-> (MiscFlags -> String)
-> ([MiscFlags] -> ShowS)
-> Show MiscFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MiscFlags -> ShowS
showsPrec :: Int -> MiscFlags -> ShowS
$cshow :: MiscFlags -> String
show :: MiscFlags -> String
$cshowList :: [MiscFlags] -> ShowS
showList :: [MiscFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. MiscFlags -> Rep MiscFlags x)
-> (forall x. Rep MiscFlags x -> MiscFlags) -> Generic MiscFlags
forall x. Rep MiscFlags x -> MiscFlags
forall x. MiscFlags -> Rep MiscFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MiscFlags -> Rep MiscFlags x
from :: forall x. MiscFlags -> Rep MiscFlags x
$cto :: forall x. Rep MiscFlags x -> MiscFlags
to :: forall x. Rep MiscFlags x -> MiscFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Flags to control debugging output & extra checking in various
-- subsystems.
--
-- @since base-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 ( Int -> DebugFlags -> ShowS
[DebugFlags] -> ShowS
DebugFlags -> String
(Int -> DebugFlags -> ShowS)
-> (DebugFlags -> String)
-> ([DebugFlags] -> ShowS)
-> Show DebugFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DebugFlags -> ShowS
showsPrec :: Int -> DebugFlags -> ShowS
$cshow :: DebugFlags -> String
show :: DebugFlags -> String
$cshowList :: [DebugFlags] -> ShowS
showList :: [DebugFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. DebugFlags -> Rep DebugFlags x)
-> (forall x. Rep DebugFlags x -> DebugFlags) -> Generic DebugFlags
forall x. Rep DebugFlags x -> DebugFlags
forall x. DebugFlags -> Rep DebugFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DebugFlags -> Rep DebugFlags x
from :: forall x. DebugFlags -> Rep DebugFlags x
$cto :: forall x. Rep DebugFlags x -> DebugFlags
to :: forall x. Rep DebugFlags x -> DebugFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Should the RTS produce a cost-center summary?
--
-- @since base-4.8.2.0
data DoCostCentres
    = CostCentresNone
    | CostCentresSummary
    | CostCentresVerbose
    | CostCentresAll
    | CostCentresJSON
    deriving ( Int -> DoCostCentres -> ShowS
[DoCostCentres] -> ShowS
DoCostCentres -> String
(Int -> DoCostCentres -> ShowS)
-> (DoCostCentres -> String)
-> ([DoCostCentres] -> ShowS)
-> Show DoCostCentres
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DoCostCentres -> ShowS
showsPrec :: Int -> DoCostCentres -> ShowS
$cshow :: DoCostCentres -> String
show :: DoCostCentres -> String
$cshowList :: [DoCostCentres] -> ShowS
showList :: [DoCostCentres] -> ShowS
Show -- ^ @since base-4.8.0.0
             , (forall x. DoCostCentres -> Rep DoCostCentres x)
-> (forall x. Rep DoCostCentres x -> DoCostCentres)
-> Generic DoCostCentres
forall x. Rep DoCostCentres x -> DoCostCentres
forall x. DoCostCentres -> Rep DoCostCentres x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DoCostCentres -> Rep DoCostCentres x
from :: forall x. DoCostCentres -> Rep DoCostCentres x
$cto :: forall x. Rep DoCostCentres x -> DoCostCentres
to :: forall x. Rep DoCostCentres x -> DoCostCentres
Generic -- ^ @since base-4.15.0.0
             )

-- | @since base-4.8.0.0
instance Enum DoCostCentres where
    fromEnum :: DoCostCentres -> Int
fromEnum DoCostCentres
CostCentresNone    = Int
0
{-# LINE 241 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum CostCentresSummary = 1
{-# LINE 242 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum CostCentresVerbose = 2
{-# LINE 243 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum CostCentresAll     = 3
{-# LINE 244 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum CostCentresJSON    = 4
{-# LINE 245 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

    toEnum :: Int -> DoCostCentres
toEnum Int
0    = DoCostCentres
CostCentresNone
{-# LINE 247 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 1 = CostCentresSummary
{-# LINE 248 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 2 = CostCentresVerbose
{-# LINE 249 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 3     = CostCentresAll
{-# LINE 250 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 4    = CostCentresJSON
{-# LINE 251 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for DoCostCentres: " ++ show e)

-- | Parameters pertaining to the cost-center profiler.
--
-- @since base-4.8.0.0
data CCFlags = CCFlags
    { CCFlags -> DoCostCentres
doCostCentres :: DoCostCentres
    , CCFlags -> Int
profilerTicks :: Int
    , CCFlags -> Int
msecsPerTick  :: Int
    } deriving ( Int -> CCFlags -> ShowS
[CCFlags] -> ShowS
CCFlags -> String
(Int -> CCFlags -> ShowS)
-> (CCFlags -> String) -> ([CCFlags] -> ShowS) -> Show CCFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CCFlags -> ShowS
showsPrec :: Int -> CCFlags -> ShowS
$cshow :: CCFlags -> String
show :: CCFlags -> String
$cshowList :: [CCFlags] -> ShowS
showList :: [CCFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. CCFlags -> Rep CCFlags x)
-> (forall x. Rep CCFlags x -> CCFlags) -> Generic CCFlags
forall x. Rep CCFlags x -> CCFlags
forall x. CCFlags -> Rep CCFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CCFlags -> Rep CCFlags x
from :: forall x. CCFlags -> Rep CCFlags x
$cto :: forall x. Rep CCFlags x -> CCFlags
to :: forall x. Rep CCFlags x -> CCFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | What sort of heap profile are we collecting?
--
-- @since base-4.8.2.0
data DoHeapProfile
    = NoHeapProfiling
    | HeapByCCS
    | HeapByMod
    | HeapByDescr
    | HeapByType
    | HeapByRetainer
    | HeapByLDV
    | HeapByClosureType
    | HeapByInfoTable
    | HeapByEra -- ^ @since base-4.20.0.0
    deriving ( Int -> DoHeapProfile -> ShowS
[DoHeapProfile] -> ShowS
DoHeapProfile -> String
(Int -> DoHeapProfile -> ShowS)
-> (DoHeapProfile -> String)
-> ([DoHeapProfile] -> ShowS)
-> Show DoHeapProfile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DoHeapProfile -> ShowS
showsPrec :: Int -> DoHeapProfile -> ShowS
$cshow :: DoHeapProfile -> String
show :: DoHeapProfile -> String
$cshowList :: [DoHeapProfile] -> ShowS
showList :: [DoHeapProfile] -> ShowS
Show -- ^ @since base-4.8.0.0
             , (forall x. DoHeapProfile -> Rep DoHeapProfile x)
-> (forall x. Rep DoHeapProfile x -> DoHeapProfile)
-> Generic DoHeapProfile
forall x. Rep DoHeapProfile x -> DoHeapProfile
forall x. DoHeapProfile -> Rep DoHeapProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DoHeapProfile -> Rep DoHeapProfile x
from :: forall x. DoHeapProfile -> Rep DoHeapProfile x
$cto :: forall x. Rep DoHeapProfile x -> DoHeapProfile
to :: forall x. Rep DoHeapProfile x -> DoHeapProfile
Generic -- ^ @since base-4.15.0.0
             )

-- | @since base-4.8.0.0
instance Enum DoHeapProfile where
    fromEnum :: DoHeapProfile -> Int
fromEnum DoHeapProfile
NoHeapProfiling   = Int
0
{-# LINE 285 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByCCS         = 1
{-# LINE 286 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByMod         = 2
{-# LINE 287 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByDescr       = 4
{-# LINE 288 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByType        = 5
{-# LINE 289 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByRetainer    = 6
{-# LINE 290 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByLDV         = 7
{-# LINE 291 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByClosureType = 8
{-# LINE 292 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByInfoTable   = 9
{-# LINE 293 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum HeapByEra         = 10
{-# LINE 294 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

    toEnum :: Int -> DoHeapProfile
toEnum Int
0    = DoHeapProfile
NoHeapProfiling
{-# LINE 296 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 1          = HeapByCCS
{-# LINE 297 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 2          = HeapByMod
{-# LINE 298 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 4        = HeapByDescr
{-# LINE 299 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 5         = HeapByType
{-# LINE 300 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 6     = HeapByRetainer
{-# LINE 301 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 7          = HeapByLDV
{-# LINE 302 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 8 = HeapByClosureType
{-# LINE 303 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 9   = HeapByInfoTable
{-# LINE 304 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 10          = HeapByEra
{-# LINE 305 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for DoHeapProfile: " ++ show e)

-- | Parameters of the cost-center profiler
--
-- @since base-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
startHeapProfileAtStartup :: Bool
    , ProfFlags -> Bool
startTimeProfileAtStartup :: Bool   -- ^ @since base-4.20.0.0
    , ProfFlags -> Bool
showCCSOnException       :: Bool
    , ProfFlags -> Bool
automaticEraIncrement    :: Bool   -- ^ @since 4.20.0.0
    , 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
    , ProfFlags -> Word
eraSelector              :: Word -- ^ @since base-4.20.0.0
    } deriving ( Int -> ProfFlags -> ShowS
[ProfFlags] -> ShowS
ProfFlags -> String
(Int -> ProfFlags -> ShowS)
-> (ProfFlags -> String)
-> ([ProfFlags] -> ShowS)
-> Show ProfFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProfFlags -> ShowS
showsPrec :: Int -> ProfFlags -> ShowS
$cshow :: ProfFlags -> String
show :: ProfFlags -> String
$cshowList :: [ProfFlags] -> ShowS
showList :: [ProfFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. ProfFlags -> Rep ProfFlags x)
-> (forall x. Rep ProfFlags x -> ProfFlags) -> Generic ProfFlags
forall x. Rep ProfFlags x -> ProfFlags
forall x. ProfFlags -> Rep ProfFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProfFlags -> Rep ProfFlags x
from :: forall x. ProfFlags -> Rep ProfFlags x
$cto :: forall x. Rep ProfFlags x -> ProfFlags
to :: forall x. Rep ProfFlags x -> ProfFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Is event tracing enabled?
--
-- @since base-4.8.2.0
data DoTrace
    = TraceNone      -- ^ no tracing
    | TraceEventLog  -- ^ send tracing events to the event log
    | TraceStderr    -- ^ send tracing events to @stderr@
    deriving ( Int -> DoTrace -> ShowS
[DoTrace] -> ShowS
DoTrace -> String
(Int -> DoTrace -> ShowS)
-> (DoTrace -> String) -> ([DoTrace] -> ShowS) -> Show DoTrace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DoTrace -> ShowS
showsPrec :: Int -> DoTrace -> ShowS
$cshow :: DoTrace -> String
show :: DoTrace -> String
$cshowList :: [DoTrace] -> ShowS
showList :: [DoTrace] -> ShowS
Show -- ^ @since base-4.8.0.0
             , (forall x. DoTrace -> Rep DoTrace x)
-> (forall x. Rep DoTrace x -> DoTrace) -> Generic DoTrace
forall x. Rep DoTrace x -> DoTrace
forall x. DoTrace -> Rep DoTrace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DoTrace -> Rep DoTrace x
from :: forall x. DoTrace -> Rep DoTrace x
$cto :: forall x. Rep DoTrace x -> DoTrace
to :: forall x. Rep DoTrace x -> DoTrace
Generic -- ^ @since base-4.15.0.0
             )

-- | @since base-4.8.0.0
instance Enum DoTrace where
    fromEnum :: DoTrace -> Int
fromEnum DoTrace
TraceNone     = Int
0
{-# LINE 346 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum TraceEventLog = 1
{-# LINE 347 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    fromEnum TraceStderr   = 2
{-# LINE 348 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

    toEnum :: Int -> DoTrace
toEnum Int
0     = DoTrace
TraceNone
{-# LINE 350 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 1 = TraceEventLog
{-# LINE 351 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum 2   = TraceStderr
{-# LINE 352 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    toEnum e = errorWithoutStackTrace ("invalid enum for DoTrace: " ++ show e)

-- | Parameters pertaining to event tracing
--
-- @since base-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 ( Int -> TraceFlags -> ShowS
[TraceFlags] -> ShowS
TraceFlags -> String
(Int -> TraceFlags -> ShowS)
-> (TraceFlags -> String)
-> ([TraceFlags] -> ShowS)
-> Show TraceFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceFlags -> ShowS
showsPrec :: Int -> TraceFlags -> ShowS
$cshow :: TraceFlags -> String
show :: TraceFlags -> String
$cshowList :: [TraceFlags] -> ShowS
showList :: [TraceFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. TraceFlags -> Rep TraceFlags x)
-> (forall x. Rep TraceFlags x -> TraceFlags) -> Generic TraceFlags
forall x. Rep TraceFlags x -> TraceFlags
forall x. TraceFlags -> Rep TraceFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TraceFlags -> Rep TraceFlags x
from :: forall x. TraceFlags -> Rep TraceFlags x
$cto :: forall x. Rep TraceFlags x -> TraceFlags
to :: forall x. Rep TraceFlags x -> TraceFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Parameters pertaining to ticky-ticky profiler
--
-- @since base-4.8.0.0
data TickyFlags = TickyFlags
    { TickyFlags -> Bool
showTickyStats :: Bool
    , TickyFlags -> Maybe String
tickyFile      :: Maybe FilePath
    } deriving ( Int -> TickyFlags -> ShowS
[TickyFlags] -> ShowS
TickyFlags -> String
(Int -> TickyFlags -> ShowS)
-> (TickyFlags -> String)
-> ([TickyFlags] -> ShowS)
-> Show TickyFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TickyFlags -> ShowS
showsPrec :: Int -> TickyFlags -> ShowS
$cshow :: TickyFlags -> String
show :: TickyFlags -> String
$cshowList :: [TickyFlags] -> ShowS
showList :: [TickyFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. TickyFlags -> Rep TickyFlags x)
-> (forall x. Rep TickyFlags x -> TickyFlags) -> Generic TickyFlags
forall x. Rep TickyFlags x -> TickyFlags
forall x. TickyFlags -> Rep TickyFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TickyFlags -> Rep TickyFlags x
from :: forall x. TickyFlags -> Rep TickyFlags x
$cto :: forall x. Rep TickyFlags x -> TickyFlags
to :: forall x. Rep TickyFlags x -> TickyFlags
Generic -- ^ @since base-4.15.0.0
               )

-- | Parameters pertaining to parallelism
--
-- @since base-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 ( Int -> ParFlags -> ShowS
[ParFlags] -> ShowS
ParFlags -> String
(Int -> ParFlags -> ShowS)
-> (ParFlags -> String) -> ([ParFlags] -> ShowS) -> Show ParFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParFlags -> ShowS
showsPrec :: Int -> ParFlags -> ShowS
$cshow :: ParFlags -> String
show :: ParFlags -> String
$cshowList :: [ParFlags] -> ShowS
showList :: [ParFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
             , (forall x. ParFlags -> Rep ParFlags x)
-> (forall x. Rep ParFlags x -> ParFlags) -> Generic ParFlags
forall x. Rep ParFlags x -> ParFlags
forall x. ParFlags -> Rep ParFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParFlags -> Rep ParFlags x
from :: forall x. ParFlags -> Rep ParFlags x
$cto :: forall x. Rep ParFlags x -> ParFlags
to :: forall x. Rep ParFlags x -> ParFlags
Generic -- ^ @since base-4.15.0.0
             )

-- | Parameters pertaining to Haskell program coverage (HPC)
--
-- @since base-4.20.0.0
data HpcFlags = HpcFlags
    { HpcFlags -> Bool
writeTixFile :: Bool
      -- ^ Controls whether the @<program>.tix@ file should be
      -- written after the execution of the program.
    }
    deriving (Int -> HpcFlags -> ShowS
[HpcFlags] -> ShowS
HpcFlags -> String
(Int -> HpcFlags -> ShowS)
-> (HpcFlags -> String) -> ([HpcFlags] -> ShowS) -> Show HpcFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HpcFlags -> ShowS
showsPrec :: Int -> HpcFlags -> ShowS
$cshow :: HpcFlags -> String
show :: HpcFlags -> String
$cshowList :: [HpcFlags] -> ShowS
showList :: [HpcFlags] -> ShowS
Show -- ^ @since base-4.20.0.0
             , (forall x. HpcFlags -> Rep HpcFlags x)
-> (forall x. Rep HpcFlags x -> HpcFlags) -> Generic HpcFlags
forall x. Rep HpcFlags x -> HpcFlags
forall x. HpcFlags -> Rep HpcFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HpcFlags -> Rep HpcFlags x
from :: forall x. HpcFlags -> Rep HpcFlags x
$cto :: forall x. Rep HpcFlags x -> HpcFlags
to :: forall x. Rep HpcFlags x -> HpcFlags
Generic -- ^ @since base-4.20.0.0
             )
-- | Parameters of the runtime system
--
-- @since base-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
    , RTSFlags -> HpcFlags
hpcFlags        :: HpcFlags
    } deriving ( Int -> RTSFlags -> ShowS
[RTSFlags] -> ShowS
RTSFlags -> String
(Int -> RTSFlags -> ShowS)
-> (RTSFlags -> String) -> ([RTSFlags] -> ShowS) -> Show RTSFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RTSFlags -> ShowS
showsPrec :: Int -> RTSFlags -> ShowS
$cshow :: RTSFlags -> String
show :: RTSFlags -> String
$cshowList :: [RTSFlags] -> ShowS
showList :: [RTSFlags] -> ShowS
Show -- ^ @since base-4.8.0.0
               , (forall x. RTSFlags -> Rep RTSFlags x)
-> (forall x. Rep RTSFlags x -> RTSFlags) -> Generic RTSFlags
forall x. Rep RTSFlags x -> RTSFlags
forall x. RTSFlags -> Rep RTSFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RTSFlags -> Rep RTSFlags x
from :: forall x. RTSFlags -> Rep RTSFlags x
$cto :: forall x. Rep RTSFlags x -> RTSFlags
to :: forall x. Rep RTSFlags x -> RTSFlags
Generic -- ^ @since base-4.15.0.0
               )

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

getRTSFlags :: IO RTSFlags
getRTSFlags :: IO RTSFlags
getRTSFlags =
  GCFlags
-> ConcFlags
-> MiscFlags
-> DebugFlags
-> CCFlags
-> ProfFlags
-> TraceFlags
-> TickyFlags
-> ParFlags
-> HpcFlags
-> RTSFlags
RTSFlags (GCFlags
 -> ConcFlags
 -> MiscFlags
 -> DebugFlags
 -> CCFlags
 -> ProfFlags
 -> TraceFlags
 -> TickyFlags
 -> ParFlags
 -> HpcFlags
 -> RTSFlags)
-> IO GCFlags
-> IO
     (ConcFlags
      -> MiscFlags
      -> DebugFlags
      -> CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> HpcFlags
      -> 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
   -> HpcFlags
   -> RTSFlags)
-> IO ConcFlags
-> IO
     (MiscFlags
      -> DebugFlags
      -> CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> HpcFlags
      -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO ConcFlags
getConcFlags
           IO
  (MiscFlags
   -> DebugFlags
   -> CCFlags
   -> ProfFlags
   -> TraceFlags
   -> TickyFlags
   -> ParFlags
   -> HpcFlags
   -> RTSFlags)
-> IO MiscFlags
-> IO
     (DebugFlags
      -> CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> HpcFlags
      -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO MiscFlags
getMiscFlags
           IO
  (DebugFlags
   -> CCFlags
   -> ProfFlags
   -> TraceFlags
   -> TickyFlags
   -> ParFlags
   -> HpcFlags
   -> RTSFlags)
-> IO DebugFlags
-> IO
     (CCFlags
      -> ProfFlags
      -> TraceFlags
      -> TickyFlags
      -> ParFlags
      -> HpcFlags
      -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO DebugFlags
getDebugFlags
           IO
  (CCFlags
   -> ProfFlags
   -> TraceFlags
   -> TickyFlags
   -> ParFlags
   -> HpcFlags
   -> RTSFlags)
-> IO CCFlags
-> IO
     (ProfFlags
      -> TraceFlags -> TickyFlags -> ParFlags -> HpcFlags -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO CCFlags
getCCFlags
           IO
  (ProfFlags
   -> TraceFlags -> TickyFlags -> ParFlags -> HpcFlags -> RTSFlags)
-> IO ProfFlags
-> IO
     (TraceFlags -> TickyFlags -> ParFlags -> HpcFlags -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO ProfFlags
getProfFlags
           IO (TraceFlags -> TickyFlags -> ParFlags -> HpcFlags -> RTSFlags)
-> IO TraceFlags
-> IO (TickyFlags -> ParFlags -> HpcFlags -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO TraceFlags
getTraceFlags
           IO (TickyFlags -> ParFlags -> HpcFlags -> RTSFlags)
-> IO TickyFlags -> IO (ParFlags -> HpcFlags -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO TickyFlags
getTickyFlags
           IO (ParFlags -> HpcFlags -> RTSFlags)
-> IO ParFlags -> IO (HpcFlags -> RTSFlags)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO ParFlags
getParFlags
           IO (HpcFlags -> RTSFlags) -> IO HpcFlags -> IO RTSFlags
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO HpcFlags
getHpcFlags

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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
  | Bool
otherwise      = Maybe String -> IO (Maybe String)
forall a. a -> IO a
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 a. a -> IO a
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 458 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  GCFlags <$> (peekFilePath =<< (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr)
{-# LINE 459 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toEnum . fromIntegral <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO Word32))
{-# LINE 461 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr
{-# LINE 462 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 463 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 20) ptr
{-# LINE 464 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 465 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 466 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 467 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 36) ptr
{-# LINE 468 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr
{-# LINE 469 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 44) ptr
{-# LINE 470 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr
{-# LINE 471 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 52) ptr :: IO CBool))
{-# LINE 473 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr
{-# LINE 474 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr
{-# LINE 475 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr
{-# LINE 476 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 84) ptr
{-# LINE 477 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 88) ptr :: IO CBool))
{-# LINE 479 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 89) ptr :: IO CBool))
{-# LINE 481 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 96) ptr
{-# LINE 482 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 104) ptr :: IO CBool))
{-# LINE 484 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 105) ptr :: IO CBool))
{-# LINE 486 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 112) ptr
{-# LINE 487 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 128) ptr :: IO CBool))
{-# LINE 489 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 144) ptr
{-# LINE 490 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 152) ptr
{-# LINE 491 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (toBool <$>
                ((\hsc_ptr -> peekByteOff hsc_ptr 168) ptr :: IO CBool))
{-# LINE 493 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 176) ptr
{-# LINE 494 "libraries/ghc-internal/src/GHC/Internal/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
448)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 498 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  ParFlags
    <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 500 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 502 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 503 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 505 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 506 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr :: IO CBool))
{-# LINE 508 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 509 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 510 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 511 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
    <*> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 36) ptr :: IO CBool))
{-# LINE 513 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}


getHpcFlags :: IO HpcFlags
getHpcFlags :: IO HpcFlags
getHpcFlags = 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
488)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 518 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  HpcFlags
    <$> (toBool <$>
          ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 521 "libraries/ghc-internal/src/GHC/Internal/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
192)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 525 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  ConcFlags <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 526 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 527 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

{-# INLINEABLE getMiscFlags #-}
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
208)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 532 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  MiscFlags <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 533 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 535 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 537 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 539 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 541 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 543 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 13) ptr :: IO CBool))
{-# LINE 545 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 14) ptr :: IO CBool))
{-# LINE 547 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 15) ptr :: IO CBool))
{-# LINE 549 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 550 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toEnum . fromIntegral
                 <$> ((\hsc_ptr -> peekByteOff hsc_ptr 24) ptr :: IO Word32))
{-# LINE 552 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (fromIntegral
                 <$> ((\hsc_ptr -> peekByteOff hsc_ptr 28) ptr :: IO Word32))
{-# LINE 554 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}

{- Note [The need for getIoManagerFlag]
   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

   GHC supports both the new WINIO manager
   as well as the old MIO one. In order to
   decide which code path to take we often
   have to inspect what the user selected at
   RTS startup.

   We could use getMiscFlags but then we end up with core containing
   reads for all MiscFlags. These won't be eliminated at the core level
   even if it's obvious we will only look at the ioManager part of the
   ADT.

   We could add a INLINE pragma, but that just means whatever we inline
   into is likely to be inlined. So rather than adding a dozen pragmas
   we expose a lean way to query this particular flag. It's not satisfying
   but it works well enough and allows these checks to be inlined nicely.

-}

{-# INLINE getIoManagerFlag #-}
-- | Needed to optimize support for different IO Managers on Windows.
-- See Note [The need for getIoManagerFlag]
getIoManagerFlag :: IO IoSubSystem
getIoManagerFlag :: IO IoSubSystem
getIoManagerFlag = 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
208)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 582 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
      mgrFlag <- ((\hsc_ptr -> peekByteOff hsc_ptr 24) ptr :: IO Word32)
{-# LINE 583 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
      return $ (toEnum . fromIntegral) mgrFlag

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
240)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 588 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  DebugFlags <$> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 590 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 1) ptr :: IO CBool))
{-# LINE 592 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 2) ptr :: IO CBool))
{-# LINE 594 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 3) ptr :: IO CBool))
{-# LINE 596 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 598 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 5) ptr :: IO CBool))
{-# LINE 600 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO CBool))
{-# LINE 602 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 7) ptr :: IO CBool))
{-# LINE 604 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 606 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 608 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 610 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 13) ptr :: IO CBool))
{-# LINE 612 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 14) ptr :: IO CBool))
{-# LINE 614 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 15) ptr :: IO CBool))
{-# LINE 616 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 16) ptr :: IO CBool))
{-# LINE 618 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 17) ptr :: IO CBool))
{-# LINE 620 "libraries/ghc-internal/src/GHC/Internal/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 624 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  CCFlags <$> (toEnum . fromIntegral
                <$> ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO Word32))
{-# LINE 626 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 627 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
          <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 628 "libraries/ghc-internal/src/GHC/Internal/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
288)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 632 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  ProfFlags <$> (toEnum <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr)
{-# LINE 633 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 634 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 635 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr :: IO CBool))
{-# LINE 637 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 21) ptr :: IO CBool))
{-# LINE 639 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 23) ptr :: IO CBool))
{-# LINE 641 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (toBool <$>
                  ((\hsc_ptr -> peekByteOff hsc_ptr 22) ptr :: IO CBool))
{-# LINE 643 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 644 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 645 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr)
{-# LINE 646 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr)
{-# LINE 647 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr)
{-# LINE 648 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr)
{-# LINE 649 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr)
{-# LINE 650 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr)
{-# LINE 651 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 88) ptr)
{-# LINE 652 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
            <*> (\hsc_ptr -> peekByteOff hsc_ptr 80) ptr
{-# LINE 653 "libraries/ghc-internal/src/GHC/Internal/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
384)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 657 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  TraceFlags <$> (toEnum . fromIntegral
                   <$> ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CInt))
{-# LINE 659 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 661 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 5) ptr :: IO CBool))
{-# LINE 663 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO CBool))
{-# LINE 665 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 7) ptr :: IO CBool))
{-# LINE 667 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 669 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 671 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 673 "libraries/ghc-internal/src/GHC/Internal/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
432)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 677 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
  TickyFlags <$> (toBool <$>
                   ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 679 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}
             <*> (peekFilePath =<< (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr)
{-# LINE 680 "libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc" #-}