{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module BlockId
( BlockId, mkBlockId
, newBlockId
, blockLbl, infoTblLbl
) where
import GhcPrelude
import CLabel
import IdInfo
import Name
import Unique
import UniqSupply
import Hoopl.Label (Label, uniqueToLbl)
import Hoopl.Unique (intToUnique)
type BlockId = Label
mkBlockId :: Unique -> BlockId
mkBlockId unique = uniqueToLbl $ intToUnique $ getKey unique
newBlockId :: MonadUnique m => m BlockId
newBlockId = mkBlockId <$> getUniqueM
blockLbl :: BlockId -> CLabel
blockLbl label = mkLocalBlockLabel (getUnique label)
infoTblLbl :: BlockId -> CLabel
infoTblLbl label
= mkBlockInfoTableLabel (mkFCallName (getUnique label) "block") NoCafRefs