{-# LANGUAGE CPP #-}

-- | This is where we define a mapping from Uniques to their associated
-- known-key Names for things associated with tuples and sums. We use this
-- mapping while deserializing known-key Names in interface file symbol tables,
-- which are encoded as their Unique. See Note [Symbol table representation of
-- names] for details.
--

module GHC.Builtin.Uniques
    ( -- * Looking up known-key names
      knownUniqueName

      -- * Getting the 'Unique's of 'Name's
      -- ** Anonymous sums
    , mkSumTyConUnique
    , mkSumDataConUnique
      -- ** Tuples
      -- *** Vanilla
    , mkTupleTyConUnique
    , mkTupleDataConUnique
      -- *** Constraint
    , mkCTupleTyConUnique
    , mkCTupleDataConUnique
    , mkCTupleSelIdUnique

      -- ** Making built-in uniques
    , mkAlphaTyVarUnique
    , mkPrimOpIdUnique, mkPrimOpWrapperUnique
    , mkPreludeMiscIdUnique, mkPreludeDataConUnique
    , mkPreludeTyConUnique, mkPreludeClassUnique
    , mkCoVarUnique

    , mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique
    , mkRegSingleUnique, mkRegPairUnique, mkRegClassUnique, mkRegSubUnique
    , mkCostCentreUnique

    , mkBuiltinUnique
    , mkPseudoUniqueD
    , mkPseudoUniqueE
    , mkPseudoUniqueH

      -- ** Deriving uniquesc
      -- *** From TyCon name uniques
    , tyConRepNameUnique
      -- *** From DataCon name uniques
    , dataConWorkerUnique, dataConTyRepNameUnique

    , initTyVarUnique
    , initExitJoinUnique

    ) where

#include "GhclibHsVersions.h"

import GHC.Prelude

import {-# SOURCE #-} GHC.Builtin.Types
import {-# SOURCE #-} GHC.Core.TyCon
import {-# SOURCE #-} GHC.Core.DataCon
import {-# SOURCE #-} GHC.Types.Id
import {-# SOURCE #-} GHC.Types.Name
import GHC.Types.Basic
import GHC.Types.Unique
import GHC.Data.FastString

import GHC.Utils.Outputable
import GHC.Utils.Misc
import GHC.Utils.Panic

import Data.Maybe

-- | Get the 'Name' associated with a known-key 'Unique'.
knownUniqueName :: Unique -> Maybe Name
knownUniqueName :: Unique -> Maybe Name
knownUniqueName Unique
u =
    case Char
tag of
      Char
'z' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Int -> Name
getUnboxedSumName Int
n
      Char
'4' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> Name
getTupleTyConName Boxity
Boxed Int
n
      Char
'5' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> Name
getTupleTyConName Boxity
Unboxed Int
n
      Char
'7' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> Name
getTupleDataConName Boxity
Boxed Int
n
      Char
'8' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> Name
getTupleDataConName Boxity
Unboxed Int
n
      Char
'j' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Int -> Name
getCTupleSelIdName Int
n
      Char
'k' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Int -> Name
getCTupleTyConName Int
n
      Char
'm' -> Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Int -> Name
getCTupleDataConName Int
n
      Char
_   -> Maybe Name
forall a. Maybe a
Nothing
  where
    (Char
tag, Int
n) = Unique -> (Char, Int)
unpkUnique Unique
u

{-
Note [Unique layout for unboxed sums]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Sum arities start from 2. The encoding is a bit funny: we break up the
integral part into bitfields for the arity, an alternative index (which is
taken to be 0xfc in the case of the TyCon), and, in the case of a datacon, a
tag (used to identify the sum's TypeRep binding).

This layout is chosen to remain compatible with the usual unique allocation
for wired-in data constructors described in GHC.Types.Unique

TyCon for sum of arity k:
  00000000 kkkkkkkk 11111100

TypeRep of TyCon for sum of arity k:
  00000000 kkkkkkkk 11111101

DataCon for sum of arity k and alternative n (zero-based):
  00000000 kkkkkkkk nnnnnn00

TypeRep for sum DataCon of arity k and alternative n (zero-based):
  00000000 kkkkkkkk nnnnnn10
-}

mkSumTyConUnique :: Arity -> Unique
mkSumTyConUnique :: Int -> Unique
mkSumTyConUnique Int
arity =
    ASSERT(arity < 0x3f) -- 0x3f since we only have 6 bits to encode the
                         -- alternative
    Char -> Int -> Unique
mkUnique Char
'z' (Int
arity Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Int
0xfc)

mkSumDataConUnique :: ConTagZ -> Arity -> Unique
mkSumDataConUnique :: Int -> Int -> Unique
mkSumDataConUnique Int
alt Int
arity
  | Int
alt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
arity
  = String -> Unique
forall a. String -> a
panic (String
"mkSumDataConUnique: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
alt String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" >= " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
arity)
  | Bool
otherwise
  = Char -> Int -> Unique
mkUnique Char
'z' (Int
arity Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
alt Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2) {- skip the tycon -}

getUnboxedSumName :: Int -> Name
getUnboxedSumName :: Int -> Name
getUnboxedSumName Int
n
  | Int
n Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xfc Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0xfc
  = case Int
tag of
      Int
0x0 -> TyCon -> Name
tyConName (TyCon -> Name) -> TyCon -> Name
forall a b. (a -> b) -> a -> b
$ Int -> TyCon
sumTyCon Int
arity
      Int
0x1 -> TyCon -> Name
getRep (TyCon -> Name) -> TyCon -> Name
forall a b. (a -> b) -> a -> b
$ Int -> TyCon
sumTyCon Int
arity
      Int
_   -> String -> SDoc -> Name
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getUnboxedSumName: invalid tag" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
tag)
  | Int
tag Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0x0
  = DataCon -> Name
dataConName (DataCon -> Name) -> DataCon -> Name
forall a b. (a -> b) -> a -> b
$ Int -> Int -> DataCon
sumDataCon (Int
alt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
arity
  | Int
tag Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0x1
  = Id -> Name
forall a. NamedThing a => a -> Name
getName (Id -> Name) -> Id -> Name
forall a b. (a -> b) -> a -> b
$ DataCon -> Id
dataConWrapId (DataCon -> Id) -> DataCon -> Id
forall a b. (a -> b) -> a -> b
$ Int -> Int -> DataCon
sumDataCon (Int
alt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
arity
  | Int
tag Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0x2
  = TyCon -> Name
getRep (TyCon -> Name) -> TyCon -> Name
forall a b. (a -> b) -> a -> b
$ DataCon -> TyCon
promoteDataCon (DataCon -> TyCon) -> DataCon -> TyCon
forall a b. (a -> b) -> a -> b
$ Int -> Int -> DataCon
sumDataCon (Int
alt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
arity
  | Bool
otherwise
  = String -> SDoc -> Name
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getUnboxedSumName" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
n)
  where
    arity :: Int
arity = Int
n Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
8
    alt :: Int
alt = (Int
n Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xfc) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
2
    tag :: Int
tag = Int
0x3 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
n
    getRep :: TyCon -> Name
getRep TyCon
tycon =
        Name -> Maybe Name -> Name
forall a. a -> Maybe a -> a
fromMaybe (String -> SDoc -> Name
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getUnboxedSumName(getRep)" (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
tycon))
        (Maybe Name -> Name) -> Maybe Name -> Name
forall a b. (a -> b) -> a -> b
$ TyCon -> Maybe Name
tyConRepName_maybe TyCon
tycon

-- Note [Uniques for tuple type and data constructors]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- Wired-in type constructor keys occupy *two* slots:
--    * u: the TyCon itself
--    * u+1: the TyConRepName of the TyCon
--
-- Wired-in tuple data constructor keys occupy *three* slots:
--    * u: the DataCon itself
--    * u+1: its worker Id
--    * u+2: the TyConRepName of the promoted TyCon

{-
Note [Unique layout for constraint tuple selectors]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Constraint tuples, like boxed and unboxed tuples, have their type and data
constructor Uniques wired in (see
Note [Uniques for tuple type and data constructors]). Constraint tuples are
somewhat more involved, however. For a boxed or unboxed n-tuple, we need:

* A Unique for the type constructor, and
* A Unique for the data constructor

With a constraint n-tuple, however, we need:

* A Unique for the type constructor,
* A Unique for the data constructor, and
* A Unique for each of the n superclass selectors

To pick a concrete example (n = 2), the binary constraint tuple has a type
constructor and data constructor (%,%) along with superclass selectors
$p1(%,%) and $p2(%,%).

Just as we wire in the Uniques for constraint tuple type constructors and data
constructors, we wish to wire in the Uniques for the superclass selectors as
well. Not only does this make everything consistent, it also avoids a
compile-time performance penalty whenever GHC.Classes is loaded from an
interface file. This is because GHC.Classes defines constraint tuples as class
definitions, and if these classes weren't wired in, then loading GHC.Classes
would also load every single constraint tuple type constructor, data
constructor, and superclass selector. See #18635.

We encode the Uniques for constraint tuple superclass selectors as follows. The
integral part of the Unique is broken up into bitfields for the arity and the
position of the superclass. Given a selector for a constraint tuple with
arity n (zero-based) and position k (where 1 <= k <= n), its Unique will look
like:

  00000000 nnnnnnnn kkkkkkkk

We can use bit-twiddling tricks to access the arity and position with
cTupleSelIdArityBits and cTupleSelIdPosBitmask, respectively.

This pattern bears a certain resemblance to the way that the Uniques for
unboxed sums are encoded. This is because for a unboxed sum of arity n, there
are n corresponding data constructors, each with an alternative position k.
Similarly, for a constraint tuple of arity n, there are n corresponding
superclass selectors. Reading Note [Unique layout for unboxed sums] will
instill an appreciation for how the encoding for constraint tuple superclass
selector Uniques takes inspiration from the encoding for unboxed sum Uniques.
-}

mkCTupleTyConUnique :: Arity -> Unique
mkCTupleTyConUnique :: Int -> Unique
mkCTupleTyConUnique Int
a = Char -> Int -> Unique
mkUnique Char
'k' (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
a)

mkCTupleDataConUnique :: Arity -> Unique
mkCTupleDataConUnique :: Int -> Unique
mkCTupleDataConUnique Int
a = Char -> Int -> Unique
mkUnique Char
'm' (Int
3Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
a)

mkCTupleSelIdUnique :: ConTagZ -> Arity -> Unique
mkCTupleSelIdUnique :: Int -> Int -> Unique
mkCTupleSelIdUnique Int
sc_pos Int
arity
  | Int
sc_pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
arity
  = String -> Unique
forall a. String -> a
panic (String
"mkCTupleSelIdUnique: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
sc_pos String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" >= " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
arity)
  | Bool
otherwise
  = Char -> Int -> Unique
mkUnique Char
'j' (Int
arity Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
cTupleSelIdArityBits Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
sc_pos)

getCTupleTyConName :: Int -> Name
getCTupleTyConName :: Int -> Name
getCTupleTyConName Int
n =
    case Int
n Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
2 of
      (Int
arity, Int
0) -> Int -> Name
cTupleTyConName Int
arity
      (Int
arity, Int
1) -> Name -> Name
mkPrelTyConRepName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Int -> Name
cTupleTyConName Int
arity
      (Int, Int)
_          -> String -> Name
forall a. String -> a
panic String
"getCTupleTyConName: impossible"

getCTupleDataConName :: Int -> Name
getCTupleDataConName :: Int -> Name
getCTupleDataConName Int
n =
    case Int
n Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
3 of
      (Int
arity,  Int
0) -> Int -> Name
cTupleDataConName Int
arity
      (Int
arity,  Int
1) -> Id -> Name
forall a. NamedThing a => a -> Name
getName (Id -> Name) -> Id -> Name
forall a b. (a -> b) -> a -> b
$ DataCon -> Id
dataConWrapId (DataCon -> Id) -> DataCon -> Id
forall a b. (a -> b) -> a -> b
$ Int -> DataCon
cTupleDataCon Int
arity
      (Int
arity,  Int
2) -> Name -> Name
mkPrelTyConRepName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Int -> Name
cTupleDataConName Int
arity
      (Int, Int)
_           -> String -> Name
forall a. String -> a
panic String
"getCTupleDataConName: impossible"

getCTupleSelIdName :: Int -> Name
getCTupleSelIdName :: Int -> Name
getCTupleSelIdName Int
n = Int -> Int -> Name
cTupleSelIdName (Int
sc_pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
arity
  where
    arity :: Int
arity  = Int
n Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
cTupleSelIdArityBits
    sc_pos :: Int
sc_pos = Int
n Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
cTupleSelIdPosBitmask

-- Given the arity of a constraint tuple, this is the number of bits by which
-- one must shift it to the left in order to encode the arity in the Unique
-- of a superclass selector for that constraint tuple. Alternatively, given the
-- Unique for a constraint tuple superclass selector, this is the number of
-- bits by which one must shift it to the right to retrieve the arity of the
-- constraint tuple. See Note [Unique layout for constraint tuple selectors].
cTupleSelIdArityBits :: Int
cTupleSelIdArityBits :: Int
cTupleSelIdArityBits = Int
8

-- Given the Unique for a constraint tuple superclass selector, one can
-- retrieve the position of the selector by ANDing this mask, which will
-- clear all but the eight least significant bits.
-- See Note [Unique layout for constraint tuple selectors].
cTupleSelIdPosBitmask :: Int
cTupleSelIdPosBitmask :: Int
cTupleSelIdPosBitmask = Int
0xff

--------------------------------------------------
-- Normal tuples

mkTupleDataConUnique :: Boxity -> Arity -> Unique
mkTupleDataConUnique :: Boxity -> Int -> Unique
mkTupleDataConUnique Boxity
Boxed          Int
a = Char -> Int -> Unique
mkUnique Char
'7' (Int
3Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
a)    -- may be used in C labels
mkTupleDataConUnique Boxity
Unboxed        Int
a = Char -> Int -> Unique
mkUnique Char
'8' (Int
3Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
a)

mkTupleTyConUnique :: Boxity -> Arity -> Unique
mkTupleTyConUnique :: Boxity -> Int -> Unique
mkTupleTyConUnique Boxity
Boxed           Int
a  = Char -> Int -> Unique
mkUnique Char
'4' (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
a)
mkTupleTyConUnique Boxity
Unboxed         Int
a  = Char -> Int -> Unique
mkUnique Char
'5' (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
a)

getTupleTyConName :: Boxity -> Int -> Name
getTupleTyConName :: Boxity -> Int -> Name
getTupleTyConName Boxity
boxity Int
n =
    case Int
n Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
2 of
      (Int
arity, Int
0) -> TyCon -> Name
tyConName (TyCon -> Name) -> TyCon -> Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> TyCon
tupleTyCon Boxity
boxity Int
arity
      (Int
arity, Int
1) -> Name -> Maybe Name -> Name
forall a. a -> Maybe a -> a
fromMaybe (String -> Name
forall a. String -> a
panic String
"getTupleTyConName")
                    (Maybe Name -> Name) -> Maybe Name -> Name
forall a b. (a -> b) -> a -> b
$ TyCon -> Maybe Name
tyConRepName_maybe (TyCon -> Maybe Name) -> TyCon -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> TyCon
tupleTyCon Boxity
boxity Int
arity
      (Int, Int)
_          -> String -> Name
forall a. String -> a
panic String
"getTupleTyConName: impossible"

getTupleDataConName :: Boxity -> Int -> Name
getTupleDataConName :: Boxity -> Int -> Name
getTupleDataConName Boxity
boxity Int
n =
    case Int
n Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
3 of
      (Int
arity, Int
0) -> DataCon -> Name
dataConName (DataCon -> Name) -> DataCon -> Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> DataCon
tupleDataCon Boxity
boxity Int
arity
      (Int
arity, Int
1) -> Id -> Name
idName (Id -> Name) -> Id -> Name
forall a b. (a -> b) -> a -> b
$ DataCon -> Id
dataConWorkId (DataCon -> Id) -> DataCon -> Id
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> DataCon
tupleDataCon Boxity
boxity Int
arity
      (Int
arity, Int
2) -> Name -> Maybe Name -> Name
forall a. a -> Maybe a -> a
fromMaybe (String -> Name
forall a. String -> a
panic String
"getTupleDataCon")
                    (Maybe Name -> Name) -> Maybe Name -> Name
forall a b. (a -> b) -> a -> b
$ TyCon -> Maybe Name
tyConRepName_maybe (TyCon -> Maybe Name) -> TyCon -> Maybe Name
forall a b. (a -> b) -> a -> b
$ Boxity -> Int -> TyCon
promotedTupleDataCon Boxity
boxity Int
arity
      (Int, Int)
_          -> String -> Name
forall a. String -> a
panic String
"getTupleDataConName: impossible"

{-
Note [Uniques for wired-in prelude things and known masks]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Allocation of unique supply characters:
        v,t,u : for renumbering value-, type- and usage- vars.
        B:   builtin
        C-E: pseudo uniques     (used in native-code generator)
        I:   GHCi evaluation
        X:   uniques from mkLocalUnique
        _:   unifiable tyvars   (above)
        0-9: prelude things below
             (no numbers left any more..)
        ::   (prelude) parallel array data constructors

        other a-z: lower case chars for unique supplies.  Used so far:

        a       TypeChecking?
        c       StgToCmm/Renamer
        d       desugarer
        f       AbsC flattener
        g       SimplStg
        i       TypeChecking interface files
        j       constraint tuple superclass selectors
        k       constraint tuple tycons
        m       constraint tuple datacons
        n       Native/LLVM codegen
        r       Hsc name cache
        s       simplifier
        u       Cmm pipeline
        y       GHCi bytecode generator
        z       anonymous sums
-}

mkAlphaTyVarUnique     :: Int -> Unique
mkPreludeClassUnique   :: Int -> Unique
mkPrimOpIdUnique       :: Int -> Unique
-- See Note [Primop wrappers] in GHC.Builtin.PrimOps.
mkPrimOpWrapperUnique  :: Int -> Unique
mkPreludeMiscIdUnique  :: Int -> Unique
mkCoVarUnique          :: Int -> Unique

mkAlphaTyVarUnique :: Int -> Unique
mkAlphaTyVarUnique   Int
i = Char -> Int -> Unique
mkUnique Char
'1' Int
i
mkCoVarUnique :: Int -> Unique
mkCoVarUnique        Int
i = Char -> Int -> Unique
mkUnique Char
'g' Int
i
mkPreludeClassUnique :: Int -> Unique
mkPreludeClassUnique Int
i = Char -> Int -> Unique
mkUnique Char
'2' Int
i

--------------------------------------------------
mkPrimOpIdUnique :: Int -> Unique
mkPrimOpIdUnique Int
op         = Char -> Int -> Unique
mkUnique Char
'9' (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
op)
mkPrimOpWrapperUnique :: Int -> Unique
mkPrimOpWrapperUnique Int
op    = Char -> Int -> Unique
mkUnique Char
'9' (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
opInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
mkPreludeMiscIdUnique :: Int -> Unique
mkPreludeMiscIdUnique  Int
i    = Char -> Int -> Unique
mkUnique Char
'0' Int
i

-- The "tyvar uniques" print specially nicely: a, b, c, etc.
-- See pprUnique for details

initTyVarUnique :: Unique
initTyVarUnique :: Unique
initTyVarUnique = Char -> Int -> Unique
mkUnique Char
't' Int
0

mkPseudoUniqueD, mkPseudoUniqueE, mkPseudoUniqueH,
  mkBuiltinUnique :: Int -> Unique

mkBuiltinUnique :: Int -> Unique
mkBuiltinUnique Int
i = Char -> Int -> Unique
mkUnique Char
'B' Int
i
mkPseudoUniqueD :: Int -> Unique
mkPseudoUniqueD Int
i = Char -> Int -> Unique
mkUnique Char
'D' Int
i -- used in NCG for getUnique on RealRegs
mkPseudoUniqueE :: Int -> Unique
mkPseudoUniqueE Int
i = Char -> Int -> Unique
mkUnique Char
'E' Int
i -- used in NCG spiller to create spill VirtualRegs
mkPseudoUniqueH :: Int -> Unique
mkPseudoUniqueH Int
i = Char -> Int -> Unique
mkUnique Char
'H' Int
i -- used in NCG spiller to create spill VirtualRegs

mkRegSingleUnique, mkRegPairUnique, mkRegSubUnique, mkRegClassUnique :: Int -> Unique
mkRegSingleUnique :: Int -> Unique
mkRegSingleUnique = Char -> Int -> Unique
mkUnique Char
'R'
mkRegSubUnique :: Int -> Unique
mkRegSubUnique    = Char -> Int -> Unique
mkUnique Char
'S'
mkRegPairUnique :: Int -> Unique
mkRegPairUnique   = Char -> Int -> Unique
mkUnique Char
'P'
mkRegClassUnique :: Int -> Unique
mkRegClassUnique  = Char -> Int -> Unique
mkUnique Char
'L'

mkCostCentreUnique :: Int -> Unique
mkCostCentreUnique :: Int -> Unique
mkCostCentreUnique = Char -> Int -> Unique
mkUnique Char
'C'

mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique :: FastString -> Unique
-- See Note [The Unique of an OccName] in GHC.Types.Name.Occurrence
mkVarOccUnique :: FastString -> Unique
mkVarOccUnique  FastString
fs = Char -> Int -> Unique
mkUnique Char
'i' (FastString -> Int
uniqueOfFS FastString
fs)
mkDataOccUnique :: FastString -> Unique
mkDataOccUnique FastString
fs = Char -> Int -> Unique
mkUnique Char
'd' (FastString -> Int
uniqueOfFS FastString
fs)
mkTvOccUnique :: FastString -> Unique
mkTvOccUnique   FastString
fs = Char -> Int -> Unique
mkUnique Char
'v' (FastString -> Int
uniqueOfFS FastString
fs)
mkTcOccUnique :: FastString -> Unique
mkTcOccUnique   FastString
fs = Char -> Int -> Unique
mkUnique Char
'c' (FastString -> Int
uniqueOfFS FastString
fs)

initExitJoinUnique :: Unique
initExitJoinUnique :: Unique
initExitJoinUnique = Char -> Int -> Unique
mkUnique Char
's' Int
0


--------------------------------------------------
-- Wired-in type constructor keys occupy *two* slots:
--    * u: the TyCon itself
--    * u+1: the TyConRepName of the TyCon

mkPreludeTyConUnique   :: Int -> Unique
mkPreludeTyConUnique :: Int -> Unique
mkPreludeTyConUnique Int
i                = Char -> Int -> Unique
mkUnique Char
'3' (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
i)

tyConRepNameUnique :: Unique -> Unique
tyConRepNameUnique :: Unique -> Unique
tyConRepNameUnique  Unique
u = Unique -> Unique
incrUnique Unique
u

--------------------------------------------------
-- Wired-in data constructor keys occupy *three* slots:
--    * u: the DataCon itself
--    * u+1: its worker Id
--    * u+2: the TyConRepName of the promoted TyCon
-- Prelude data constructors are too simple to need wrappers.

mkPreludeDataConUnique :: Arity -> Unique
mkPreludeDataConUnique :: Int -> Unique
mkPreludeDataConUnique Int
i              = Char -> Int -> Unique
mkUnique Char
'6' (Int
3Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
i)    -- Must be alphabetic

--------------------------------------------------
dataConTyRepNameUnique, dataConWorkerUnique :: Unique -> Unique
dataConWorkerUnique :: Unique -> Unique
dataConWorkerUnique  Unique
u = Unique -> Unique
incrUnique Unique
u
dataConTyRepNameUnique :: Unique -> Unique
dataConTyRepNameUnique Unique
u = Unique -> Int -> Unique
stepUnique Unique
u Int
2