{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

{- BlockId module should probably go away completely, being superseded by Label -}
module BlockId
  ( BlockId, mkBlockId -- ToDo: BlockId should be abstract, but it isn't yet
  , newBlockId
  , blockLbl, infoTblLbl
  ) where

import GhcPrelude

import CLabel
import IdInfo
import Name
import Unique
import UniqSupply

import Hoopl.Label (Label, mkHooplLabel)

----------------------------------------------------------------
--- Block Ids, their environments, and their sets

{- Note [Unique BlockId]
~~~~~~~~~~~~~~~~~~~~~~~~
Although a 'BlockId' is a local label, for reasons of implementation,
'BlockId's must be unique within an entire compilation unit.  The reason
is that each local label is mapped to an assembly-language label, and in
most assembly languages allow, a label is visible throughout the entire
compilation unit in which it appears.
-}

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
<$> m Unique
forall (m :: * -> *). MonadUnique m => m Unique
getUniqueM

blockLbl :: BlockId -> CLabel
blockLbl :: BlockId -> CLabel
blockLbl BlockId
label = Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
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
getUnique BlockId
label) String
"block") CafInfo
NoCafRefs