lots of portability changes (#1405)
[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, getKeyFastInt,          -- 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 FastTypes
63 import FastString
64 import Outputable
65
66 #if defined(__GLASGOW_HASKELL__)
67 --just for implementing a fast [0,61) -> Char function
68 import GHC.Exts (indexCharOffAddr#, Char(..))
69 #else
70 import Data.Array
71 #endif
72 import Data.Char        ( chr, ord )
73 \end{code}
74
75 %************************************************************************
76 %*                                                                      *
77 \subsection[Unique-type]{@Unique@ type and operations}
78 %*                                                                      *
79 %************************************************************************
80
81 The @Chars@ are ``tag letters'' that identify the @UniqueSupply@.
82 Fast comparison is everything on @Uniques@:
83
84 \begin{code}
85 --why not newtype Int?
86 data Unique = MkUnique FastInt
87 \end{code}
88
89 Now come the functions which construct uniques from their pieces, and vice versa.
90 The stuff about unique *supplies* is handled further down this module.
91
92 \begin{code}
93 mkUnique        :: Char -> Int -> Unique        -- Builds a unique from pieces
94 unpkUnique      :: Unique -> (Char, Int)        -- The reverse
95
96 mkUniqueGrimily :: Int -> Unique                -- A trap-door for UniqSupply
97 getKey          :: Unique -> Int                -- for Var
98 getKeyFastInt   :: Unique -> FastInt            -- for Var
99
100 incrUnique      :: Unique -> Unique
101 deriveUnique    :: Unique -> Int -> Unique
102 newTagUnique    :: Unique -> Char -> Unique
103
104 isTupleKey      :: Unique -> Bool
105 \end{code}
106
107
108 \begin{code}
109 mkUniqueGrimily x = MkUnique (iUnbox x)
110
111 {-# INLINE getKey #-}
112 getKey (MkUnique x) = iBox x
113 {-# INLINE getKeyFastInt #-}
114 getKeyFastInt (MkUnique x) = x
115
116 incrUnique (MkUnique i) = MkUnique (i +# _ILIT(1))
117
118 -- deriveUnique uses an 'X' tag so that it won't clash with
119 -- any of the uniques produced any other way
120 deriveUnique (MkUnique i) delta = mkUnique 'X' (iBox i + delta)
121
122 -- newTagUnique changes the "domain" of a unique to a different char
123 newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u
124
125 -- pop the Char in the top 8 bits of the Unique(Supply)
126
127 -- No 64-bit bugs here, as long as we have at least 32 bits. --JSM
128
129 -- and as long as the Char fits in 8 bits, which we assume anyway!
130
131 mkUnique c i
132   = MkUnique (tag `bitOrFastInt` bits)
133   where
134     tag  = fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24)
135     bits = iUnbox i `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-}
136
137 unpkUnique (MkUnique u)
138   = let
139         -- as long as the Char may have its eighth bit set, we
140         -- really do need the logical right-shift here!
141         tag = cBox (fastChr (u `shiftRLFastInt` _ILIT(24)))
142         i   = iBox (u `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-})
143     in
144     (tag, i)
145 \end{code}
146
147
148
149 %************************************************************************
150 %*                                                                      *
151 \subsection[Uniquable-class]{The @Uniquable@ class}
152 %*                                                                      *
153 %************************************************************************
154
155 \begin{code}
156 class Uniquable a where
157     getUnique :: a -> Unique
158
159 hasKey          :: Uniquable a => a -> Unique -> Bool
160 x `hasKey` k    = getUnique x == k
161
162 instance Uniquable FastString where
163  getUnique fs = mkUniqueGrimily (iBox (uniqueOfFS fs))
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 #ifdef DEBUG
209   | opt_SuppressUniques
210   = empty       -- Used exclusively to suppress uniques so you 
211   | otherwise   -- can compare output easily
212 #endif
213   = case unpkUnique uniq of
214       (tag, u) -> finish_ppr tag u (text (iToBase62 u))
215
216 #ifdef UNUSED
217 pprUnique10 :: Unique -> SDoc
218 pprUnique10 uniq        -- in base-10, dudes
219   = case unpkUnique uniq of
220       (tag, u) -> finish_ppr tag u (int u)
221 #endif
222
223 finish_ppr 't' u pp_u | u < 26
224   =     -- Special case to make v common tyvars, t1, t2, ...
225         -- come out as a, b, ... (shorter, easier to read)
226     char (chr (ord 'a' + u))
227 finish_ppr tag u pp_u = char tag <> pp_u
228
229 instance Outputable Unique where
230     ppr u = pprUnique u
231
232 instance Show Unique where
233     showsPrec p uniq = showsPrecSDoc p (pprUnique uniq)
234 \end{code}
235
236 %************************************************************************
237 %*                                                                      *
238 \subsection[Utils-base62]{Base-62 numbers}
239 %*                                                                      *
240 %************************************************************************
241
242 A character-stingy way to read/write numbers (notably Uniques).
243 The ``62-its'' are \tr{[0-9a-zA-Z]}.  We don't handle negative Ints.
244 Code stolen from Lennart.
245
246 \begin{code}
247 iToBase62 :: Int -> String
248 iToBase62 n_
249   = ASSERT(n_ >= 0) go (iUnbox n_) ""
250   where
251     go n cs | n <# _ILIT(62)
252              = case chooseChar62 n of { c -> c `seq` (c : cs) }
253              | otherwise
254              =  case (quotRem (iBox n) 62) of { (q_, r_) ->
255                 case iUnbox q_ of { q -> case iUnbox r_ of { r ->
256                 case (chooseChar62 r) of { c -> c `seq`
257                 (go q (c : cs)) }}}}
258
259     chooseChar62 :: FastInt -> Char
260     {-# INLINE chooseChar62 #-}
261 #if defined(__GLASGOW_HASKELL__)
262     --then FastInt == Int#
263     chooseChar62 n = C# (indexCharOffAddr# chars62 n)
264     chars62 = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"#
265 #else
266     --Haskell98 arrays are portable
267     chooseChar62 n = (!) chars62 n
268     chars62 = listArray (0,61) "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"
269 #endif
270 \end{code}
271
272 %************************************************************************
273 %*                                                                      *
274 \subsection[Uniques-prelude]{@Uniques@ for wired-in Prelude things}
275 %*                                                                      *
276 %************************************************************************
277
278 Allocation of unique supply characters:
279         v,t,u : for renumbering value-, type- and usage- vars.
280         B:   builtin
281         C-E: pseudo uniques     (used in native-code generator)
282         X:   uniques derived by deriveUnique
283         _:   unifiable tyvars   (above)
284         0-9: prelude things below
285
286         other a-z: lower case chars for unique supplies.  Used so far:
287
288         d       desugarer
289         f       AbsC flattener
290         g       SimplStg
291         l       ndpFlatten
292         n       Native codegen
293         r       Hsc name cache
294         s       simplifier
295
296 \begin{code}
297 mkAlphaTyVarUnique i            = mkUnique '1' i
298
299 mkPreludeClassUnique i          = mkUnique '2' i
300
301 -- Prelude type constructors occupy *three* slots.
302 -- The first is for the tycon itself; the latter two
303 -- are for the generic to/from Ids.  See TysWiredIn.mk_tc_gen_info.
304
305 mkPreludeTyConUnique i          = mkUnique '3' (3*i)
306 mkTupleTyConUnique Boxed   a    = mkUnique '4' (3*a)
307 mkTupleTyConUnique Unboxed a    = mkUnique '5' (3*a)
308
309 -- Data constructor keys occupy *two* slots.  The first is used for the
310 -- data constructor itself and its wrapper function (the function that
311 -- evaluates arguments as necessary and calls the worker). The second is
312 -- used for the worker function (the function that builds the constructor
313 -- representation).
314
315 mkPreludeDataConUnique i        = mkUnique '6' (2*i)    -- Must be alphabetic
316 mkTupleDataConUnique Boxed a    = mkUnique '7' (2*a)    -- ditto (*may* be used in C labels)
317 mkTupleDataConUnique Unboxed a  = mkUnique '8' (2*a)
318
319 -- This one is used for a tiresome reason
320 -- to improve a consistency-checking error check in the renamer
321 isTupleKey u = case unpkUnique u of
322                 (tag,_) -> tag == '4' || tag == '5' || tag == '7' || tag == '8'
323
324 mkPrimOpIdUnique op             = mkUnique '9' op
325 mkPreludeMiscIdUnique i         = mkUnique '0' i
326
327 -- No numbers left anymore, so I pick something different for the character
328 -- tag 
329 mkPArrDataConUnique a           = mkUnique ':' (2*a)
330
331 -- The "tyvar uniques" print specially nicely: a, b, c, etc.
332 -- See pprUnique for details
333
334 initTyVarUnique :: Unique
335 initTyVarUnique = mkUnique 't' 0
336
337 mkPseudoUniqueC, mkPseudoUniqueD, mkPseudoUniqueE, mkPseudoUniqueH,
338    mkBuiltinUnique :: Int -> Unique
339
340 mkBuiltinUnique i = mkUnique 'B' i
341 mkPseudoUniqueC i = mkUnique 'C' i -- used for getUnique on Regs
342 mkPseudoUniqueD i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs
343 mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs
344 mkPseudoUniqueH i = mkUnique 'H' i -- used in NCG spiller to create spill VirtualRegs
345 \end{code}
346