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