{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module GHC.Types.CostCentre.State
   ( CostCentreState
   , newCostCentreState
   , CostCentreIndex
   , unCostCentreIndex
   , getCCIndex
   )
where

import GHC.Prelude
import GHC.Data.FastString
import GHC.Data.FastString.Env

import Data.Data
import GHC.Utils.Binary

-- | Per-module state for tracking cost centre indices.
--
-- See documentation of 'GHC.Types.CostCentre.cc_flavour' for more details.
newtype CostCentreState = CostCentreState (FastStringEnv Int)

-- | Initialize cost centre state.
newCostCentreState :: CostCentreState
newCostCentreState :: CostCentreState
newCostCentreState = FastStringEnv Int -> CostCentreState
CostCentreState FastStringEnv Int
forall a. FastStringEnv a
emptyFsEnv

-- | An index into a given cost centre module,name,flavour set
newtype CostCentreIndex = CostCentreIndex { CostCentreIndex -> Int
unCostCentreIndex :: Int }
  deriving (CostCentreIndex -> CostCentreIndex -> Bool
(CostCentreIndex -> CostCentreIndex -> Bool)
-> (CostCentreIndex -> CostCentreIndex -> Bool)
-> Eq CostCentreIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CostCentreIndex -> CostCentreIndex -> Bool
$c/= :: CostCentreIndex -> CostCentreIndex -> Bool
== :: CostCentreIndex -> CostCentreIndex -> Bool
$c== :: CostCentreIndex -> CostCentreIndex -> Bool
Eq, Eq CostCentreIndex
Eq CostCentreIndex
-> (CostCentreIndex -> CostCentreIndex -> Ordering)
-> (CostCentreIndex -> CostCentreIndex -> Bool)
-> (CostCentreIndex -> CostCentreIndex -> Bool)
-> (CostCentreIndex -> CostCentreIndex -> Bool)
-> (CostCentreIndex -> CostCentreIndex -> Bool)
-> (CostCentreIndex -> CostCentreIndex -> CostCentreIndex)
-> (CostCentreIndex -> CostCentreIndex -> CostCentreIndex)
-> Ord CostCentreIndex
CostCentreIndex -> CostCentreIndex -> Bool
CostCentreIndex -> CostCentreIndex -> Ordering
CostCentreIndex -> CostCentreIndex -> CostCentreIndex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CostCentreIndex -> CostCentreIndex -> CostCentreIndex
$cmin :: CostCentreIndex -> CostCentreIndex -> CostCentreIndex
max :: CostCentreIndex -> CostCentreIndex -> CostCentreIndex
$cmax :: CostCentreIndex -> CostCentreIndex -> CostCentreIndex
>= :: CostCentreIndex -> CostCentreIndex -> Bool
$c>= :: CostCentreIndex -> CostCentreIndex -> Bool
> :: CostCentreIndex -> CostCentreIndex -> Bool
$c> :: CostCentreIndex -> CostCentreIndex -> Bool
<= :: CostCentreIndex -> CostCentreIndex -> Bool
$c<= :: CostCentreIndex -> CostCentreIndex -> Bool
< :: CostCentreIndex -> CostCentreIndex -> Bool
$c< :: CostCentreIndex -> CostCentreIndex -> Bool
compare :: CostCentreIndex -> CostCentreIndex -> Ordering
$ccompare :: CostCentreIndex -> CostCentreIndex -> Ordering
Ord, Typeable CostCentreIndex
Typeable CostCentreIndex
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> CostCentreIndex -> c CostCentreIndex)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c CostCentreIndex)
-> (CostCentreIndex -> Constr)
-> (CostCentreIndex -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c CostCentreIndex))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c CostCentreIndex))
-> ((forall b. Data b => b -> b)
    -> CostCentreIndex -> CostCentreIndex)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> CostCentreIndex -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> CostCentreIndex -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> CostCentreIndex -> m CostCentreIndex)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CostCentreIndex -> m CostCentreIndex)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CostCentreIndex -> m CostCentreIndex)
-> Data CostCentreIndex
CostCentreIndex -> DataType
CostCentreIndex -> Constr
(forall b. Data b => b -> b) -> CostCentreIndex -> CostCentreIndex
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CostCentreIndex -> u
forall u. (forall d. Data d => d -> u) -> CostCentreIndex -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CostCentreIndex
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CostCentreIndex -> c CostCentreIndex
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CostCentreIndex)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CostCentreIndex)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CostCentreIndex -> m CostCentreIndex
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CostCentreIndex -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CostCentreIndex -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> CostCentreIndex -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CostCentreIndex -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CostCentreIndex -> r
gmapT :: (forall b. Data b => b -> b) -> CostCentreIndex -> CostCentreIndex
$cgmapT :: (forall b. Data b => b -> b) -> CostCentreIndex -> CostCentreIndex
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CostCentreIndex)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CostCentreIndex)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CostCentreIndex)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CostCentreIndex)
dataTypeOf :: CostCentreIndex -> DataType
$cdataTypeOf :: CostCentreIndex -> DataType
toConstr :: CostCentreIndex -> Constr
$ctoConstr :: CostCentreIndex -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CostCentreIndex
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CostCentreIndex
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CostCentreIndex -> c CostCentreIndex
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CostCentreIndex -> c CostCentreIndex
Data, BinHandle -> IO CostCentreIndex
BinHandle -> CostCentreIndex -> IO ()
BinHandle -> CostCentreIndex -> IO (Bin CostCentreIndex)
(BinHandle -> CostCentreIndex -> IO ())
-> (BinHandle -> CostCentreIndex -> IO (Bin CostCentreIndex))
-> (BinHandle -> IO CostCentreIndex)
-> Binary CostCentreIndex
forall a.
(BinHandle -> a -> IO ())
-> (BinHandle -> a -> IO (Bin a))
-> (BinHandle -> IO a)
-> Binary a
get :: BinHandle -> IO CostCentreIndex
$cget :: BinHandle -> IO CostCentreIndex
put :: BinHandle -> CostCentreIndex -> IO (Bin CostCentreIndex)
$cput :: BinHandle -> CostCentreIndex -> IO (Bin CostCentreIndex)
put_ :: BinHandle -> CostCentreIndex -> IO ()
$cput_ :: BinHandle -> CostCentreIndex -> IO ()
Binary)

-- | Get a new index for a given cost centre name.
getCCIndex :: FastString
           -> CostCentreState
           -> (CostCentreIndex, CostCentreState)
getCCIndex :: FastString -> CostCentreState -> (CostCentreIndex, CostCentreState)
getCCIndex FastString
nm (CostCentreState FastStringEnv Int
m) =
    (Int -> CostCentreIndex
CostCentreIndex Int
idx, FastStringEnv Int -> CostCentreState
CostCentreState FastStringEnv Int
m')
  where
    m_idx :: Maybe Int
m_idx = FastStringEnv Int -> FastString -> Maybe Int
forall a. FastStringEnv a -> FastString -> Maybe a
lookupFsEnv FastStringEnv Int
m FastString
nm
    idx :: Int
idx = Int -> (Int -> Int) -> Maybe Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 Int -> Int
forall a. a -> a
id Maybe Int
m_idx
    m' :: FastStringEnv Int
m' = FastStringEnv Int -> FastString -> Int -> FastStringEnv Int
forall a. FastStringEnv a -> FastString -> a -> FastStringEnv a
extendFsEnv FastStringEnv Int
m FastString
nm (Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)