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