module GHC.Core.LateCC.Types
( LateCCConfig(..)
, LateCCBindSpec(..)
, LateCCEnv(..)
, LateCCState(..)
, initLateCCState
, LateCCM
) where
import GHC.Prelude
import Control.Monad.Trans.Reader
import Control.Monad.Trans.State.Strict
import qualified Data.Set as S
import GHC.Data.FastString
import GHC.Types.CostCentre
import GHC.Types.CostCentre.State
import GHC.Unit.Types
data LateCCConfig =
LateCCConfig
{ LateCCConfig -> LateCCBindSpec
lateCCConfig_whichBinds :: !LateCCBindSpec
, LateCCConfig -> Bool
lateCCConfig_overloadedCalls :: !Bool
, LateCCConfig -> LateCCEnv
lateCCConfig_env :: !LateCCEnv
}
data LateCCBindSpec =
LateCCNone
| LateCCBinds
| LateCCOverloadedBinds
data LateCCEnv = LateCCEnv
{ LateCCEnv -> Module
lateCCEnv_module :: !Module
, LateCCEnv -> Maybe FastString
lateCCEnv_file :: Maybe FastString
, LateCCEnv -> Bool
lateCCEnv_countEntries:: !Bool
, LateCCEnv -> Bool
lateCCEnv_collectCCs :: !Bool
}
data LateCCState s = LateCCState
{ forall s. LateCCState s -> Set CostCentre
lateCCState_ccs :: !(S.Set CostCentre)
, forall s. LateCCState s -> CostCentreState
lateCCState_ccState :: !CostCentreState
, :: !s
}
initLateCCState :: s -> LateCCState s
initLateCCState :: forall s. s -> LateCCState s
initLateCCState s
s =
LateCCState
{ lateCCState_ccState :: CostCentreState
lateCCState_ccState = CostCentreState
newCostCentreState
, lateCCState_ccs :: Set CostCentre
lateCCState_ccs = Set CostCentre
forall a. Monoid a => a
mempty
, lateCCState_extra :: s
lateCCState_extra = s
s
}
type LateCCM s = ReaderT LateCCEnv (State (LateCCState s))