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