6e0ee20ead805d7163cc3ed95f596603c7204d09
[ghc-hetmet.git] / compiler / basicTypes / Unique.lhs
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 comparison.  Unsurprisingly, there is quite a bit of huff-and-puff
12 directed to that end.
13
14 Some of the other hair in this code is to be able to use a
15 ``splittable @UniqueSupply@'' if requested/possible (not standard
16 Haskell).
17
18 \begin{code}
19 module Unique (
20         -- * Main data types
21         Unique, Uniquable(..), 
22         
23         -- ** Constructors, desctructors and operations on 'Unique's
24         hasKey,
25
26         pprUnique, 
27
28         mkUniqueGrimily,                -- Used in UniqSupply only!
29         getKey, getKeyFastInt,          -- Used in Var, UniqFM, Name only!
30
31         incrUnique,                     -- Used for renumbering
32         deriveUnique,                   -- Ditto
33         newTagUnique,                   -- Used in CgCase
34         initTyVarUnique,
35
36         isTupleKey, 
37
38         -- ** Making built-in uniques
39
40         -- now all the built-in Uniques (and functions to make them)
41         -- [the Oh-So-Wonderful Haskell module system wins again...]
42         mkAlphaTyVarUnique,
43         mkPrimOpIdUnique,
44         mkTupleTyConUnique, mkTupleDataConUnique,
45         mkPreludeMiscIdUnique, mkPreludeDataConUnique,
46         mkPreludeTyConUnique, mkPreludeClassUnique,
47         mkPArrDataConUnique,
48
49         mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique,
50         mkRegSingleUnique, mkRegPairUnique, mkRegClassUnique, mkRegSubUnique,
51
52         mkBuiltinUnique,
53         mkPseudoUniqueC,
54         mkPseudoUniqueD,
55         mkPseudoUniqueE,
56         mkPseudoUniqueH
57     ) where
58
59 #include "HsVersions.h"
60
61 import BasicTypes
62 import FastTypes
63 import FastString
64 import Outputable
65 -- import StaticFlags
66
67 #if defined(__GLASGOW_HASKELL__)
68 --just for implementing a fast [0,61) -> Char function
69 import GHC.Exts (indexCharOffAddr#, Char(..))
70 #else
71 import Data.Array
72 #endif
73 import Data.Char        ( chr, ord )
74 \end{code}
75
76 %************************************************************************
77 %*                                                                      *
78 \subsection[Unique-type]{@Unique@ type and operations}
79 %*                                                                      *
80 %************************************************************************
81
82 The @Chars@ are ``tag letters'' that identify the @UniqueSupply@.
83 Fast comparison is everything on @Uniques@:
84
85 \begin{code}
86 --why not newtype Int?
87
88 -- | The type of unique identifiers that are used in many places in GHC
89 -- for fast ordering and equality tests. You should generate these with
90 -- the functions from the 'UniqSupply' module
91 data Unique = MkUnique FastInt
92 \end{code}
93
94 Now come the functions which construct uniques from their pieces, and vice versa.
95 The stuff about unique *supplies* is handled further down this module.
96
97 \begin{code}
98 unpkUnique      :: Unique -> (Char, Int)        -- The reverse
99
100 mkUniqueGrimily :: Int -> Unique                -- A trap-door for UniqSupply
101 getKey          :: Unique -> Int                -- for Var
102 getKeyFastInt   :: Unique -> FastInt            -- for Var
103
104 incrUnique      :: Unique -> Unique
105 deriveUnique    :: Unique -> Int -> Unique
106 newTagUnique    :: Unique -> Char -> Unique
107
108 isTupleKey      :: Unique -> Bool
109 \end{code}
110
111
112 \begin{code}
113 mkUniqueGrimily x = MkUnique (iUnbox x)
114
115 {-# INLINE getKey #-}
116 getKey (MkUnique x) = iBox x
117 {-# INLINE getKeyFastInt #-}
118 getKeyFastInt (MkUnique x) = x
119
120 incrUnique (MkUnique i) = MkUnique (i +# _ILIT(1))
121
122 -- deriveUnique uses an 'X' tag so that it won't clash with
123 -- any of the uniques produced any other way
124 deriveUnique (MkUnique i) delta = mkUnique 'X' (iBox i + delta)
125
126 -- newTagUnique changes the "domain" of a unique to a different char
127 newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u
128
129 -- pop the Char in the top 8 bits of the Unique(Supply)
130
131 -- No 64-bit bugs here, as long as we have at least 32 bits. --JSM
132
133 -- and as long as the Char fits in 8 bits, which we assume anyway!
134
135 mkUnique :: Char -> Int -> Unique       -- Builds a unique from pieces
136 -- NOT EXPORTED, so that we can see all the Chars that 
137 --               are used in this one module
138 mkUnique c i
139   = MkUnique (tag `bitOrFastInt` bits)
140   where
141     !tag  = fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24)
142     !bits = iUnbox i `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-}
143
144 unpkUnique (MkUnique u)
145   = let
146         -- as long as the Char may have its eighth bit set, we
147         -- really do need the logical right-shift here!
148         tag = cBox (fastChr (u `shiftRLFastInt` _ILIT(24)))
149         i   = iBox (u `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-})
150     in
151     (tag, i)
152 \end{code}
153
154
155
156 %************************************************************************
157 %*                                                                      *
158 \subsection[Uniquable-class]{The @Uniquable@ class}
159 %*                                                                      *
160 %************************************************************************
161
162 \begin{code}
163 -- | Class of things that we can obtain a 'Unique' from
164 class Uniquable a where
165     getUnique :: a -> Unique
166
167 hasKey          :: Uniquable a => a -> Unique -> Bool
168 x `hasKey` k    = getUnique x == k
169
170 instance Uniquable FastString where
171  getUnique fs = mkUniqueGrimily (iBox (uniqueOfFS fs))
172
173 instance Uniquable Int where
174  getUnique i = mkUniqueGrimily i
175 \end{code}
176
177
178 %************************************************************************
179 %*                                                                      *
180 \subsection[Unique-instances]{Instance declarations for @Unique@}
181 %*                                                                      *
182 %************************************************************************
183
184 And the whole point (besides uniqueness) is fast equality.  We don't
185 use `deriving' because we want {\em precise} control of ordering
186 (equality on @Uniques@ is v common).
187
188 \begin{code}
189 eqUnique, ltUnique, leUnique :: Unique -> Unique -> Bool
190 eqUnique (MkUnique u1) (MkUnique u2) = u1 ==# u2
191 ltUnique (MkUnique u1) (MkUnique u2) = u1 <#  u2
192 leUnique (MkUnique u1) (MkUnique u2) = u1 <=# u2
193
194 cmpUnique :: Unique -> Unique -> Ordering
195 cmpUnique (MkUnique u1) (MkUnique u2)
196   = if u1 ==# u2 then EQ else if u1 <# u2 then LT else GT
197
198 instance Eq Unique where
199     a == b = eqUnique a b
200     a /= b = not (eqUnique a b)
201
202 instance Ord Unique where
203     a  < b = ltUnique a b
204     a <= b = leUnique a b
205     a  > b = not (leUnique a b)
206     a >= b = not (ltUnique a b)
207     compare a b = cmpUnique a b
208
209 -----------------
210 instance Uniquable Unique where
211     getUnique u = u
212 \end{code}
213
214 We do sometimes make strings with @Uniques@ in them:
215 \begin{code}
216 pprUnique :: Unique -> SDoc
217 pprUnique uniq
218 --   | opt_SuppressUniques
219 --  = empty     -- Used exclusively to suppress uniques so you 
220 --  | otherwise -- can compare output easily
221   = case unpkUnique uniq of
222       (tag, u) -> finish_ppr tag u (text (iToBase62 u))
223
224 #ifdef UNUSED
225 pprUnique10 :: Unique -> SDoc
226 pprUnique10 uniq        -- in base-10, dudes
227   = case unpkUnique uniq of
228       (tag, u) -> finish_ppr tag u (int u)
229 #endif
230
231 finish_ppr :: Char -> Int -> SDoc -> SDoc
232 finish_ppr 't' u _pp_u | u < 26
233   =     -- Special case to make v common tyvars, t1, t2, ...
234         -- come out as a, b, ... (shorter, easier to read)
235     char (chr (ord 'a' + u))
236 finish_ppr tag _ pp_u = char tag <> pp_u
237
238 instance Outputable Unique where
239     ppr u = pprUnique u
240
241 instance Show Unique where
242     showsPrec p uniq = showsPrecSDoc p (pprUnique uniq)
243 \end{code}
244
245 %************************************************************************
246 %*                                                                      *
247 \subsection[Utils-base62]{Base-62 numbers}
248 %*                                                                      *
249 %************************************************************************
250
251 A character-stingy way to read/write numbers (notably Uniques).
252 The ``62-its'' are \tr{[0-9a-zA-Z]}.  We don't handle negative Ints.
253 Code stolen from Lennart.
254
255 \begin{code}
256 iToBase62 :: Int -> String
257 iToBase62 n_
258   = ASSERT(n_ >= 0) go (iUnbox n_) ""
259   where
260     go n cs | n <# _ILIT(62)
261              = case chooseChar62 n of { c -> c `seq` (c : cs) }
262              | otherwise
263              =  case (quotRem (iBox n) 62) of { (q_, r_) ->
264                 case iUnbox q_ of { q -> case iUnbox r_ of { r ->
265                 case (chooseChar62 r) of { c -> c `seq`
266                 (go q (c : cs)) }}}}
267
268     chooseChar62 :: FastInt -> Char
269     {-# INLINE chooseChar62 #-}
270 #if defined(__GLASGOW_HASKELL__)
271     --then FastInt == Int#
272     chooseChar62 n = C# (indexCharOffAddr# chars62 n)
273     !chars62 = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"#
274 #else
275     --Haskell98 arrays are portable
276     chooseChar62 n = (!) chars62 n
277     chars62 = listArray (0,61) "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"
278 #endif
279 \end{code}
280
281 %************************************************************************
282 %*                                                                      *
283 \subsection[Uniques-prelude]{@Uniques@ for wired-in Prelude things}
284 %*                                                                      *
285 %************************************************************************
286
287 Allocation of unique supply characters:
288         v,t,u : for renumbering value-, type- and usage- vars.
289         B:   builtin
290         C-E: pseudo uniques     (used in native-code generator)
291         X:   uniques derived by deriveUnique
292         _:   unifiable tyvars   (above)
293         0-9: prelude things below
294              (no numbers left any more..)
295         ::   (prelude) parallel array data constructors
296
297         other a-z: lower case chars for unique supplies.  Used so far:
298
299         d       desugarer
300         f       AbsC flattener
301         g       SimplStg
302         n       Native codegen
303         r       Hsc name cache
304         s       simplifier
305
306 \begin{code}
307 mkAlphaTyVarUnique     :: Int -> Unique
308 mkPreludeClassUnique   :: Int -> Unique
309 mkPreludeTyConUnique   :: Int -> Unique
310 mkTupleTyConUnique     :: Boxity -> Int -> Unique
311 mkPreludeDataConUnique :: Int -> Unique
312 mkTupleDataConUnique   :: Boxity -> Int -> Unique
313 mkPrimOpIdUnique       :: Int -> Unique
314 mkPreludeMiscIdUnique  :: Int -> Unique
315 mkPArrDataConUnique    :: Int -> Unique
316
317 mkAlphaTyVarUnique i            = mkUnique '1' i
318
319 mkPreludeClassUnique i          = mkUnique '2' i
320
321 -- Prelude type constructors occupy *three* slots.
322 -- The first is for the tycon itself; the latter two
323 -- are for the generic to/from Ids.  See TysWiredIn.mk_tc_gen_info.
324
325 mkPreludeTyConUnique i          = mkUnique '3' (3*i)
326 mkTupleTyConUnique Boxed   a    = mkUnique '4' (3*a)
327 mkTupleTyConUnique Unboxed a    = mkUnique '5' (3*a)
328
329 -- Data constructor keys occupy *two* slots.  The first is used for the
330 -- data constructor itself and its wrapper function (the function that
331 -- evaluates arguments as necessary and calls the worker). The second is
332 -- used for the worker function (the function that builds the constructor
333 -- representation).
334
335 mkPreludeDataConUnique i        = mkUnique '6' (2*i)    -- Must be alphabetic
336 mkTupleDataConUnique Boxed a    = mkUnique '7' (2*a)    -- ditto (*may* be used in C labels)
337 mkTupleDataConUnique Unboxed a  = mkUnique '8' (2*a)
338
339 -- This one is used for a tiresome reason
340 -- to improve a consistency-checking error check in the renamer
341 isTupleKey u = case unpkUnique u of
342                 (tag,_) -> tag == '4' || tag == '5' || tag == '7' || tag == '8'
343
344 mkPrimOpIdUnique op         = mkUnique '9' op
345 mkPreludeMiscIdUnique  i    = mkUnique '0' i
346
347 -- No numbers left anymore, so I pick something different for the character tag 
348 mkPArrDataConUnique a           = mkUnique ':' (2*a)
349
350 -- The "tyvar uniques" print specially nicely: a, b, c, etc.
351 -- See pprUnique for details
352
353 initTyVarUnique :: Unique
354 initTyVarUnique = mkUnique 't' 0
355
356 mkPseudoUniqueC, mkPseudoUniqueD, mkPseudoUniqueE, mkPseudoUniqueH,
357    mkBuiltinUnique :: Int -> Unique
358
359 mkBuiltinUnique i = mkUnique 'B' i
360 mkPseudoUniqueC i = mkUnique 'C' i -- used for getUnique on Regs
361 mkPseudoUniqueD i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs
362 mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs
363 mkPseudoUniqueH i = mkUnique 'H' i -- used in NCG spiller to create spill VirtualRegs
364
365 mkRegSingleUnique, mkRegPairUnique, mkRegSubUnique, mkRegClassUnique :: Int -> Unique
366 mkRegSingleUnique = mkUnique 'R'
367 mkRegSubUnique    = mkUnique 'S'
368 mkRegPairUnique   = mkUnique 'P'
369 mkRegClassUnique  = mkUnique 'L'
370
371 mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique :: FastString -> Unique
372 -- See Note [The Unique of an OccName] in OccName
373 mkVarOccUnique  fs = mkUnique 'i' (iBox (uniqueOfFS fs))
374 mkDataOccUnique fs = mkUnique 'd' (iBox (uniqueOfFS fs))
375 mkTvOccUnique   fs = mkUnique 'v' (iBox (uniqueOfFS fs))
376 mkTcOccUnique   fs = mkUnique 'c' (iBox (uniqueOfFS fs))
377 \end{code}
378