2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
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.
10 If there is any single operation that needs to be fast, it is @Unique@
11 comparison. Unsurprisingly, there is quite a bit of huff-and-puff
14 Some of the other hair in this code is to be able to use a
15 ``splittable @UniqueSupply@'' if requested/possible (not standard
19 {-# LANGUAGE BangPatterns #-}
21 {-# OPTIONS -fno-warn-tabs #-}
22 -- The above warning supression flag is a temporary kludge.
23 -- While working on this module you are encouraged to remove it and
24 -- detab the module (please do the detabbing in a separate patch). See
25 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
30 Unique, Uniquable(..),
32 -- ** Constructors, desctructors and operations on 'Unique's
37 mkUniqueGrimily, -- Used in UniqSupply only!
38 getKey, getKeyFastInt, -- Used in Var, UniqFM, Name only!
39 mkUnique, unpkUnique, -- Used in BinIface only
41 incrUnique, -- Used for renumbering
42 deriveUnique, -- Ditto
43 newTagUnique, -- Used in CgCase
46 -- ** Making built-in uniques
48 -- now all the built-in Uniques (and functions to make them)
49 -- [the Oh-So-Wonderful Haskell module system wins again...]
52 mkTupleTyConUnique, mkTupleDataConUnique,
53 mkPreludeMiscIdUnique, mkPreludeDataConUnique,
54 mkPreludeTyConUnique, mkPreludeClassUnique,
57 mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique,
58 mkRegSingleUnique, mkRegPairUnique, mkRegClassUnique, mkRegSubUnique,
67 #include "HsVersions.h"
76 #if defined(__GLASGOW_HASKELL__)
77 --just for implementing a fast [0,61) -> Char function
78 import GHC.Exts (indexCharOffAddr#, Char(..))
82 import Data.Char ( chr, ord )
85 %************************************************************************
87 \subsection[Unique-type]{@Unique@ type and operations}
89 %************************************************************************
91 The @Chars@ are ``tag letters'' that identify the @UniqueSupply@.
92 Fast comparison is everything on @Uniques@:
95 --why not newtype Int?
97 -- | The type of unique identifiers that are used in many places in GHC
98 -- for fast ordering and equality tests. You should generate these with
99 -- the functions from the 'UniqSupply' module
100 data Unique = MkUnique FastInt
103 Now come the functions which construct uniques from their pieces, and vice versa.
104 The stuff about unique *supplies* is handled further down this module.
107 unpkUnique :: Unique -> (Char, Int) -- The reverse
109 mkUniqueGrimily :: Int -> Unique -- A trap-door for UniqSupply
110 getKey :: Unique -> Int -- for Var
111 getKeyFastInt :: Unique -> FastInt -- for Var
113 incrUnique :: Unique -> Unique
114 deriveUnique :: Unique -> Int -> Unique
115 newTagUnique :: Unique -> Char -> Unique
120 mkUniqueGrimily x = MkUnique (iUnbox x)
122 {-# INLINE getKey #-}
123 getKey (MkUnique x) = iBox x
124 {-# INLINE getKeyFastInt #-}
125 getKeyFastInt (MkUnique x) = x
127 incrUnique (MkUnique i) = MkUnique (i +# _ILIT(1))
129 -- deriveUnique uses an 'X' tag so that it won't clash with
130 -- any of the uniques produced any other way
131 deriveUnique (MkUnique i) delta = mkUnique 'X' (iBox i + delta)
133 -- newTagUnique changes the "domain" of a unique to a different char
134 newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u
136 -- pop the Char in the top 8 bits of the Unique(Supply)
138 -- No 64-bit bugs here, as long as we have at least 32 bits. --JSM
140 -- and as long as the Char fits in 8 bits, which we assume anyway!
142 mkUnique :: Char -> Int -> Unique -- Builds a unique from pieces
143 -- NOT EXPORTED, so that we can see all the Chars that
144 -- are used in this one module
146 = MkUnique (tag `bitOrFastInt` bits)
148 !tag = fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24)
149 !bits = iUnbox i `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-}
151 unpkUnique (MkUnique u)
153 -- as long as the Char may have its eighth bit set, we
154 -- really do need the logical right-shift here!
155 tag = cBox (fastChr (u `shiftRLFastInt` _ILIT(24)))
156 i = iBox (u `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-})
163 %************************************************************************
165 \subsection[Uniquable-class]{The @Uniquable@ class}
167 %************************************************************************
170 -- | Class of things that we can obtain a 'Unique' from
171 class Uniquable a where
172 getUnique :: a -> Unique
174 hasKey :: Uniquable a => a -> Unique -> Bool
175 x `hasKey` k = getUnique x == k
177 instance Uniquable FastString where
178 getUnique fs = mkUniqueGrimily (iBox (uniqueOfFS fs))
180 instance Uniquable Int where
181 getUnique i = mkUniqueGrimily i
183 instance Uniquable n => Uniquable (IPName n) where
184 getUnique (IPName n) = getUnique n
188 %************************************************************************
190 \subsection[Unique-instances]{Instance declarations for @Unique@}
192 %************************************************************************
194 And the whole point (besides uniqueness) is fast equality. We don't
195 use `deriving' because we want {\em precise} control of ordering
196 (equality on @Uniques@ is v common).
199 eqUnique, ltUnique, leUnique :: Unique -> Unique -> Bool
200 eqUnique (MkUnique u1) (MkUnique u2) = u1 ==# u2
201 ltUnique (MkUnique u1) (MkUnique u2) = u1 <# u2
202 leUnique (MkUnique u1) (MkUnique u2) = u1 <=# u2
204 cmpUnique :: Unique -> Unique -> Ordering
205 cmpUnique (MkUnique u1) (MkUnique u2)
206 = if u1 ==# u2 then EQ else if u1 <# u2 then LT else GT
208 instance Eq Unique where
209 a == b = eqUnique a b
210 a /= b = not (eqUnique a b)
212 instance Ord Unique where
214 a <= b = leUnique a b
215 a > b = not (leUnique a b)
216 a >= b = not (ltUnique a b)
217 compare a b = cmpUnique a b
220 instance Uniquable Unique where
224 We do sometimes make strings with @Uniques@ in them:
226 pprUnique :: Unique -> SDoc
228 -- | opt_SuppressUniques
229 -- = empty -- Used exclusively to suppress uniques so you
230 -- | otherwise -- can compare output easily
231 = case unpkUnique uniq of
232 (tag, u) -> finish_ppr tag u (text (iToBase62 u))
235 pprUnique10 :: Unique -> SDoc
236 pprUnique10 uniq -- in base-10, dudes
237 = case unpkUnique uniq of
238 (tag, u) -> finish_ppr tag u (int u)
241 finish_ppr :: Char -> Int -> SDoc -> SDoc
242 finish_ppr 't' u _pp_u | u < 26
243 = -- Special case to make v common tyvars, t1, t2, ...
244 -- come out as a, b, ... (shorter, easier to read)
245 char (chr (ord 'a' + u))
246 finish_ppr tag _ pp_u = char tag <> pp_u
248 instance Outputable Unique where
251 instance Show Unique where
252 showsPrec p uniq = showsPrecSDoc p (pprUnique uniq)
255 %************************************************************************
257 \subsection[Utils-base62]{Base-62 numbers}
259 %************************************************************************
261 A character-stingy way to read/write numbers (notably Uniques).
262 The ``62-its'' are \tr{[0-9a-zA-Z]}. We don't handle negative Ints.
263 Code stolen from Lennart.
266 iToBase62 :: Int -> String
268 = ASSERT(n_ >= 0) go (iUnbox n_) ""
270 go n cs | n <# _ILIT(62)
271 = case chooseChar62 n of { c -> c `seq` (c : cs) }
273 = case (quotRem (iBox n) 62) of { (q_, r_) ->
274 case iUnbox q_ of { q -> case iUnbox r_ of { r ->
275 case (chooseChar62 r) of { c -> c `seq`
278 chooseChar62 :: FastInt -> Char
279 {-# INLINE chooseChar62 #-}
280 #if defined(__GLASGOW_HASKELL__)
281 --then FastInt == Int#
282 chooseChar62 n = C# (indexCharOffAddr# chars62 n)
283 !chars62 = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"#
285 --Haskell98 arrays are portable
286 chooseChar62 n = (!) chars62 n
287 chars62 = listArray (0,61) "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"
291 %************************************************************************
293 \subsection[Uniques-prelude]{@Uniques@ for wired-in Prelude things}
295 %************************************************************************
297 Allocation of unique supply characters:
298 v,t,u : for renumbering value-, type- and usage- vars.
300 C-E: pseudo uniques (used in native-code generator)
301 X: uniques derived by deriveUnique
302 _: unifiable tyvars (above)
303 0-9: prelude things below
304 (no numbers left any more..)
305 :: (prelude) parallel array data constructors
307 other a-z: lower case chars for unique supplies. Used so far:
317 mkAlphaTyVarUnique :: Int -> Unique
318 mkPreludeClassUnique :: Int -> Unique
319 mkPreludeTyConUnique :: Int -> Unique
320 mkTupleTyConUnique :: TupleSort -> Int -> Unique
321 mkPreludeDataConUnique :: Int -> Unique
322 mkTupleDataConUnique :: TupleSort -> Int -> Unique
323 mkPrimOpIdUnique :: Int -> Unique
324 mkPreludeMiscIdUnique :: Int -> Unique
325 mkPArrDataConUnique :: Int -> Unique
327 mkAlphaTyVarUnique i = mkUnique '1' i
329 mkPreludeClassUnique i = mkUnique '2' i
331 -- Prelude type constructors occupy *three* slots.
332 -- The first is for the tycon itself; the latter two
333 -- are for the generic to/from Ids. See TysWiredIn.mk_tc_gen_info.
335 mkPreludeTyConUnique i = mkUnique '3' (3*i)
336 mkTupleTyConUnique BoxedTuple a = mkUnique '4' (3*a)
337 mkTupleTyConUnique UnboxedTuple a = mkUnique '5' (3*a)
338 mkTupleTyConUnique ConstraintTuple a = mkUnique 'k' (3*a)
340 -- Data constructor keys occupy *two* slots. The first is used for the
341 -- data constructor itself and its wrapper function (the function that
342 -- evaluates arguments as necessary and calls the worker). The second is
343 -- used for the worker function (the function that builds the constructor
346 mkPreludeDataConUnique i = mkUnique '6' (2*i) -- Must be alphabetic
347 mkTupleDataConUnique BoxedTuple a = mkUnique '7' (2*a) -- ditto (*may* be used in C labels)
348 mkTupleDataConUnique UnboxedTuple a = mkUnique '8' (2*a)
349 mkTupleDataConUnique ConstraintTuple a = mkUnique 'h' (2*a)
351 mkPrimOpIdUnique op = mkUnique '9' op
352 mkPreludeMiscIdUnique i = mkUnique '0' i
354 -- No numbers left anymore, so I pick something different for the character tag
355 mkPArrDataConUnique a = mkUnique ':' (2*a)
357 -- The "tyvar uniques" print specially nicely: a, b, c, etc.
358 -- See pprUnique for details
360 initTyVarUnique :: Unique
361 initTyVarUnique = mkUnique 't' 0
363 mkPseudoUniqueD, mkPseudoUniqueE, mkPseudoUniqueH,
364 mkBuiltinUnique :: Int -> Unique
366 mkBuiltinUnique i = mkUnique 'B' i
367 mkPseudoUniqueD i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs
368 mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs
369 mkPseudoUniqueH i = mkUnique 'H' i -- used in NCG spiller to create spill VirtualRegs
371 mkRegSingleUnique, mkRegPairUnique, mkRegSubUnique, mkRegClassUnique :: Int -> Unique
372 mkRegSingleUnique = mkUnique 'R'
373 mkRegSubUnique = mkUnique 'S'
374 mkRegPairUnique = mkUnique 'P'
375 mkRegClassUnique = mkUnique 'L'
377 mkCostCentreUnique :: Int -> Unique
378 mkCostCentreUnique = mkUnique 'C'
380 mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique :: FastString -> Unique
381 -- See Note [The Unique of an OccName] in OccName
382 mkVarOccUnique fs = mkUnique 'i' (iBox (uniqueOfFS fs))
383 mkDataOccUnique fs = mkUnique 'd' (iBox (uniqueOfFS fs))
384 mkTvOccUnique fs = mkUnique 'v' (iBox (uniqueOfFS fs))
385 mkTcOccUnique fs = mkUnique 'c' (iBox (uniqueOfFS fs))