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