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