-- | Types related to late cost center insertion
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

-- | Late cost center insertion configuration.
--
-- Specifies whether cost centers are added to overloaded function call sites
-- and/or top-level bindings, and which top-level bindings they are added to.
-- Also holds the cost center insertion environment.
data LateCCConfig =
      LateCCConfig
        { LateCCConfig -> LateCCBindSpec
lateCCConfig_whichBinds :: !LateCCBindSpec
        , LateCCConfig -> Bool
lateCCConfig_overloadedCalls :: !Bool
        , LateCCConfig -> LateCCEnv
lateCCConfig_env :: !LateCCEnv
        }

-- | The types of top-level bindings we support adding cost centers to.
data LateCCBindSpec =
      LateCCNone
    | LateCCAllBinds
    | LateCCOverloadedBinds

-- | Late cost centre insertion environment
data LateCCEnv = LateCCEnv
  { LateCCEnv -> Module
lateCCEnv_module :: !Module
    -- ^ Current module
  , LateCCEnv -> Maybe FastString
lateCCEnv_file :: Maybe FastString
    -- ^ Current file, if we have one
  , LateCCEnv -> Bool
lateCCEnv_countEntries:: !Bool
    -- ^ Whether the inserted cost centers should count entries
  , LateCCEnv -> Bool
lateCCEnv_collectCCs  :: !Bool
    -- ^ Whether to collect the cost centres we insert. See
    -- Note [Collecting late cost centres]

  }

-- | Late cost centre insertion state, indexed by some extra state type that an
-- insertion method may require.
data LateCCState s = LateCCState
    { forall s. LateCCState s -> Set CostCentre
lateCCState_ccs :: !(S.Set CostCentre)
      -- ^ Cost centres that have been inserted
    , forall s. LateCCState s -> CostCentreState
lateCCState_ccState :: !CostCentreState
      -- ^ Per-module state tracking for cost centre indices
    , forall s. LateCCState s -> s
lateCCState_extra :: !s
    }

-- | The empty late cost centre insertion state
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
      }

-- | Late cost centre insertion monad
type LateCCM s = ReaderT LateCCEnv (State (LateCCState s))