[project @ 2004-08-13 13:04:50 by simonmar]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Unique.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4
5 @Uniques@ are used to distinguish entities in the compiler (@Ids@,
6 @Classes@, etc.) from each other.  Thus, @Uniques@ are the basic
7 comparison key in the compiler.
8
9 If there is any single operation that needs to be fast, it is @Unique@
10 comparison.  Unsurprisingly, there is quite a bit of huff-and-puff
11 directed to that end.
12
13 Some of the other hair in this code is to be able to use a
14 ``splittable @UniqueSupply@'' if requested/possible (not standard
15 Haskell).
16
17 \begin{code}
18 module Unique (
19         Unique, Uniquable(..), hasKey,
20
21         pprUnique,
22
23         mkUnique,                       -- Used in UniqSupply
24         mkUniqueGrimily,                -- Used in UniqSupply only!
25         getKey, getKey#,                -- Used in Var, UniqFM, Name only!
26
27         incrUnique,                     -- Used for renumbering
28         deriveUnique,                   -- Ditto
29         newTagUnique,                   -- Used in CgCase
30         initTyVarUnique,
31
32         isTupleKey, 
33
34         -- now all the built-in Uniques (and functions to make them)
35         -- [the Oh-So-Wonderful Haskell module system wins again...]
36         mkAlphaTyVarUnique,
37         mkPrimOpIdUnique,
38         mkTupleTyConUnique, mkTupleDataConUnique,
39         mkPreludeMiscIdUnique, mkPreludeDataConUnique,
40         mkPreludeTyConUnique, mkPreludeClassUnique,
41         mkPArrDataConUnique,
42
43         mkBuiltinUnique,
44         mkPseudoUniqueC,
45         mkPseudoUniqueD,
46         mkPseudoUniqueE,
47         mkPseudoUniqueH
48     ) where
49
50 #include "HsVersions.h"
51
52 import BasicTypes       ( Boxity(..) )
53 import FastString       ( FastString, uniqueOfFS )
54 import Outputable
55 import FastTypes
56
57 import GLAEXTS
58
59 import Char             ( chr, ord )
60 \end{code}
61
62 %************************************************************************
63 %*                                                                      *
64 \subsection[Unique-type]{@Unique@ type and operations}
65 %*                                                                      *
66 %************************************************************************
67
68 The @Chars@ are ``tag letters'' that identify the @UniqueSupply@.
69 Fast comparison is everything on @Uniques@:
70
71 \begin{code}
72 data Unique = MkUnique Int#
73 \end{code}
74
75 Now come the functions which construct uniques from their pieces, and vice versa.
76 The stuff about unique *supplies* is handled further down this module.
77
78 \begin{code}
79 mkUnique        :: Char -> Int -> Unique        -- Builds a unique from pieces
80 unpkUnique      :: Unique -> (Char, Int)        -- The reverse
81
82 mkUniqueGrimily :: Int -> Unique                -- A trap-door for UniqSupply
83 getKey          :: Unique -> Int                -- for Var
84 getKey#         :: Unique -> Int#               -- for Var
85
86 incrUnique      :: Unique -> Unique
87 deriveUnique    :: Unique -> Int -> Unique
88 newTagUnique    :: Unique -> Char -> Unique
89
90 isTupleKey      :: Unique -> Bool
91 \end{code}
92
93
94 \begin{code}
95 mkUniqueGrimily (I# x) = MkUnique x
96
97 {-# INLINE getKey #-}
98 getKey (MkUnique x) = I# x
99 {-# INLINE getKey# #-}
100 getKey# (MkUnique x) = x
101
102 incrUnique (MkUnique i) = MkUnique (i +# 1#)
103
104 -- deriveUnique uses an 'X' tag so that it won't clash with
105 -- any of the uniques produced any other way
106 deriveUnique (MkUnique i) delta = mkUnique 'X' (I# i + delta)
107
108 -- newTagUnique changes the "domain" of a unique to a different char
109 newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u
110
111 -- pop the Char in the top 8 bits of the Unique(Supply)
112
113 -- No 64-bit bugs here, as long as we have at least 32 bits. --JSM
114
115 w2i x = word2Int# x
116 i2w x = int2Word# x
117 i2w_s x = (x::Int#)
118
119 mkUnique (C# c) (I# i)
120   = MkUnique (w2i (tag `or#` bits))
121   where
122 #if __GLASGOW_HASKELL__ >= 503
123     tag  = i2w (ord# c) `uncheckedShiftL#` i2w_s 24#
124 #else
125     tag  = i2w (ord# c) `shiftL#` i2w_s 24#
126 #endif
127     bits = i2w i `and#` (i2w 16777215#){-``0x00ffffff''-}
128
129 unpkUnique (MkUnique u)
130   = let
131         tag = C# (chr# (w2i ((i2w u) `shiftr` (i2w_s 24#))))
132         i   = I# (w2i ((i2w u) `and#` (i2w 16777215#){-``0x00ffffff''-}))
133     in
134     (tag, i)
135   where
136 #if __GLASGOW_HASKELL__ >= 503
137     shiftr x y = uncheckedShiftRL# x y
138 #else
139     shiftr x y = shiftRL# x y
140 #endif
141 \end{code}
142
143
144
145 %************************************************************************
146 %*                                                                      *
147 \subsection[Uniquable-class]{The @Uniquable@ class}
148 %*                                                                      *
149 %************************************************************************
150
151 \begin{code}
152 class Uniquable a where
153     getUnique :: a -> Unique
154
155 hasKey          :: Uniquable a => a -> Unique -> Bool
156 x `hasKey` k    = getUnique x == k
157
158 instance Uniquable FastString where
159  getUnique fs = mkUniqueGrimily (I# (uniqueOfFS fs))
160
161 instance Uniquable Int where
162  getUnique i = mkUniqueGrimily i
163 \end{code}
164
165
166 %************************************************************************
167 %*                                                                      *
168 \subsection[Unique-instances]{Instance declarations for @Unique@}
169 %*                                                                      *
170 %************************************************************************
171
172 And the whole point (besides uniqueness) is fast equality.  We don't
173 use `deriving' because we want {\em precise} control of ordering
174 (equality on @Uniques@ is v common).
175
176 \begin{code}
177 eqUnique (MkUnique u1) (MkUnique u2) = u1 ==# u2
178 ltUnique (MkUnique u1) (MkUnique u2) = u1 <#  u2
179 leUnique (MkUnique u1) (MkUnique u2) = u1 <=# u2
180
181 cmpUnique (MkUnique u1) (MkUnique u2)
182   = if u1 ==# u2 then EQ else if u1 <# u2 then LT else GT
183
184 instance Eq Unique where
185     a == b = eqUnique a b
186     a /= b = not (eqUnique a b)
187
188 instance Ord Unique where
189     a  < b = ltUnique a b
190     a <= b = leUnique a b
191     a  > b = not (leUnique a b)
192     a >= b = not (ltUnique a b)
193     compare a b = cmpUnique a b
194
195 -----------------
196 instance Uniquable Unique where
197     getUnique u = u
198 \end{code}
199
200 We do sometimes make strings with @Uniques@ in them:
201 \begin{code}
202 pprUnique :: Unique -> SDoc
203 pprUnique uniq
204   = case unpkUnique uniq of
205       (tag, u) -> finish_ppr tag u (iToBase62 u)
206
207 #ifdef UNUSED
208 pprUnique10 :: Unique -> SDoc
209 pprUnique10 uniq        -- in base-10, dudes
210   = case unpkUnique uniq of
211       (tag, u) -> finish_ppr tag u (int u)
212 #endif
213
214 finish_ppr 't' u pp_u | u < 26
215   =     -- Special case to make v common tyvars, t1, t2, ...
216         -- come out as a, b, ... (shorter, easier to read)
217     char (chr (ord 'a' + u))
218 finish_ppr tag u pp_u = char tag <> pp_u
219
220 instance Outputable Unique where
221     ppr u = pprUnique u
222
223 instance Show Unique where
224     showsPrec p uniq = showsPrecSDoc p (pprUnique uniq)
225 \end{code}
226
227 %************************************************************************
228 %*                                                                      *
229 \subsection[Utils-base62]{Base-62 numbers}
230 %*                                                                      *
231 %************************************************************************
232
233 A character-stingy way to read/write numbers (notably Uniques).
234 The ``62-its'' are \tr{[0-9a-zA-Z]}.  We don't handle negative Ints.
235 Code stolen from Lennart.
236
237 \begin{code}
238 iToBase62 :: Int -> SDoc
239
240 iToBase62 n@(I# n#)
241   = ASSERT(n >= 0)
242     if n# <# 62# then
243         case (indexCharOffAddr# chars62# n#) of { c ->
244         char (C# c) }
245     else
246         case (quotRem n 62)             of { (q, I# r#) ->
247         case (indexCharOffAddr# chars62# r#) of { c  ->
248         (<>) (iToBase62 q) (char (C# c)) }}
249   where
250      chars62# = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"#
251 \end{code}
252
253 %************************************************************************
254 %*                                                                      *
255 \subsection[Uniques-prelude]{@Uniques@ for wired-in Prelude things}
256 %*                                                                      *
257 %************************************************************************
258
259 Allocation of unique supply characters:
260         v,t,u : for renumbering value-, type- and usage- vars.
261         B:   builtin
262         C-E: pseudo uniques     (used in native-code generator)
263         X:   uniques derived by deriveUnique
264         _:   unifiable tyvars   (above)
265         0-9: prelude things below
266
267         other a-z: lower case chars for unique supplies.  Used so far:
268
269         d       desugarer
270         f       AbsC flattener
271         g       SimplStg
272         l       ndpFlatten
273         n       Native codegen
274         r       Hsc name cache
275         s       simplifier
276
277 \begin{code}
278 mkAlphaTyVarUnique i            = mkUnique '1' i
279
280 mkPreludeClassUnique i          = mkUnique '2' i
281
282 -- Prelude type constructors occupy *three* slots.
283 -- The first is for the tycon itself; the latter two
284 -- are for the generic to/from Ids.  See TysWiredIn.mk_tc_gen_info.
285
286 mkPreludeTyConUnique i          = mkUnique '3' (3*i)
287 mkTupleTyConUnique Boxed   a    = mkUnique '4' (3*a)
288 mkTupleTyConUnique Unboxed a    = mkUnique '5' (3*a)
289
290 -- Data constructor keys occupy *two* slots.  The first is used for the
291 -- data constructor itself and its wrapper function (the function that
292 -- evaluates arguments as necessary and calls the worker). The second is
293 -- used for the worker function (the function that builds the constructor
294 -- representation).
295
296 mkPreludeDataConUnique i        = mkUnique '6' (2*i)    -- Must be alphabetic
297 mkTupleDataConUnique Boxed a    = mkUnique '7' (2*a)    -- ditto (*may* be used in C labels)
298 mkTupleDataConUnique Unboxed a  = mkUnique '8' (2*a)
299
300 -- This one is used for a tiresome reason
301 -- to improve a consistency-checking error check in the renamer
302 isTupleKey u = case unpkUnique u of
303                 (tag,_) -> tag == '4' || tag == '5' || tag == '7' || tag == '8'
304
305 mkPrimOpIdUnique op             = mkUnique '9' op
306 mkPreludeMiscIdUnique i         = mkUnique '0' i
307
308 -- No numbers left anymore, so I pick something different for the character
309 -- tag 
310 mkPArrDataConUnique a           = mkUnique ':' (2*a)
311
312 -- The "tyvar uniques" print specially nicely: a, b, c, etc.
313 -- See pprUnique for details
314
315 initTyVarUnique :: Unique
316 initTyVarUnique = mkUnique 't' 0
317
318 mkPseudoUniqueC, mkPseudoUniqueD, mkPseudoUniqueE, mkPseudoUniqueH,
319    mkBuiltinUnique :: Int -> Unique
320
321 mkBuiltinUnique i = mkUnique 'B' i
322 mkPseudoUniqueC i = mkUnique 'C' i -- used for getUnique on Regs
323 mkPseudoUniqueD i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs
324 mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs
325 mkPseudoUniqueH i = mkUnique 'H' i -- used in NCG spiller to create spill VirtualRegs
326 \end{code}
327