module GHC.Driver.Config.CmmToAsm
( initNCGConfig
)
where
import GHC.Prelude
import GHC.Driver.DynFlags
import GHC.Platform
import GHC.Unit.Types (Module)
import GHC.CmmToAsm.Config
import GHC.Utils.Outputable
import GHC.CmmToAsm.BlockLayout
initNCGConfig :: DynFlags -> Module -> NCGConfig
initNCGConfig :: DynFlags -> Module -> NCGConfig
initNCGConfig DynFlags
dflags Module
this_mod = NCGConfig
{ ncgPlatform :: Platform
ncgPlatform = DynFlags -> Platform
targetPlatform DynFlags
dflags
, ncgThisModule :: Module
ncgThisModule = Module
this_mod
, ncgAsmContext :: SDocContext
ncgAsmContext = DynFlags -> PprStyle -> SDocContext
initSDocContext DynFlags
dflags PprStyle
PprCode
, ncgProcAlignment :: Maybe Int
ncgProcAlignment = DynFlags -> Maybe Int
cmmProcAlignment DynFlags
dflags
, ncgExternalDynamicRefs :: Bool
ncgExternalDynamicRefs = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ExternalDynamicRefs DynFlags
dflags
, ncgPIC :: Bool
ncgPIC = DynFlags -> Bool
positionIndependent DynFlags
dflags
, ncgInlineThresholdMemcpy :: Word
ncgInlineThresholdMemcpy = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word) -> Int -> Word
forall a b. (a -> b) -> a -> b
$ DynFlags -> Int
maxInlineMemcpyInsns DynFlags
dflags
, ncgInlineThresholdMemset :: Word
ncgInlineThresholdMemset = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word) -> Int -> Word
forall a b. (a -> b) -> a -> b
$ DynFlags -> Int
maxInlineMemsetInsns DynFlags
dflags
, ncgSplitSections :: Bool
ncgSplitSections = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_SplitSections DynFlags
dflags
, ncgRegsIterative :: Bool
ncgRegsIterative = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_RegsIterative DynFlags
dflags
, ncgRegsGraph :: Bool
ncgRegsGraph = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_RegsGraph DynFlags
dflags
, ncgAsmLinting :: Bool
ncgAsmLinting = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DoAsmLinting DynFlags
dflags
, ncgCfgWeights :: Weights
ncgCfgWeights = DynFlags -> Weights
cfgWeights DynFlags
dflags
, ncgCfgBlockLayout :: Bool
ncgCfgBlockLayout = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_CfgBlocklayout DynFlags
dflags
, ncgCfgWeightlessLayout :: Bool
ncgCfgWeightlessLayout = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_WeightlessBlocklayout DynFlags
dflags
, ncgDoConstantFolding :: Bool
ncgDoConstantFolding = Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_CoreConstantFolding DynFlags
dflags Bool -> Bool -> Bool
|| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_CmmSink DynFlags
dflags)
, ncgDumpRegAllocStages :: Bool
ncgDumpRegAllocStages = DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_dump_asm_regalloc_stages DynFlags
dflags
, ncgDumpAsmStats :: Bool
ncgDumpAsmStats = DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_dump_asm_stats DynFlags
dflags
, ncgDumpAsmConflicts :: Bool
ncgDumpAsmConflicts = DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_dump_asm_conflicts DynFlags
dflags
, ncgBmiVersion :: Maybe BmiVersion
ncgBmiVersion = case Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) of
Arch
ArchX86_64 -> DynFlags -> Maybe BmiVersion
bmiVersion DynFlags
dflags
Arch
ArchX86 -> DynFlags -> Maybe BmiVersion
bmiVersion DynFlags
dflags
Arch
_ -> Maybe BmiVersion
forall a. Maybe a
Nothing
, ncgSseVersion :: Maybe SseVersion
ncgSseVersion =
let v :: Maybe SseVersion
v | DynFlags -> Maybe SseVersion
sseVersion DynFlags
dflags Maybe SseVersion -> Maybe SseVersion -> Bool
forall a. Ord a => a -> a -> Bool
< SseVersion -> Maybe SseVersion
forall a. a -> Maybe a
Just SseVersion
SSE2 = SseVersion -> Maybe SseVersion
forall a. a -> Maybe a
Just SseVersion
SSE2
| Bool
otherwise = DynFlags -> Maybe SseVersion
sseVersion DynFlags
dflags
in case Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) of
Arch
ArchX86_64 -> Maybe SseVersion
v
Arch
ArchX86 -> Maybe SseVersion
v
Arch
_ -> Maybe SseVersion
forall a. Maybe a
Nothing
, ncgAvxEnabled :: Bool
ncgAvxEnabled = DynFlags -> Bool
isAvxEnabled DynFlags
dflags
, ncgAvx2Enabled :: Bool
ncgAvx2Enabled = DynFlags -> Bool
isAvx2Enabled DynFlags
dflags
, ncgAvx512fEnabled :: Bool
ncgAvx512fEnabled = DynFlags -> Bool
isAvx512fEnabled DynFlags
dflags
, ncgDwarfEnabled :: Bool
ncgDwarfEnabled = OS -> Bool
osElfTarget (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)) Bool -> Bool -> Bool
&& DynFlags -> Int
debugLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
/= Arch
ArchAArch64
, ncgDwarfUnwindings :: Bool
ncgDwarfUnwindings = OS -> Bool
osElfTarget (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)) Bool -> Bool -> Bool
&& DynFlags -> Int
debugLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
, ncgDwarfStripBlockInfo :: Bool
ncgDwarfStripBlockInfo = OS -> Bool
osElfTarget (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)) Bool -> Bool -> Bool
&& DynFlags -> Int
debugLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2
, ncgDwarfSourceNotes :: Bool
ncgDwarfSourceNotes = OS -> Bool
osElfTarget (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)) Bool -> Bool -> Bool
&& DynFlags -> Int
debugLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2
, ncgExposeInternalSymbols :: Bool
ncgExposeInternalSymbols = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ExposeInternalSymbols DynFlags
dflags
, ncgCmmStaticPred :: Bool
ncgCmmStaticPred = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_CmmStaticPred DynFlags
dflags
, ncgEnableShortcutting :: Bool
ncgEnableShortcutting = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_AsmShortcutting DynFlags
dflags
, ncgComputeUnwinding :: Bool
ncgComputeUnwinding = DynFlags -> Int
debugLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
, ncgEnableDeadCodeElimination :: Bool
ncgEnableDeadCodeElimination = Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_InfoTableMap DynFlags
dflags)
Bool -> Bool -> Bool
&& Platform -> Bool
backendMaintainsCfg (DynFlags -> Platform
targetPlatform DynFlags
dflags)
}