never executed always true always false
    1 {-
    2 (c) The University of Glasgow 2006
    3 (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
    4 
    5 
    6 @Uniques@ are used to distinguish entities in the compiler (@Ids@,
    7 @Classes@, etc.) from each other.  Thus, @Uniques@ are the basic
    8 comparison key in the compiler.
    9 
   10 If there is any single operation that needs to be fast, it is @Unique@
   11 
   12 comparison.  Unsurprisingly, there is quite a bit of huff-and-puff
   13 directed to that end.
   14 
   15 Some of the other hair in this code is to be able to use a
   16 ``splittable @UniqueSupply@'' if requested/possible (not standard
   17 Haskell).
   18 -}
   19 
   20 {-# LANGUAGE CPP #-}
   21 {-# LANGUAGE BangPatterns, MagicHash #-}
   22 
   23 module GHC.Types.Unique (
   24         -- * Main data types
   25         Unique, Uniquable(..),
   26         uNIQUE_BITS,
   27 
   28         -- ** Constructors, destructors and operations on 'Unique's
   29         hasKey,
   30 
   31         pprUniqueAlways,
   32 
   33         mkUniqueGrimily,
   34         getKey,
   35         mkUnique, unpkUnique,
   36         eqUnique, ltUnique,
   37         incrUnique, stepUnique,
   38 
   39         newTagUnique,
   40         nonDetCmpUnique,
   41         isValidKnownKeyUnique,
   42 
   43         -- ** Local uniques
   44         -- | These are exposed exclusively for use by 'GHC.Types.Var.Env.uniqAway', which
   45         -- has rather peculiar needs. See Note [Local uniques].
   46         mkLocalUnique, minLocalUnique, maxLocalUnique,
   47     ) where
   48 
   49 #include "Unique.h"
   50 
   51 import GHC.Prelude
   52 
   53 import GHC.Data.FastString
   54 import GHC.Utils.Outputable
   55 import GHC.Utils.Panic.Plain
   56 
   57 -- just for implementing a fast [0,61) -> Char function
   58 import GHC.Exts (indexCharOffAddr#, Char(..), Int(..))
   59 
   60 import Data.Char        ( chr, ord )
   61 
   62 {-
   63 ************************************************************************
   64 *                                                                      *
   65 \subsection[Unique-type]{@Unique@ type and operations}
   66 *                                                                      *
   67 ************************************************************************
   68 
   69 Note [Uniques and masks]
   70 ~~~~~~~~~~~~~~~~~~~~~~~~
   71 A `Unique` in GHC is a Word-sized value composed of two pieces:
   72 * A "mask", of width `UNIQUE_TAG_BITS`, in the high order bits
   73 * A number, of width `uNIQUE_BITS`, which fills up the remainder of the Word
   74 
   75 The mask is typically an ASCII character.  It is typically used to make it easier
   76 to distinguish uniques constructed by different parts of the compiler.
   77 There is a (potentially incomplete) list of unique masks used given in
   78 GHC.Builtin.Uniques. See Note [Uniques-prelude - Uniques for wired-in Prelude things]
   79 
   80 `mkUnique` constructs a `Unique` from its pieces
   81   mkUnique :: Char -> Int -> Unique
   82 
   83 -}
   84 
   85 -- | Unique identifier.
   86 --
   87 -- The type of unique identifiers that are used in many places in GHC
   88 -- for fast ordering and equality tests. You should generate these with
   89 -- the functions from the 'UniqSupply' module
   90 --
   91 -- These are sometimes also referred to as \"keys\" in comments in GHC.
   92 newtype Unique = MkUnique Int
   93 
   94 {-# INLINE uNIQUE_BITS #-}
   95 uNIQUE_BITS :: Int
   96 uNIQUE_BITS = finiteBitSize (0 :: Int) - UNIQUE_TAG_BITS
   97 
   98 {-
   99 Now come the functions which construct uniques from their pieces, and vice versa.
  100 The stuff about unique *supplies* is handled further down this module.
  101 -}
  102 
  103 unpkUnique      :: Unique -> (Char, Int)        -- The reverse
  104 
  105 mkUniqueGrimily :: Int -> Unique                -- A trap-door for UniqSupply
  106 getKey          :: Unique -> Int                -- for Var
  107 
  108 incrUnique   :: Unique -> Unique
  109 stepUnique   :: Unique -> Int -> Unique
  110 newTagUnique :: Unique -> Char -> Unique
  111 
  112 mkUniqueGrimily = MkUnique
  113 
  114 {-# INLINE getKey #-}
  115 getKey (MkUnique x) = x
  116 
  117 incrUnique (MkUnique i) = MkUnique (i + 1)
  118 stepUnique (MkUnique i) n = MkUnique (i + n)
  119 
  120 mkLocalUnique :: Int -> Unique
  121 mkLocalUnique i = mkUnique 'X' i
  122 
  123 minLocalUnique :: Unique
  124 minLocalUnique = mkLocalUnique 0
  125 
  126 maxLocalUnique :: Unique
  127 maxLocalUnique = mkLocalUnique uniqueMask
  128 
  129 -- newTagUnique changes the "domain" of a unique to a different char
  130 newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u
  131 
  132 -- | How many bits are devoted to the unique index (as opposed to the class
  133 -- character).
  134 uniqueMask :: Int
  135 uniqueMask = (1 `shiftL` uNIQUE_BITS) - 1
  136 
  137 -- pop the Char in the top 8 bits of the Unique(Supply)
  138 
  139 -- No 64-bit bugs here, as long as we have at least 32 bits. --JSM
  140 
  141 -- and as long as the Char fits in 8 bits, which we assume anyway!
  142 
  143 mkUnique :: Char -> Int -> Unique       -- Builds a unique from pieces
  144 -- EXPORTED and used only in GHC.Builtin.Uniques
  145 mkUnique c i
  146   = MkUnique (tag .|. bits)
  147   where
  148     tag  = ord c `shiftL` uNIQUE_BITS
  149     bits = i .&. uniqueMask
  150 
  151 unpkUnique (MkUnique u)
  152   = let
  153         -- as long as the Char may have its eighth bit set, we
  154         -- really do need the logical right-shift here!
  155         tag = chr (u `shiftR` uNIQUE_BITS)
  156         i   = u .&. uniqueMask
  157     in
  158     (tag, i)
  159 
  160 -- | The interface file symbol-table encoding assumes that known-key uniques fit
  161 -- in 30-bits; verify this.
  162 --
  163 -- See Note [Symbol table representation of names] in "GHC.Iface.Binary" for details.
  164 isValidKnownKeyUnique :: Unique -> Bool
  165 isValidKnownKeyUnique u =
  166     case unpkUnique u of
  167       (c, x) -> ord c < 0xff && x <= (1 `shiftL` 22)
  168 
  169 {-
  170 ************************************************************************
  171 *                                                                      *
  172 \subsection[Uniquable-class]{The @Uniquable@ class}
  173 *                                                                      *
  174 ************************************************************************
  175 -}
  176 
  177 -- | Class of things that we can obtain a 'Unique' from
  178 class Uniquable a where
  179     getUnique :: a -> Unique
  180 
  181 hasKey          :: Uniquable a => a -> Unique -> Bool
  182 x `hasKey` k    = getUnique x == k
  183 
  184 instance Uniquable FastString where
  185  getUnique fs = mkUniqueGrimily (uniqueOfFS fs)
  186 
  187 instance Uniquable Int where
  188  getUnique i = mkUniqueGrimily i
  189 
  190 {-
  191 ************************************************************************
  192 *                                                                      *
  193 \subsection[Unique-instances]{Instance declarations for @Unique@}
  194 *                                                                      *
  195 ************************************************************************
  196 
  197 And the whole point (besides uniqueness) is fast equality.  We don't
  198 use `deriving' because we want {\em precise} control of ordering
  199 (equality on @Uniques@ is v common).
  200 -}
  201 
  202 -- Note [Unique Determinism]
  203 -- ~~~~~~~~~~~~~~~~~~~~~~~~~
  204 -- The order of allocated @Uniques@ is not stable across rebuilds.
  205 -- The main reason for that is that typechecking interface files pulls
  206 -- @Uniques@ from @UniqSupply@ and the interface file for the module being
  207 -- currently compiled can, but doesn't have to exist.
  208 --
  209 -- It gets more complicated if you take into account that the interface
  210 -- files are loaded lazily and that building multiple files at once has to
  211 -- work for any subset of interface files present. When you add parallelism
  212 -- this makes @Uniques@ hopelessly random.
  213 --
  214 -- As such, to get deterministic builds, the order of the allocated
  215 -- @Uniques@ should not affect the final result.
  216 -- see also wiki/deterministic-builds
  217 --
  218 -- Note [Unique Determinism and code generation]
  219 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  220 -- The goal of the deterministic builds (wiki/deterministic-builds, #4012)
  221 -- is to get ABI compatible binaries given the same inputs and environment.
  222 -- The motivation behind that is that if the ABI doesn't change the
  223 -- binaries can be safely reused.
  224 -- Note that this is weaker than bit-for-bit identical binaries and getting
  225 -- bit-for-bit identical binaries is not a goal for now.
  226 -- This means that we don't care about nondeterminism that happens after
  227 -- the interface files are created, in particular we don't care about
  228 -- register allocation and code generation.
  229 -- To track progress on bit-for-bit determinism see #12262.
  230 
  231 eqUnique :: Unique -> Unique -> Bool
  232 eqUnique (MkUnique u1) (MkUnique u2) = u1 == u2
  233 
  234 ltUnique :: Unique -> Unique -> Bool
  235 ltUnique (MkUnique u1) (MkUnique u2) = u1 < u2
  236 
  237 -- Provided here to make it explicit at the call-site that it can
  238 -- introduce non-determinism.
  239 -- See Note [Unique Determinism]
  240 -- See Note [No Ord for Unique]
  241 nonDetCmpUnique :: Unique -> Unique -> Ordering
  242 nonDetCmpUnique (MkUnique u1) (MkUnique u2)
  243   = if u1 == u2 then EQ else if u1 < u2 then LT else GT
  244 
  245 {-
  246 Note [No Ord for Unique]
  247 ~~~~~~~~~~~~~~~~~~~~~~~~~~
  248 As explained in Note [Unique Determinism] the relative order of Uniques
  249 is nondeterministic. To prevent from accidental use the Ord Unique
  250 instance has been removed.
  251 This makes it easier to maintain deterministic builds, but comes with some
  252 drawbacks.
  253 The biggest drawback is that Maps keyed by Uniques can't directly be used.
  254 The alternatives are:
  255 
  256   1) Use UniqFM or UniqDFM, see Note [Deterministic UniqFM] to decide which
  257   2) Create a newtype wrapper based on Unique ordering where nondeterminism
  258      is controlled. See Module.ModuleEnv
  259   3) Change the algorithm to use nonDetCmpUnique and document why it's still
  260      deterministic
  261   4) Use TrieMap as done in GHC.Cmm.CommonBlockElim.groupByLabel
  262 -}
  263 
  264 instance Eq Unique where
  265     a == b = eqUnique a b
  266     a /= b = not (eqUnique a b)
  267 
  268 instance Uniquable Unique where
  269     getUnique u = u
  270 
  271 -- We do sometimes make strings with @Uniques@ in them:
  272 
  273 showUnique :: Unique -> String
  274 showUnique uniq
  275   = case unpkUnique uniq of
  276       (tag, u) -> tag : iToBase62 u
  277 
  278 pprUniqueAlways :: Unique -> SDoc
  279 -- The "always" means regardless of -dsuppress-uniques
  280 -- It replaces the old pprUnique to remind callers that
  281 -- they should consider whether they want to consult
  282 -- Opt_SuppressUniques
  283 pprUniqueAlways u
  284   = text (showUnique u)
  285 
  286 instance Outputable Unique where
  287     ppr = pprUniqueAlways
  288 
  289 instance Show Unique where
  290     show uniq = showUnique uniq
  291 
  292 {-
  293 ************************************************************************
  294 *                                                                      *
  295 \subsection[Utils-base62]{Base-62 numbers}
  296 *                                                                      *
  297 ************************************************************************
  298 
  299 A character-stingy way to read/write numbers (notably Uniques).
  300 The ``62-its'' are \tr{[0-9a-zA-Z]}.  We don't handle negative Ints.
  301 Code stolen from Lennart.
  302 -}
  303 
  304 iToBase62 :: Int -> String
  305 iToBase62 n_
  306   = assert (n_ >= 0) $ go n_ ""
  307   where
  308     go n cs | n < 62
  309             = let !c = chooseChar62 n in c : cs
  310             | otherwise
  311             = go q (c : cs) where (!q, r) = quotRem n 62
  312                                   !c = chooseChar62 r
  313 
  314     chooseChar62 :: Int -> Char
  315     {-# INLINE chooseChar62 #-}
  316     chooseChar62 (I# n) = C# (indexCharOffAddr# chars62 n)
  317     chars62 = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"#