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