{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module GHC.Cmm.BlockId
( BlockId, mkBlockId
, newBlockId
, blockLbl, infoTblLbl
) where
import GHC.Prelude
import GHC.Cmm.CLabel
import GHC.Types.Id.Info
import GHC.Types.Name
import GHC.Types.Unique
import GHC.Types.Unique.Supply
import GHC.Cmm.Dataflow.Label (Label, mkHooplLabel)
type BlockId = Label
mkBlockId :: Unique -> BlockId
mkBlockId :: Unique -> BlockId
mkBlockId Unique
unique = Int -> BlockId
mkHooplLabel (Int -> BlockId) -> Int -> BlockId
forall a b. (a -> b) -> a -> b
$ Unique -> Int
getKey Unique
unique
newBlockId :: MonadUnique m => m BlockId
newBlockId :: m BlockId
newBlockId = Unique -> BlockId
mkBlockId (Unique -> BlockId) -> m Unique -> m BlockId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
External instance of the constraint type forall (m :: * -> *). MonadUnique m => Monad m
Evidence bound by a type signature of the constraint type MonadUnique m
<$> m Unique
forall (m :: * -> *). MonadUnique m => m Unique
Evidence bound by a type signature of the constraint type MonadUnique m
getUniqueM
blockLbl :: BlockId -> CLabel
blockLbl :: BlockId -> CLabel
blockLbl BlockId
label = Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
External instance of the constraint type Uniquable BlockId
getUnique BlockId
label)
infoTblLbl :: BlockId -> CLabel
infoTblLbl :: BlockId -> CLabel
infoTblLbl BlockId
label
= Name -> CafInfo -> CLabel
mkBlockInfoTableLabel (Unique -> String -> Name
mkFCallName (BlockId -> Unique
forall a. Uniquable a => a -> Unique
External instance of the constraint type Uniquable BlockId
getUnique BlockId
label) String
"block") CafInfo
NoCafRefs