never executed always true always false
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
3 module GHC.Types.CostCentre.State
4 ( CostCentreState
5 , newCostCentreState
6 , CostCentreIndex
7 , unCostCentreIndex
8 , getCCIndex
9 )
10 where
11
12 import GHC.Prelude
13 import GHC.Data.FastString
14 import GHC.Data.FastString.Env
15
16 import Data.Data
17 import GHC.Utils.Binary
18
19 -- | Per-module state for tracking cost centre indices.
20 --
21 -- See documentation of 'GHC.Types.CostCentre.cc_flavour' for more details.
22 newtype CostCentreState = CostCentreState (FastStringEnv Int)
23
24 -- | Initialize cost centre state.
25 newCostCentreState :: CostCentreState
26 newCostCentreState = CostCentreState emptyFsEnv
27
28 -- | An index into a given cost centre module,name,flavour set
29 newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int }
30 deriving (Eq, Ord, Data, Binary)
31
32 -- | Get a new index for a given cost centre name.
33 getCCIndex :: FastString
34 -> CostCentreState
35 -> (CostCentreIndex, CostCentreState)
36 getCCIndex nm (CostCentreState m) =
37 (CostCentreIndex idx, CostCentreState m')
38 where
39 m_idx = lookupFsEnv m nm
40 idx = maybe 0 id m_idx
41 m' = extendFsEnv m nm (idx + 1)