-- | The stg to cmm code generator configuration

module GHC.StgToCmm.Config
  ( StgToCmmConfig(..)
  , stgToCmmPlatform
  ) where

import GHC.Platform.Profile
import GHC.Platform
import GHC.Unit.Module
import GHC.Utils.Outputable
import GHC.Utils.TmpFs

import GHC.Prelude


-- This config is static and contains information only passed *downwards* by StgToCmm.Monad
data StgToCmmConfig = StgToCmmConfig
  ----------------------------- General Settings --------------------------------
  { StgToCmmConfig -> Profile
stgToCmmProfile       :: !Profile            -- ^ Current profile
  , StgToCmmConfig -> Module
stgToCmmThisModule    :: Module              -- ^ The module being compiled. This field kept lazy for
                                                 -- Cmm/Parser.y which preloads it with a panic
  , StgToCmmConfig -> TempDir
stgToCmmTmpDir        :: !TempDir            -- ^ Temp Dir for files used in compilation
  , StgToCmmConfig -> SDocContext
stgToCmmContext       :: !SDocContext        -- ^ Context for StgToCmm phase
  , StgToCmmConfig -> Int
stgToCmmDebugLevel    :: !Int                -- ^ The verbosity of debug messages
  , StgToCmmConfig -> Maybe Word
stgToCmmBinBlobThresh :: !(Maybe Word)        -- ^ Threshold at which Binary literals (e.g. strings)
                                                 -- are either dumped to a file and a CmmFileEmbed literal
                                                 -- is emitted (over threshold), or become a CmmString
                                                 -- Literal (under or at threshold). CmmFileEmbed is only supported
                                                 -- with the NCG, thus a Just means two things: We have a threshold,
                                                 -- and will be using the NCG. Conversely, a Nothing implies we are not
                                                 -- using NCG and disables CmmFileEmbed. See Note
                                                 -- [Embedding large binary blobs] in GHC.CmmToAsm.Ppr, and
                                                 -- @cgTopBinding@ in GHC.StgToCmm.
  , StgToCmmConfig -> Int
stgToCmmMaxInlAllocSize :: !Int              -- ^ Max size, in bytes, of inline array allocations.
  ------------------------------ Ticky Options ----------------------------------
  , StgToCmmConfig -> Bool
stgToCmmDoTicky        :: !Bool              -- ^ Ticky profiling enabled (cf @-ticky@)
  , StgToCmmConfig -> Bool
stgToCmmTickyAllocd    :: !Bool              -- ^ True indicates ticky prof traces allocs of each named
                                                 -- thing in addition to allocs _by_ that thing
  , StgToCmmConfig -> Bool
stgToCmmTickyLNE       :: !Bool              -- ^ True indicates ticky uses name-specific counters for
                                                 -- join-points (let-no-escape)
  , StgToCmmConfig -> Bool
stgToCmmTickyDynThunk  :: !Bool              -- ^ True indicates ticky uses name-specific counters for
                                                 -- dynamic thunks
  , StgToCmmConfig -> Bool
stgToCmmTickyTag       :: !Bool              -- ^ True indicates ticky will count number of avoided tag checks by tag inference.
  ---------------------------------- Flags --------------------------------------
  , StgToCmmConfig -> Bool
stgToCmmLoopification  :: !Bool              -- ^ Loopification enabled (cf @-floopification@)
  , StgToCmmConfig -> Bool
stgToCmmAlignCheck     :: !Bool              -- ^ Insert alignment check (cf @-falignment-sanitisation@)
  , StgToCmmConfig -> Bool
stgToCmmOptHpc         :: !Bool              -- ^ perform code generation for code coverage
  , StgToCmmConfig -> Bool
stgToCmmFastPAPCalls   :: !Bool              -- ^
  , StgToCmmConfig -> Bool
stgToCmmSCCProfiling   :: !Bool              -- ^ Check if cost-centre profiling is enabled
  , StgToCmmConfig -> Bool
stgToCmmEagerBlackHole :: !Bool              -- ^
  , StgToCmmConfig -> Bool
stgToCmmInfoTableMap   :: !Bool              -- ^ true means generate C Stub for IPE map, See note [Mapping
                                                 -- Info Tables to Source Positions]
  , StgToCmmConfig -> Bool
stgToCmmOmitYields     :: !Bool              -- ^ true means omit heap checks when no allocation is performed
  , StgToCmmConfig -> Bool
stgToCmmOmitIfPragmas  :: !Bool              -- ^ true means don't generate interface programs (implied by -O0)
  , StgToCmmConfig -> Bool
stgToCmmPIC            :: !Bool              -- ^ true if @-fPIC@
  , StgToCmmConfig -> Bool
stgToCmmPIE            :: !Bool              -- ^ true if @-fPIE@
  , StgToCmmConfig -> Bool
stgToCmmExtDynRefs     :: !Bool              -- ^ true if @-fexternal-dynamic-refs@, meaning generate
                                                 -- code for linking against dynamic libraries
  , StgToCmmConfig -> Bool
stgToCmmDoBoundsCheck  :: !Bool              -- ^ decides whether to check array bounds in StgToCmm.Prim
                                                 -- or not
  , StgToCmmConfig -> Bool
stgToCmmDoTagCheck     :: !Bool              -- ^ Verify tag inference predictions.
  ------------------------------ Backend Flags ----------------------------------
  , StgToCmmConfig -> Bool
stgToCmmAllowBigArith             :: !Bool   -- ^ Allowed to emit larger than native size arithmetic (only LLVM and C backends)
  , StgToCmmConfig -> Bool
stgToCmmAllowQuotRemInstr         :: !Bool   -- ^ Allowed to generate QuotRem instructions
  , StgToCmmConfig -> Bool
stgToCmmAllowQuotRem2             :: !Bool   -- ^ Allowed to generate QuotRem
  , StgToCmmConfig -> Bool
stgToCmmAllowExtendedAddSubInstrs :: !Bool   -- ^ Allowed to generate AddWordC, SubWordC, Add2, etc.
  , StgToCmmConfig -> Bool
stgToCmmAllowIntMul2Instr         :: !Bool   -- ^ Allowed to generate IntMul2 instruction
  , StgToCmmConfig -> Bool
stgToCmmAllowFabsInstrs           :: !Bool   -- ^ Allowed to generate Fabs instructions
  , StgToCmmConfig -> Bool
stgToCmmTickyAP                   :: !Bool   -- ^ Disable use of precomputed standard thunks.
  ------------------------------ SIMD flags ------------------------------------
  -- Each of these flags checks vector compatibility with the backend requested
  -- during compilation. In essence, this means checking for @-fllvm@ which is
  -- the only backend that currently allows SIMD instructions, see
  -- Ghc.StgToCmm.Prim.checkVecCompatibility for these flags only call site.
  , StgToCmmConfig -> Maybe String
stgToCmmVecInstrsErr   :: Maybe String       -- ^ Error (if any) to raise when vector instructions are
                                                 -- used, see @StgToCmm.Prim.checkVecCompatibility@
  , StgToCmmConfig -> Bool
stgToCmmAvx            :: !Bool              -- ^ check for Advanced Vector Extensions
  , StgToCmmConfig -> Bool
stgToCmmAvx2           :: !Bool              -- ^ check for Advanced Vector Extensions 2
  , StgToCmmConfig -> Bool
stgToCmmAvx512f        :: !Bool              -- ^ check for Advanced Vector 512-bit Extensions
  }


stgToCmmPlatform :: StgToCmmConfig -> Platform
stgToCmmPlatform :: StgToCmmConfig -> Platform
stgToCmmPlatform = Profile -> Platform
profilePlatform (Profile -> Platform)
-> (StgToCmmConfig -> Profile) -> StgToCmmConfig -> Platform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StgToCmmConfig -> Profile
stgToCmmProfile