-- | Cmm compilation configuration

{-# LANGUAGE DerivingStrategies         #-}

module GHC.Cmm.Config
  ( CmmConfig(..)
  , cmmPlatform
  ) where

import GHC.Prelude

import GHC.Platform
import GHC.Platform.Profile


data CmmConfig = CmmConfig
  { CmmConfig -> Profile
cmmProfile             :: !Profile -- ^ Target Profile
  , CmmConfig -> Bool
cmmOptControlFlow      :: !Bool    -- ^ Optimize Cmm Control Flow or not
  , CmmConfig -> Bool
cmmDoLinting           :: !Bool    -- ^ Do Cmm Linting Optimization or not
  , CmmConfig -> Bool
cmmOptElimCommonBlks   :: !Bool    -- ^ Eliminate common blocks or not
  , CmmConfig -> Bool
cmmOptSink             :: !Bool    -- ^ Perform sink after stack layout or not
  , CmmConfig -> Bool
cmmGenStackUnwindInstr :: !Bool    -- ^ Generate stack unwinding instructions (for debugging)
  , CmmConfig -> Bool
cmmExternalDynamicRefs :: !Bool    -- ^ Generate code to link against dynamic libraries
  , CmmConfig -> Bool
cmmDoCmmSwitchPlans    :: !Bool    -- ^ Should the Cmm pass replace Stg switch statements
  , CmmConfig -> Bool
cmmSplitProcPoints     :: !Bool    -- ^ Should Cmm split proc points or not
  }

-- | retrieve the target Cmm platform
cmmPlatform :: CmmConfig -> Platform
cmmPlatform :: CmmConfig -> Platform
cmmPlatform = Profile -> Platform
profilePlatform forall b c a. (b -> c) -> (a -> b) -> a -> c
. CmmConfig -> Profile
cmmProfile