module StaticFlags (
staticFlags,
initStaticOpts,
WayName(..), Way(..), v_Ways, isRTSWay, mkBuildTag,
opt_PprUserLength,
opt_SuppressUniques,
opt_SuppressCoercions,
opt_SuppressModulePrefixes,
opt_PprStyle_Debug, opt_TraceLevel,
opt_NoDebugOutput,
opt_SccProfilingOn,
opt_Hpc,
opt_DictsStrict,
opt_IrrefutableTuples,
opt_Parallel,
opt_DsMultiTyVar,
opt_NoStateHack,
opt_SimpleListLiterals,
opt_CprOff,
opt_SimplNoPreInlining,
opt_SimplExcessPrecision,
opt_MaxWorkerArgs,
opt_UF_CreationThreshold,
opt_UF_UseThreshold,
opt_UF_FunAppDiscount,
opt_UF_DictDiscount,
opt_UF_KeenessFactor,
opt_UF_DearOp,
opt_Fuel,
opt_PIC,
opt_Static,
opt_IgnoreDotGhci,
opt_ErrorSpans,
opt_GranMacros,
opt_HiVersion,
opt_HistorySize,
opt_OmitBlackHoling,
opt_Unregisterised,
v_Ld_inputs,
tablesNextToCode,
opt_StubDeadValues,
opt_Ticky,
addOpt, removeOpt, addWay, getWayFlags, v_opt_C_ready
) where
#include "HsVersions.h"
import Config
import FastString
import Util
import Maybes ( firstJusts )
import Panic
import Data.Maybe ( listToMaybe )
import Data.IORef
import System.IO.Unsafe ( unsafePerformIO )
import Data.List
initStaticOpts :: IO ()
initStaticOpts = writeIORef v_opt_C_ready True
addOpt :: String -> IO ()
addOpt = consIORef v_opt_C
addWay :: WayName -> IO ()
addWay = consIORef v_Ways . lkupWay
removeOpt :: String -> IO ()
removeOpt f = do
fs <- readIORef v_opt_C
writeIORef v_opt_C $! filter (/= f) fs
lookUp :: FastString -> Bool
lookup_def_int :: String -> Int -> Int
lookup_def_float :: String -> Float -> Float
lookup_str :: String -> Maybe String
GLOBAL_VAR(v_opt_C, defaultStaticOpts, [String])
GLOBAL_VAR(v_opt_C_ready, False, Bool)
staticFlags :: [String]
staticFlags = unsafePerformIO $ do
ready <- readIORef v_opt_C_ready
if (not ready)
then panic "Static flags have not been initialised!\n Please call GHC.newSession or GHC.parseStaticFlags early enough."
else readIORef v_opt_C
defaultStaticOpts :: [String]
defaultStaticOpts = ["-static"]
packed_static_opts :: [FastString]
packed_static_opts = map mkFastString staticFlags
lookUp sw = sw `elem` packed_static_opts
lookup_str sw
= case firstJusts (map (stripPrefix sw) staticFlags) of
Just ('=' : str) -> Just str
Just str -> Just str
Nothing -> Nothing
lookup_def_int sw def = case (lookup_str sw) of
Nothing -> def
Just xx -> try_read sw xx
lookup_def_float sw def = case (lookup_str sw) of
Nothing -> def
Just xx -> try_read sw xx
try_read :: Read a => String -> String -> a
try_read sw str
= case reads str of
((x,_):_) -> x
[] -> ghcError (UsageError ("Malformed argument " ++ str ++ " for flag " ++ sw))
opt_IgnoreDotGhci :: Bool
opt_IgnoreDotGhci = lookUp (fsLit "-ignore-dot-ghci")
opt_SuppressUniques :: Bool
opt_SuppressUniques = lookUp (fsLit "-dsuppress-uniques")
opt_SuppressCoercions :: Bool
opt_SuppressCoercions = lookUp (fsLit "-dsuppress-coercions")
opt_SuppressModulePrefixes :: Bool
opt_SuppressModulePrefixes = lookUp (fsLit "-dsuppress-module-prefixes")
opt_PprStyle_Debug :: Bool
opt_PprStyle_Debug = lookUp (fsLit "-dppr-debug")
opt_TraceLevel :: Int
opt_TraceLevel = lookup_def_int "-dtrace-level" 1
opt_PprUserLength :: Int
opt_PprUserLength = lookup_def_int "-dppr-user-length" 5
opt_Fuel :: Int
opt_Fuel = lookup_def_int "-dopt-fuel" maxBound
opt_NoDebugOutput :: Bool
opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output")
opt_SccProfilingOn :: Bool
opt_SccProfilingOn = lookUp (fsLit "-fscc-profiling")
opt_Hpc :: Bool
opt_Hpc = lookUp (fsLit "-fhpc")
opt_DictsStrict :: Bool
opt_DictsStrict = lookUp (fsLit "-fdicts-strict")
opt_IrrefutableTuples :: Bool
opt_IrrefutableTuples = lookUp (fsLit "-firrefutable-tuples")
opt_Parallel :: Bool
opt_Parallel = lookUp (fsLit "-fparallel")
opt_DsMultiTyVar :: Bool
opt_DsMultiTyVar = not (lookUp (fsLit "-fno-ds-multi-tyvar"))
opt_SimpleListLiterals :: Bool
opt_SimpleListLiterals = lookUp (fsLit "-fsimple-list-literals")
opt_NoStateHack :: Bool
opt_NoStateHack = lookUp (fsLit "-fno-state-hack")
opt_CprOff :: Bool
opt_CprOff = lookUp (fsLit "-fcpr-off")
opt_MaxWorkerArgs :: Int
opt_MaxWorkerArgs = lookup_def_int "-fmax-worker-args" (10::Int)
opt_GranMacros :: Bool
opt_GranMacros = lookUp (fsLit "-fgransim")
opt_HiVersion :: Integer
opt_HiVersion = read (cProjectVersionInt ++ cProjectPatchLevel) :: Integer
opt_HistorySize :: Int
opt_HistorySize = lookup_def_int "-fhistory-size" 20
opt_OmitBlackHoling :: Bool
opt_OmitBlackHoling = lookUp (fsLit "-dno-black-holing")
opt_StubDeadValues :: Bool
opt_StubDeadValues = lookUp (fsLit "-dstub-dead-values")
opt_SimplNoPreInlining :: Bool
opt_SimplNoPreInlining = lookUp (fsLit "-fno-pre-inlining")
opt_SimplExcessPrecision :: Bool
opt_SimplExcessPrecision = lookUp (fsLit "-fexcess-precision")
opt_UF_CreationThreshold, opt_UF_UseThreshold :: Int
opt_UF_DearOp, opt_UF_FunAppDiscount, opt_UF_DictDiscount :: Int
opt_UF_KeenessFactor :: Float
opt_UF_CreationThreshold = lookup_def_int "-funfolding-creation-threshold" (45::Int)
opt_UF_UseThreshold = lookup_def_int "-funfolding-use-threshold" (6::Int)
opt_UF_FunAppDiscount = lookup_def_int "-funfolding-fun-discount" (6::Int)
opt_UF_DictDiscount = lookup_def_int "-funfolding-dict-discount" (3::Int)
opt_UF_KeenessFactor = lookup_def_float "-funfolding-keeness-factor" (1.5::Float)
opt_UF_DearOp = ( 4 :: Int)
opt_PIC :: Bool
#if darwin_TARGET_OS && x86_64_TARGET_ARCH
opt_PIC = True
#elif darwin_TARGET_OS
opt_PIC = lookUp (fsLit "-fPIC") || not opt_Static
#else
opt_PIC = lookUp (fsLit "-fPIC")
#endif
opt_Static :: Bool
opt_Static = lookUp (fsLit "-static")
opt_Unregisterised :: Bool
opt_Unregisterised = lookUp (fsLit "-funregisterised")
tablesNextToCode :: Bool
tablesNextToCode = not opt_Unregisterised
&& cGhcEnableTablesNextToCode == "YES"
opt_ErrorSpans :: Bool
opt_ErrorSpans = lookUp (fsLit "-ferror-spans")
opt_Ticky :: Bool
opt_Ticky = lookUp (fsLit "-ticky")
GLOBAL_VAR(v_Ld_inputs, [], [String])
data WayName
= WayThreaded
| WayDebug
| WayProf
| WayEventLog
| WayPar
| WayGran
| WayNDP
| WayDyn
deriving (Eq,Ord)
GLOBAL_VAR(v_Ways, [] ,[Way])
allowed_combination :: [WayName] -> Bool
allowed_combination way = and [ x `allowedWith` y
| x <- way, y <- way, x < y ]
where
_ `allowedWith` WayDyn = True
WayDyn `allowedWith` _ = True
_ `allowedWith` WayDebug = True
WayDebug `allowedWith` _ = True
WayProf `allowedWith` WayNDP = True
WayThreaded `allowedWith` WayProf = True
WayThreaded `allowedWith` WayEventLog = True
_ `allowedWith` _ = False
getWayFlags :: IO [String]
getWayFlags = do
unsorted <- readIORef v_Ways
let ways = sortBy (compare `on` wayName) $
nubBy ((==) `on` wayName) $ unsorted
writeIORef v_Ways ways
if not (allowed_combination (map wayName ways))
then ghcError (CmdLineError $
"combination not supported: " ++
foldr1 (\a b -> a ++ '/':b)
(map wayDesc ways))
else
return (concatMap wayOpts ways)
mkBuildTag :: [Way] -> String
mkBuildTag ways = concat (intersperse "_" (map wayTag ways))
lkupWay :: WayName -> Way
lkupWay w =
case listToMaybe (filter ((==) w . wayName) way_details) of
Nothing -> error "findBuildTag"
Just details -> details
isRTSWay :: WayName -> Bool
isRTSWay = wayRTSOnly . lkupWay
data Way = Way {
wayName :: WayName,
wayTag :: String,
wayRTSOnly :: Bool,
wayDesc :: String,
wayOpts :: [String]
}
way_details :: [ Way ]
way_details =
[ Way WayThreaded "thr" True "Threaded" [
#if defined(freebsd_TARGET_OS)
"-optl-lthr"
#elif defined(openbsd_TARGET_OS)
"-optc-pthread"
, "-optl-pthread"
#elif defined(solaris2_TARGET_OS)
"-optl-lrt"
#endif
],
Way WayDebug "debug" True "Debug" [],
Way WayDyn "dyn" False "Dynamic"
[ "-DDYNAMIC"
, "-optc-DDYNAMIC"
#if defined(mingw32_TARGET_OS)
, "-fPIC"
#elif defined(openbsd_TARGET_OS)
, "-optl-pthread"
#endif
],
Way WayProf "p" False "Profiling"
[ "-fscc-profiling"
, "-DPROFILING"
, "-optc-DPROFILING" ],
Way WayEventLog "l" True "RTS Event Logging"
[ "-DTRACING"
, "-optc-DTRACING" ],
Way WayPar "mp" False "Parallel"
[ "-fparallel"
, "-D__PARALLEL_HASKELL__"
, "-optc-DPAR"
, "-package concurrent"
, "-optc-w"
, "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
, "-optl-lpvm3"
, "-optl-lgpvm3" ],
Way WayPar "mt" False "Parallel ticky profiling"
[ "-fparallel"
, "-D__PARALLEL_HASKELL__"
, "-optc-DPAR"
, "-optc-DPAR_TICKY"
, "-package concurrent"
, "-optc-w"
, "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
, "-optl-lpvm3"
, "-optl-lgpvm3" ],
Way WayPar "md" False "Distributed"
[ "-fparallel"
, "-D__PARALLEL_HASKELL__"
, "-D__DISTRIBUTED_HASKELL__"
, "-optc-DPAR"
, "-optc-DDIST"
, "-package concurrent"
, "-optc-w"
, "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
, "-optl-lpvm3"
, "-optl-lgpvm3" ],
Way WayGran "mg" False "GranSim"
[ "-fgransim"
, "-D__GRANSIM__"
, "-optc-DGRAN"
, "-package concurrent" ],
Way WayNDP "ndp" False "Nested data parallelism"
[ "-XParr"
, "-fvectorise"]
]