module CostCentreState ( CostCentreState, newCostCentreState
                       , CostCentreIndex, unCostCentreIndex, getCCIndex
                       ) where
import GhcPrelude
import FastString
import FastStringEnv
import Data.Data
import Binary
newtype CostCentreState = CostCentreState (FastStringEnv Int)
newCostCentreState :: CostCentreState
newCostCentreState = CostCentreState emptyFsEnv
newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int }
  deriving (Eq, Ord, Data, Binary)
getCCIndex :: FastString
           -> CostCentreState
           -> (CostCentreIndex, CostCentreState)
getCCIndex nm (CostCentreState m) =
    (CostCentreIndex idx, CostCentreState m')
  where
    m_idx = lookupFsEnv m nm
    idx = maybe 0 id m_idx
    m' = extendFsEnv m nm (idx + 1)