{-# LINE 1 "GHC/RTS/Flags.hsc" #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
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
type RtsTime = Word64
data GiveGCStats
= NoGCStats
| CollectGCStats
| OneLineGCStats
| SummaryGCStats
| VerboseGCStats
deriving ( Show
)
instance Enum GiveGCStats where
fromEnum :: GiveGCStats -> Int
fromEnum NoGCStats = 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 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)
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
, GCFlags -> Double
compactThreshold :: Double
, GCFlags -> Bool
sweep :: Bool
, GCFlags -> Bool
ringBell :: Bool
, GCFlags -> RtsTime
idleGCDelayTime :: RtsTime
, GCFlags -> Bool
doIdleGC :: Bool
, GCFlags -> Word
heapBase :: Word
, GCFlags -> Word
allocLimitGrace :: Word
, GCFlags -> Bool
numa :: Bool
, GCFlags -> Word
numaMask :: Word
} deriving ( Show
)
data ConcFlags = ConcFlags
{ ConcFlags -> RtsTime
ctxtSwitchTime :: RtsTime
, ConcFlags -> Int
ctxtSwitchTicks :: Int
} deriving ( Show
)
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
internalCounters :: Bool
, MiscFlags -> Word
linkerMemBase :: Word
} deriving ( Show
)
data DebugFlags = DebugFlags
{ DebugFlags -> Bool
scheduler :: Bool
, DebugFlags -> Bool
interpreter :: Bool
, DebugFlags -> Bool
weak :: Bool
, DebugFlags -> Bool
gccafs :: Bool
, DebugFlags -> Bool
gc :: Bool
, DebugFlags -> Bool
block_alloc :: Bool
, DebugFlags -> Bool
sanity :: Bool
, DebugFlags -> Bool
stable :: Bool
, DebugFlags -> Bool
prof :: Bool
, DebugFlags -> Bool
linker :: Bool
, DebugFlags -> Bool
apply :: Bool
, DebugFlags -> Bool
stm :: Bool
, DebugFlags -> Bool
squeeze :: Bool
, DebugFlags -> Bool
hpc :: Bool
, DebugFlags -> Bool
sparks :: Bool
} deriving ( Show
)
data DoCostCentres
= CostCentresNone
| CostCentresSummary
| CostCentresVerbose
| CostCentresAll
| CostCentresJSON
deriving ( Show
)
instance Enum DoCostCentres where
fromEnum :: DoCostCentres -> Int
fromEnum CostCentresNone = 0
{-# LINE 185 "GHC/RTS/Flags.hsc" #-}
fromEnum CostCentresSummary = 1
{-# LINE 186 "GHC/RTS/Flags.hsc" #-}
fromEnum CostCentresVerbose = 2
{-# LINE 187 "GHC/RTS/Flags.hsc" #-}
fromEnum CostCentresAll = 3
{-# LINE 188 "GHC/RTS/Flags.hsc" #-}
fromEnum CostCentresJSON = 4
{-# LINE 189 "GHC/RTS/Flags.hsc" #-}
toEnum :: Int -> DoCostCentres
toEnum 0 = DoCostCentres
CostCentresNone
{-# LINE 191 "GHC/RTS/Flags.hsc" #-}
toEnum 1 = CostCentresSummary
{-# LINE 192 "GHC/RTS/Flags.hsc" #-}
toEnum 2 = CostCentresVerbose
{-# LINE 193 "GHC/RTS/Flags.hsc" #-}
toEnum 3 = CostCentresAll
{-# LINE 194 "GHC/RTS/Flags.hsc" #-}
toEnum 4 = CostCentresJSON
{-# LINE 195 "GHC/RTS/Flags.hsc" #-}
toEnum e = errorWithoutStackTrace ("invalid enum for DoCostCentres: " ++ show e)
data CCFlags = CCFlags
{ CCFlags -> DoCostCentres
doCostCentres :: DoCostCentres
, CCFlags -> Int
profilerTicks :: Int
, CCFlags -> Int
msecsPerTick :: Int
} deriving ( Show
)
data DoHeapProfile
= NoHeapProfiling
| HeapByCCS
| HeapByMod
| HeapByDescr
| HeapByType
| HeapByRetainer
| HeapByLDV
| HeapByClosureType
deriving ( Show
)
instance Enum DoHeapProfile where
fromEnum :: DoHeapProfile -> Int
fromEnum NoHeapProfiling = 0
{-# LINE 225 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByCCS = 1
{-# LINE 226 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByMod = 2
{-# LINE 227 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByDescr = 4
{-# LINE 228 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByType = 5
{-# LINE 229 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByRetainer = 6
{-# LINE 230 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByLDV = 7
{-# LINE 231 "GHC/RTS/Flags.hsc" #-}
fromEnum HeapByClosureType = 8
{-# LINE 232 "GHC/RTS/Flags.hsc" #-}
toEnum :: Int -> DoHeapProfile
toEnum 0 = DoHeapProfile
NoHeapProfiling
{-# LINE 234 "GHC/RTS/Flags.hsc" #-}
toEnum 1 = HeapByCCS
{-# LINE 235 "GHC/RTS/Flags.hsc" #-}
toEnum 2 = HeapByMod
{-# LINE 236 "GHC/RTS/Flags.hsc" #-}
toEnum 4 = HeapByDescr
{-# LINE 237 "GHC/RTS/Flags.hsc" #-}
toEnum 5 = HeapByType
{-# LINE 238 "GHC/RTS/Flags.hsc" #-}
toEnum 6 = HeapByRetainer
{-# LINE 239 "GHC/RTS/Flags.hsc" #-}
toEnum 7 = HeapByLDV
{-# LINE 240 "GHC/RTS/Flags.hsc" #-}
toEnum 8 = HeapByClosureType
{-# LINE 241 "GHC/RTS/Flags.hsc" #-}
toEnum e = errorWithoutStackTrace ("invalid enum for DoHeapProfile: " ++ show e)
data ProfFlags = ProfFlags
{ ProfFlags -> DoHeapProfile
doHeapProfile :: DoHeapProfile
, ProfFlags -> RtsTime
heapProfileInterval :: RtsTime
, ProfFlags -> Word
heapProfileIntervalTicks :: Word
, 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
)
data DoTrace
= TraceNone
| TraceEventLog
| TraceStderr
deriving ( Show
)
instance Enum DoTrace where
fromEnum :: DoTrace -> Int
fromEnum TraceNone = 0
{-# LINE 277 "GHC/RTS/Flags.hsc" #-}
fromEnum TraceEventLog = 1
{-# LINE 278 "GHC/RTS/Flags.hsc" #-}
fromEnum TraceStderr = 2
{-# LINE 279 "GHC/RTS/Flags.hsc" #-}
toEnum :: Int -> DoTrace
toEnum 0 = DoTrace
TraceNone
{-# LINE 281 "GHC/RTS/Flags.hsc" #-}
toEnum 1 = TraceEventLog
{-# LINE 282 "GHC/RTS/Flags.hsc" #-}
toEnum 2 = TraceStderr
{-# LINE 283 "GHC/RTS/Flags.hsc" #-}
toEnum e = errorWithoutStackTrace ("invalid enum for DoTrace: " ++ show e)
data TraceFlags = TraceFlags
{ TraceFlags -> DoTrace
tracing :: DoTrace
, TraceFlags -> Bool
timestamp :: Bool
, TraceFlags -> Bool
traceScheduler :: Bool
, TraceFlags -> Bool
traceGc :: Bool
, TraceFlags -> Bool
sparksSampled :: Bool
, TraceFlags -> Bool
sparksFull :: Bool
, TraceFlags -> Bool
user :: Bool
} deriving ( Show
)
data TickyFlags = TickyFlags
{ TickyFlags -> Bool
showTickyStats :: Bool
, TickyFlags -> Maybe String
tickyFile :: Maybe FilePath
} deriving ( Show
)
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
)
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
)
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 () -> 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 "<filepath>")
peekCStringOpt :: Ptr CChar -> IO (Maybe String)
peekCStringOpt :: Ptr CChar -> IO (Maybe String)
peekCStringOpt ptr :: 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 = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 370 "GHC/RTS/Flags.hsc" #-}
GCFlags <$> (peekFilePath =<< (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr)
{-# LINE 371 "GHC/RTS/Flags.hsc" #-}
<*> (toEnum . fromIntegral <$>
((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO Word32))
{-# LINE 373 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr
{-# LINE 374 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 375 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 20) ptr
{-# LINE 376 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 377 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 378 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 379 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 36) ptr
{-# LINE 380 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr
{-# LINE 381 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 44) ptr
{-# LINE 382 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr
{-# LINE 383 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 52) ptr :: IO CBool))
{-# LINE 385 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr
{-# LINE 386 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr
{-# LINE 387 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr
{-# LINE 388 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 76) ptr :: IO CBool))
{-# LINE 390 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 77) ptr :: IO CBool))
{-# LINE 392 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 80) ptr
{-# LINE 393 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 88) ptr :: IO CBool))
{-# LINE 395 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 89) ptr :: IO CBool))
{-# LINE 397 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 96) ptr
{-# LINE 398 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 104) ptr :: IO CBool))
{-# LINE 400 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 120) ptr
{-# LINE 401 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 128) ptr
{-# LINE 402 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 144) ptr :: IO CBool))
{-# LINE 404 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 152) ptr
{-# LINE 405 "GHC/RTS/Flags.hsc" #-}
getParFlags :: IO ParFlags
getParFlags :: IO ParFlags
getParFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 376)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 409 "GHC/RTS/Flags.hsc" #-}
ParFlags
<$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 411 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 413 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 414 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 416 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 417 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr :: IO CBool))
{-# LINE 419 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 420 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 421 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 422 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 36) ptr :: IO CBool))
{-# LINE 424 "GHC/RTS/Flags.hsc" #-}
getConcFlags :: IO ConcFlags
getConcFlags :: IO ConcFlags
getConcFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 428 "GHC/RTS/Flags.hsc" #-}
ConcFlags <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 429 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 430 "GHC/RTS/Flags.hsc" #-}
getMiscFlags :: IO MiscFlags
getMiscFlags :: IO MiscFlags
getMiscFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 434 "GHC/RTS/Flags.hsc" #-}
MiscFlags <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 435 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 437 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 439 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 441 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 443 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 445 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 13) ptr :: IO CBool))
{-# LINE 447 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 448 "GHC/RTS/Flags.hsc" #-}
getDebugFlags :: IO DebugFlags
getDebugFlags :: IO DebugFlags
getDebugFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 452 "GHC/RTS/Flags.hsc" #-}
DebugFlags <$> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 454 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 1) ptr :: IO CBool))
{-# LINE 456 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 2) ptr :: IO CBool))
{-# LINE 458 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 3) ptr :: IO CBool))
{-# LINE 460 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 462 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 5) ptr :: IO CBool))
{-# LINE 464 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO CBool))
{-# LINE 466 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 7) ptr :: IO CBool))
{-# LINE 468 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 470 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 472 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 10) ptr :: IO CBool))
{-# LINE 474 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 11) ptr :: IO CBool))
{-# LINE 476 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 12) ptr :: IO CBool))
{-# LINE 478 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 13) ptr :: IO CBool))
{-# LINE 480 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 14) ptr :: IO CBool))
{-# LINE 482 "GHC/RTS/Flags.hsc" #-}
getCCFlags :: IO CCFlags
getCCFlags :: IO CCFlags
getCCFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 486 "GHC/RTS/Flags.hsc" #-}
CCFlags <$> (toEnum . fromIntegral
<$> ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO Word32))
{-# LINE 488 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 489 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 490 "GHC/RTS/Flags.hsc" #-}
getProfFlags :: IO ProfFlags
getProfFlags :: IO ProfFlags
getProfFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 248)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 494 "GHC/RTS/Flags.hsc" #-}
ProfFlags <$> (toEnum <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr)
{-# LINE 495 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 496 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 497 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr :: IO CBool))
{-# LINE 499 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 21) ptr :: IO CBool))
{-# LINE 501 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 502 "GHC/RTS/Flags.hsc" #-}
<*> (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr
{-# LINE 503 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr)
{-# LINE 504 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr)
{-# LINE 505 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr)
{-# LINE 506 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr)
{-# LINE 507 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr)
{-# LINE 508 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr)
{-# LINE 509 "GHC/RTS/Flags.hsc" #-}
<*> (peekCStringOpt =<< (\hsc_ptr -> peekByteOff hsc_ptr 80) ptr)
{-# LINE 510 "GHC/RTS/Flags.hsc" #-}
getTraceFlags :: IO TraceFlags
getTraceFlags :: IO TraceFlags
getTraceFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 336)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 514 "GHC/RTS/Flags.hsc" #-}
TraceFlags <$> (toEnum . fromIntegral
<$> ((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CInt))
{-# LINE 516 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO CBool))
{-# LINE 518 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 5) ptr :: IO CBool))
{-# LINE 520 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO CBool))
{-# LINE 522 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 7) ptr :: IO CBool))
{-# LINE 524 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr :: IO CBool))
{-# LINE 526 "GHC/RTS/Flags.hsc" #-}
<*> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 9) ptr :: IO CBool))
{-# LINE 528 "GHC/RTS/Flags.hsc" #-}
getTickyFlags :: IO TickyFlags
getTickyFlags :: IO TickyFlags
getTickyFlags = do
let ptr :: Ptr b
ptr = ((\hsc_ptr :: Ptr RTSFlags
hsc_ptr -> Ptr RTSFlags
hsc_ptr Ptr RTSFlags -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 360)) Ptr RTSFlags
rtsFlagsPtr
{-# LINE 532 "GHC/RTS/Flags.hsc" #-}
TickyFlags <$> (toBool <$>
((\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO CBool))
{-# LINE 534 "GHC/RTS/Flags.hsc" #-}
<*> (peekFilePath =<< (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr)
{-# LINE 535 "GHC/RTS/Flags.hsc" #-}