never executed always true always false
    1 
    2 
    3 -- | This is where we define a mapping from Uniques to their associated
    4 -- known-key Names for things associated with tuples and sums. We use this
    5 -- mapping while deserializing known-key Names in interface file symbol tables,
    6 -- which are encoded as their Unique. See Note [Symbol table representation of
    7 -- names] for details.
    8 --
    9 
   10 module GHC.Builtin.Uniques
   11     ( -- * Looking up known-key names
   12       knownUniqueName
   13 
   14       -- * Getting the 'Unique's of 'Name's
   15       -- ** Anonymous sums
   16     , mkSumTyConUnique
   17     , mkSumDataConUnique
   18       -- ** Tuples
   19       -- *** Vanilla
   20     , mkTupleTyConUnique
   21     , mkTupleDataConUnique
   22       -- *** Constraint
   23     , mkCTupleTyConUnique
   24     , mkCTupleDataConUnique
   25     , mkCTupleSelIdUnique
   26 
   27       -- ** Making built-in uniques
   28     , mkAlphaTyVarUnique
   29     , mkPrimOpIdUnique, mkPrimOpWrapperUnique
   30     , mkPreludeMiscIdUnique, mkPreludeDataConUnique
   31     , mkPreludeTyConUnique, mkPreludeClassUnique
   32 
   33     , mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique
   34     , mkRegSingleUnique, mkRegPairUnique, mkRegClassUnique, mkRegSubUnique
   35     , mkCostCentreUnique
   36 
   37     , mkBuiltinUnique
   38     , mkPseudoUniqueE
   39 
   40       -- ** Deriving uniquesc
   41       -- *** From TyCon name uniques
   42     , tyConRepNameUnique
   43       -- *** From DataCon name uniques
   44     , dataConWorkerUnique, dataConTyRepNameUnique
   45 
   46     , initExitJoinUnique
   47 
   48     ) where
   49 
   50 import GHC.Prelude
   51 
   52 import {-# SOURCE #-} GHC.Builtin.Types
   53 import {-# SOURCE #-} GHC.Core.TyCon
   54 import {-# SOURCE #-} GHC.Core.DataCon
   55 import {-# SOURCE #-} GHC.Types.Id
   56 import {-# SOURCE #-} GHC.Types.Name
   57 import GHC.Types.Basic
   58 import GHC.Types.Unique
   59 import GHC.Data.FastString
   60 
   61 import GHC.Utils.Outputable
   62 import GHC.Utils.Panic
   63 import GHC.Utils.Panic.Plain
   64 
   65 import Data.Maybe
   66 
   67 -- | Get the 'Name' associated with a known-key 'Unique'.
   68 knownUniqueName :: Unique -> Maybe Name
   69 knownUniqueName u =
   70     case tag of
   71       'z' -> Just $ getUnboxedSumName n
   72       '4' -> Just $ getTupleTyConName Boxed n
   73       '5' -> Just $ getTupleTyConName Unboxed n
   74       '7' -> Just $ getTupleDataConName Boxed n
   75       '8' -> Just $ getTupleDataConName Unboxed n
   76       'j' -> Just $ getCTupleSelIdName n
   77       'k' -> Just $ getCTupleTyConName n
   78       'm' -> Just $ getCTupleDataConName n
   79       _   -> Nothing
   80   where
   81     (tag, n) = unpkUnique u
   82 
   83 {-
   84 Note [Unique layout for unboxed sums]
   85 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
   86 
   87 Sum arities start from 2. The encoding is a bit funny: we break up the
   88 integral part into bitfields for the arity, an alternative index (which is
   89 taken to be 0xfc in the case of the TyCon), and, in the case of a datacon, a
   90 tag (used to identify the sum's TypeRep binding).
   91 
   92 This layout is chosen to remain compatible with the usual unique allocation
   93 for wired-in data constructors described in GHC.Types.Unique
   94 
   95 TyCon for sum of arity k:
   96   00000000 kkkkkkkk 11111100
   97 
   98 TypeRep of TyCon for sum of arity k:
   99   00000000 kkkkkkkk 11111101
  100 
  101 DataCon for sum of arity k and alternative n (zero-based):
  102   00000000 kkkkkkkk nnnnnn00
  103 
  104 TypeRep for sum DataCon of arity k and alternative n (zero-based):
  105   00000000 kkkkkkkk nnnnnn10
  106 -}
  107 
  108 mkSumTyConUnique :: Arity -> Unique
  109 mkSumTyConUnique arity =
  110     assert (arity < 0x3f) $ -- 0x3f since we only have 6 bits to encode the
  111                             -- alternative
  112     mkUnique 'z' (arity `shiftL` 8 .|. 0xfc)
  113 
  114 mkSumDataConUnique :: ConTagZ -> Arity -> Unique
  115 mkSumDataConUnique alt arity
  116   | alt >= arity
  117   = panic ("mkSumDataConUnique: " ++ show alt ++ " >= " ++ show arity)
  118   | otherwise
  119   = mkUnique 'z' (arity `shiftL` 8 + alt `shiftL` 2) {- skip the tycon -}
  120 
  121 getUnboxedSumName :: Int -> Name
  122 getUnboxedSumName n
  123   | n .&. 0xfc == 0xfc
  124   = case tag of
  125       0x0 -> tyConName $ sumTyCon arity
  126       0x1 -> getRep $ sumTyCon arity
  127       _   -> pprPanic "getUnboxedSumName: invalid tag" (ppr tag)
  128   | tag == 0x0
  129   = dataConName $ sumDataCon (alt + 1) arity
  130   | tag == 0x1
  131   = getName $ dataConWrapId $ sumDataCon (alt + 1) arity
  132   | tag == 0x2
  133   = getRep $ promoteDataCon $ sumDataCon (alt + 1) arity
  134   | otherwise
  135   = pprPanic "getUnboxedSumName" (ppr n)
  136   where
  137     arity = n `shiftR` 8
  138     alt = (n .&. 0xfc) `shiftR` 2
  139     tag = 0x3 .&. n
  140     getRep tycon =
  141         fromMaybe (pprPanic "getUnboxedSumName(getRep)" (ppr tycon))
  142         $ tyConRepName_maybe tycon
  143 
  144 -- Note [Uniques for tuple type and data constructors]
  145 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  146 --
  147 -- Wired-in type constructor keys occupy *two* slots:
  148 --    * u: the TyCon itself
  149 --    * u+1: the TyConRepName of the TyCon
  150 --
  151 -- Wired-in tuple data constructor keys occupy *three* slots:
  152 --    * u: the DataCon itself
  153 --    * u+1: its worker Id
  154 --    * u+2: the TyConRepName of the promoted TyCon
  155 
  156 {-
  157 Note [Unique layout for constraint tuple selectors]
  158 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  159 
  160 Constraint tuples, like boxed and unboxed tuples, have their type and data
  161 constructor Uniques wired in (see
  162 Note [Uniques for tuple type and data constructors]). Constraint tuples are
  163 somewhat more involved, however. For a boxed or unboxed n-tuple, we need:
  164 
  165 * A Unique for the type constructor, and
  166 * A Unique for the data constructor
  167 
  168 With a constraint n-tuple, however, we need:
  169 
  170 * A Unique for the type constructor,
  171 * A Unique for the data constructor, and
  172 * A Unique for each of the n superclass selectors
  173 
  174 To pick a concrete example (n = 2), the binary constraint tuple has a type
  175 constructor and data constructor (%,%) along with superclass selectors
  176 $p1(%,%) and $p2(%,%).
  177 
  178 Just as we wire in the Uniques for constraint tuple type constructors and data
  179 constructors, we wish to wire in the Uniques for the superclass selectors as
  180 well. Not only does this make everything consistent, it also avoids a
  181 compile-time performance penalty whenever GHC.Classes is loaded from an
  182 interface file. This is because GHC.Classes defines constraint tuples as class
  183 definitions, and if these classes weren't wired in, then loading GHC.Classes
  184 would also load every single constraint tuple type constructor, data
  185 constructor, and superclass selector. See #18635.
  186 
  187 We encode the Uniques for constraint tuple superclass selectors as follows. The
  188 integral part of the Unique is broken up into bitfields for the arity and the
  189 position of the superclass. Given a selector for a constraint tuple with
  190 arity n (zero-based) and position k (where 1 <= k <= n), its Unique will look
  191 like:
  192 
  193   00000000 nnnnnnnn kkkkkkkk
  194 
  195 We can use bit-twiddling tricks to access the arity and position with
  196 cTupleSelIdArityBits and cTupleSelIdPosBitmask, respectively.
  197 
  198 This pattern bears a certain resemblance to the way that the Uniques for
  199 unboxed sums are encoded. This is because for a unboxed sum of arity n, there
  200 are n corresponding data constructors, each with an alternative position k.
  201 Similarly, for a constraint tuple of arity n, there are n corresponding
  202 superclass selectors. Reading Note [Unique layout for unboxed sums] will
  203 instill an appreciation for how the encoding for constraint tuple superclass
  204 selector Uniques takes inspiration from the encoding for unboxed sum Uniques.
  205 -}
  206 
  207 mkCTupleTyConUnique :: Arity -> Unique
  208 mkCTupleTyConUnique a = mkUnique 'k' (2*a)
  209 
  210 mkCTupleDataConUnique :: Arity -> Unique
  211 mkCTupleDataConUnique a = mkUnique 'm' (3*a)
  212 
  213 mkCTupleSelIdUnique :: ConTagZ -> Arity -> Unique
  214 mkCTupleSelIdUnique sc_pos arity
  215   | sc_pos >= arity
  216   = panic ("mkCTupleSelIdUnique: " ++ show sc_pos ++ " >= " ++ show arity)
  217   | otherwise
  218   = mkUnique 'j' (arity `shiftL` cTupleSelIdArityBits + sc_pos)
  219 
  220 getCTupleTyConName :: Int -> Name
  221 getCTupleTyConName n =
  222     case n `divMod` 2 of
  223       (arity, 0) -> cTupleTyConName arity
  224       (arity, 1) -> mkPrelTyConRepName $ cTupleTyConName arity
  225       _          -> panic "getCTupleTyConName: impossible"
  226 
  227 getCTupleDataConName :: Int -> Name
  228 getCTupleDataConName n =
  229     case n `divMod` 3 of
  230       (arity,  0) -> cTupleDataConName arity
  231       (arity,  1) -> getName $ dataConWrapId $ cTupleDataCon arity
  232       (arity,  2) -> mkPrelTyConRepName $ cTupleDataConName arity
  233       _           -> panic "getCTupleDataConName: impossible"
  234 
  235 getCTupleSelIdName :: Int -> Name
  236 getCTupleSelIdName n = cTupleSelIdName (sc_pos + 1) arity
  237   where
  238     arity  = n `shiftR` cTupleSelIdArityBits
  239     sc_pos = n .&. cTupleSelIdPosBitmask
  240 
  241 -- Given the arity of a constraint tuple, this is the number of bits by which
  242 -- one must shift it to the left in order to encode the arity in the Unique
  243 -- of a superclass selector for that constraint tuple. Alternatively, given the
  244 -- Unique for a constraint tuple superclass selector, this is the number of
  245 -- bits by which one must shift it to the right to retrieve the arity of the
  246 -- constraint tuple. See Note [Unique layout for constraint tuple selectors].
  247 cTupleSelIdArityBits :: Int
  248 cTupleSelIdArityBits = 8
  249 
  250 -- Given the Unique for a constraint tuple superclass selector, one can
  251 -- retrieve the position of the selector by ANDing this mask, which will
  252 -- clear all but the eight least significant bits.
  253 -- See Note [Unique layout for constraint tuple selectors].
  254 cTupleSelIdPosBitmask :: Int
  255 cTupleSelIdPosBitmask = 0xff
  256 
  257 --------------------------------------------------
  258 -- Normal tuples
  259 
  260 mkTupleDataConUnique :: Boxity -> Arity -> Unique
  261 mkTupleDataConUnique Boxed          a = mkUnique '7' (3*a)    -- may be used in C labels
  262 mkTupleDataConUnique Unboxed        a = mkUnique '8' (3*a)
  263 
  264 mkTupleTyConUnique :: Boxity -> Arity -> Unique
  265 mkTupleTyConUnique Boxed           a  = mkUnique '4' (2*a)
  266 mkTupleTyConUnique Unboxed         a  = mkUnique '5' (2*a)
  267 
  268 getTupleTyConName :: Boxity -> Int -> Name
  269 getTupleTyConName boxity n =
  270     case n `divMod` 2 of
  271       (arity, 0) -> tyConName $ tupleTyCon boxity arity
  272       (arity, 1) -> fromMaybe (panic "getTupleTyConName")
  273                     $ tyConRepName_maybe $ tupleTyCon boxity arity
  274       _          -> panic "getTupleTyConName: impossible"
  275 
  276 getTupleDataConName :: Boxity -> Int -> Name
  277 getTupleDataConName boxity n =
  278     case n `divMod` 3 of
  279       (arity, 0) -> dataConName $ tupleDataCon boxity arity
  280       (arity, 1) -> idName $ dataConWorkId $ tupleDataCon boxity arity
  281       (arity, 2) -> fromMaybe (panic "getTupleDataCon")
  282                     $ tyConRepName_maybe $ promotedTupleDataCon boxity arity
  283       _          -> panic "getTupleDataConName: impossible"
  284 
  285 {-
  286 Note [Uniques for wired-in prelude things and known masks]
  287 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  288 Allocation of unique supply characters:
  289         v,u: for renumbering value-, and usage- vars.
  290         B:   builtin
  291         C-E: pseudo uniques     (used in native-code generator)
  292         I:   GHCi evaluation
  293         X:   uniques from mkLocalUnique
  294         _:   unifiable tyvars   (above)
  295         0-9: prelude things below
  296              (no numbers left any more..)
  297         ::   (prelude) parallel array data constructors
  298 
  299         other a-z: lower case chars for unique supplies.  Used so far:
  300 
  301         a       TypeChecking?
  302         c       StgToCmm/Renamer
  303         d       desugarer
  304         f       AbsC flattener
  305         i       TypeChecking interface files
  306         j       constraint tuple superclass selectors
  307         k       constraint tuple tycons
  308         m       constraint tuple datacons
  309         n       Native/LLVM codegen
  310         r       Hsc name cache
  311         s       simplifier
  312         u       Cmm pipeline
  313         y       GHCi bytecode generator
  314         z       anonymous sums
  315 -}
  316 
  317 mkAlphaTyVarUnique     :: Int -> Unique
  318 mkPreludeClassUnique   :: Int -> Unique
  319 mkPrimOpIdUnique       :: Int -> Unique
  320 -- See Note [Primop wrappers] in GHC.Builtin.PrimOps.
  321 mkPrimOpWrapperUnique  :: Int -> Unique
  322 mkPreludeMiscIdUnique  :: Int -> Unique
  323 
  324 mkAlphaTyVarUnique   i = mkUnique '1' i
  325 mkPreludeClassUnique i = mkUnique '2' i
  326 
  327 --------------------------------------------------
  328 mkPrimOpIdUnique op         = mkUnique '9' (2*op)
  329 mkPrimOpWrapperUnique op    = mkUnique '9' (2*op+1)
  330 mkPreludeMiscIdUnique  i    = mkUnique '0' i
  331 
  332 mkPseudoUniqueE, mkBuiltinUnique :: Int -> Unique
  333 
  334 mkBuiltinUnique i = mkUnique 'B' i
  335 mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs
  336 
  337 mkRegSingleUnique, mkRegPairUnique, mkRegSubUnique, mkRegClassUnique :: Int -> Unique
  338 mkRegSingleUnique = mkUnique 'R'
  339 mkRegSubUnique    = mkUnique 'S'
  340 mkRegPairUnique   = mkUnique 'P'
  341 mkRegClassUnique  = mkUnique 'L'
  342 
  343 mkCostCentreUnique :: Int -> Unique
  344 mkCostCentreUnique = mkUnique 'C'
  345 
  346 mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique :: FastString -> Unique
  347 -- See Note [The Unique of an OccName] in GHC.Types.Name.Occurrence
  348 mkVarOccUnique  fs = mkUnique 'i' (uniqueOfFS fs)
  349 mkDataOccUnique fs = mkUnique 'd' (uniqueOfFS fs)
  350 mkTvOccUnique   fs = mkUnique 'v' (uniqueOfFS fs)
  351 mkTcOccUnique   fs = mkUnique 'c' (uniqueOfFS fs)
  352 
  353 initExitJoinUnique :: Unique
  354 initExitJoinUnique = mkUnique 's' 0
  355 
  356 
  357 --------------------------------------------------
  358 -- Wired-in type constructor keys occupy *two* slots:
  359 --    * u: the TyCon itself
  360 --    * u+1: the TyConRepName of the TyCon
  361 
  362 mkPreludeTyConUnique   :: Int -> Unique
  363 mkPreludeTyConUnique i                = mkUnique '3' (2*i)
  364 
  365 tyConRepNameUnique :: Unique -> Unique
  366 tyConRepNameUnique  u = incrUnique u
  367 
  368 --------------------------------------------------
  369 -- Wired-in data constructor keys occupy *three* slots:
  370 --    * u: the DataCon itself
  371 --    * u+1: its worker Id
  372 --    * u+2: the TyConRepName of the promoted TyCon
  373 -- Prelude data constructors are too simple to need wrappers.
  374 
  375 mkPreludeDataConUnique :: Int -> Unique
  376 mkPreludeDataConUnique i              = mkUnique '6' (3*i)    -- Must be alphabetic
  377 
  378 --------------------------------------------------
  379 dataConTyRepNameUnique, dataConWorkerUnique :: Unique -> Unique
  380 dataConWorkerUnique  u = incrUnique u
  381 dataConTyRepNameUnique u = stepUnique u 2