Safe Haskell | Safe-Infered |
---|
- staticFlags :: [String]
- initStaticOpts :: IO ()
- data WayName
- = WayThreaded
- | WayDebug
- | WayProf
- | WayEventLog
- | WayPar
- | WayGran
- | WayNDP
- | WayDyn
- data Way = Way {}
- v_Ways :: IORef [Way]
- isRTSWay :: WayName -> Bool
- mkBuildTag :: [Way] -> String
- opt_PprUserLength :: Int
- opt_PprCols :: Int
- opt_PprCaseAsLet :: Bool
- opt_PprStyle_Debug :: Bool
- opt_TraceLevel :: Int
- opt_NoDebugOutput :: Bool
- opt_SuppressAll :: Bool
- opt_SuppressUniques :: Bool
- opt_SuppressCoercions :: Bool
- opt_SuppressModulePrefixes :: Bool
- opt_SuppressTypeApplications :: Bool
- opt_SuppressIdInfo :: Bool
- opt_SuppressTypeSignatures :: Bool
- opt_SuppressVarKinds :: Bool
- opt_SccProfilingOn :: Bool
- opt_Hpc :: Bool
- opt_DictsStrict :: Bool
- opt_IrrefutableTuples :: Bool
- opt_Parallel :: Bool
- opt_NoStateHack :: Bool
- opt_SimpleListLiterals :: Bool
- opt_CprOff :: Bool
- opt_SimplNoPreInlining :: Bool
- opt_SimplExcessPrecision :: Bool
- opt_NoOptCoercion :: Bool
- opt_MaxWorkerArgs :: Int
- opt_UF_CreationThreshold, opt_UF_UseThreshold :: Int
- opt_UF_DearOp, opt_UF_DictDiscount, opt_UF_FunAppDiscount :: Int
- opt_UF_KeenessFactor :: Float
- opt_Fuel :: Int
- opt_PIC :: Bool
- opt_Static :: Bool
- opt_IgnoreDotGhci :: Bool
- opt_GhciScripts :: [String]
- opt_ErrorSpans :: Bool
- opt_GranMacros :: Bool
- opt_HiVersion :: Integer
- opt_HistorySize :: Int
- opt_Unregisterised :: Bool
- v_Ld_inputs :: IORef [String]
- tablesNextToCode :: Bool
- opt_StubDeadValues :: Bool
- opt_Ticky :: Bool
- addOpt :: String -> IO ()
- removeOpt :: String -> IO ()
- addWay :: WayName -> IO ()
- getWayFlags :: IO [String]
- v_opt_C_ready :: IORef Bool
- saveStaticFlagGlobals :: IO (Bool, [String], [Way])
- restoreStaticFlagGlobals :: (Bool, [String], [Way]) -> IO ()
Documentation
staticFlags :: [String]Source
initStaticOpts :: IO ()Source
mkBuildTag :: [Way] -> StringSource
Set the maximum width of the dumps If GHC's command line options are bad then the options parser uses the pretty printer display the error message. In this case the staticFlags won't be initialized yet, so we must check for this case explicitly and return the default value.
opt_PprCaseAsLet :: BoolSource
Display case expressions with a single alternative as strict let bindings
Suppress all that is suppressable in core dumps. Except for uniques, as some simplifier phases introduce new varibles that have otherwise identical names.
opt_SuppressUniques :: BoolSource
Suppress unique ids on variables. Except for uniques, as some simplifier phases introduce new variables that have otherwise identical names.
opt_SuppressCoercions :: BoolSource
Suppress all coercions, them replacing with ...
opt_SuppressModulePrefixes :: BoolSource
Suppress module id prefixes on variables.
opt_SuppressTypeApplications :: BoolSource
Suppress type applications.
opt_SuppressIdInfo :: BoolSource
Suppress info such as arity and unfoldings on identifiers.
opt_SuppressTypeSignatures :: BoolSource
Suppress separate type signatures in core, but leave types on lambda bound vars
v_Ld_inputs :: IORef [String]Source
getWayFlags :: IO [String]Source