summaryrefslogtreecommitdiff
path: root/ghc/compiler/basicTypes/Unique.lhs
blob: 874328863e7b745c79e52abb3e25709ec7fc200d (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%

@Uniques@ are used to distinguish entities in the compiler (@Ids@,
@Classes@, etc.) from each other.  Thus, @Uniques@ are the basic
comparison key in the compiler.

If there is any single operation that needs to be fast, it is @Unique@
comparison.  Unsurprisingly, there is quite a bit of huff-and-puff
directed to that end.

Some of the other hair in this code is to be able to use a
``splittable @UniqueSupply@'' if requested/possible (not standard
Haskell).

\begin{code}
module Unique (
	Unique, Uniquable(..), hasKey,

	pprUnique, 

	mkUnique,			-- Used in UniqSupply
	mkUniqueGrimily,		-- Used in UniqSupply only!
	getKey, getKey#,		-- Used in Var, UniqFM, Name only!

	incrUnique,			-- Used for renumbering
	deriveUnique,			-- Ditto
	newTagUnique,			-- Used in CgCase
	initTyVarUnique,

	isTupleKey, 

	-- now all the built-in Uniques (and functions to make them)
	-- [the Oh-So-Wonderful Haskell module system wins again...]
	mkAlphaTyVarUnique,
	mkPrimOpIdUnique,
	mkTupleTyConUnique, mkTupleDataConUnique,
	mkPreludeMiscIdUnique, mkPreludeDataConUnique,
	mkPreludeTyConUnique, mkPreludeClassUnique,
	mkPArrDataConUnique,

	mkBuiltinUnique,
	mkPseudoUniqueC,
	mkPseudoUniqueD,
	mkPseudoUniqueE,
	mkPseudoUniqueH
    ) where

#include "HsVersions.h"

import BasicTypes	( Boxity(..) )
import PackageConfig	( PackageId, packageIdFS )
import FastString	( FastString, uniqueOfFS )
import Outputable
import FastTypes

import GLAEXTS

import Char		( chr, ord )
\end{code}

%************************************************************************
%*									*
\subsection[Unique-type]{@Unique@ type and operations}
%*									*
%************************************************************************

The @Chars@ are ``tag letters'' that identify the @UniqueSupply@.
Fast comparison is everything on @Uniques@:

\begin{code}
data Unique = MkUnique Int#
\end{code}

Now come the functions which construct uniques from their pieces, and vice versa.
The stuff about unique *supplies* is handled further down this module.

\begin{code}
mkUnique	:: Char -> Int -> Unique	-- Builds a unique from pieces
unpkUnique	:: Unique -> (Char, Int)	-- The reverse

mkUniqueGrimily :: Int -> Unique		-- A trap-door for UniqSupply
getKey		:: Unique -> Int		-- for Var
getKey#		:: Unique -> Int#		-- for Var

incrUnique	:: Unique -> Unique
deriveUnique	:: Unique -> Int -> Unique
newTagUnique	:: Unique -> Char -> Unique

isTupleKey	:: Unique -> Bool
\end{code}


\begin{code}
mkUniqueGrimily (I# x) = MkUnique x

{-# INLINE getKey #-}
getKey (MkUnique x) = I# x
{-# INLINE getKey# #-}
getKey# (MkUnique x) = x

incrUnique (MkUnique i) = MkUnique (i +# 1#)

-- deriveUnique uses an 'X' tag so that it won't clash with
-- any of the uniques produced any other way
deriveUnique (MkUnique i) delta = mkUnique 'X' (I# i + delta)

-- newTagUnique changes the "domain" of a unique to a different char
newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u

-- pop the Char in the top 8 bits of the Unique(Supply)

-- No 64-bit bugs here, as long as we have at least 32 bits. --JSM

w2i x = word2Int# x
i2w x = int2Word# x
i2w_s x = (x::Int#)

mkUnique (C# c) (I# i)
  = MkUnique (w2i (tag `or#` bits))
  where
#if __GLASGOW_HASKELL__ >= 503
    tag  = i2w (ord# c) `uncheckedShiftL#` i2w_s 24#
#else
    tag  = i2w (ord# c) `shiftL#` i2w_s 24#
#endif
    bits = i2w i `and#` (i2w 16777215#){-``0x00ffffff''-}

unpkUnique (MkUnique u)
  = let
	tag = C# (chr# (w2i ((i2w u) `shiftr` (i2w_s 24#))))
	i   = I# (w2i ((i2w u) `and#` (i2w 16777215#){-``0x00ffffff''-}))
    in
    (tag, i)
  where
#if __GLASGOW_HASKELL__ >= 503
    shiftr x y = uncheckedShiftRL# x y
#else
    shiftr x y = shiftRL# x y
#endif
\end{code}



%************************************************************************
%*									*
\subsection[Uniquable-class]{The @Uniquable@ class}
%*									*
%************************************************************************

\begin{code}
class Uniquable a where
    getUnique :: a -> Unique

hasKey		:: Uniquable a => a -> Unique -> Bool
x `hasKey` k	= getUnique x == k

instance Uniquable FastString where
 getUnique fs = mkUniqueGrimily (I# (uniqueOfFS fs))

instance Uniquable PackageId where
 getUnique pid = getUnique (packageIdFS pid)

instance Uniquable Int where
 getUnique i = mkUniqueGrimily i
\end{code}


%************************************************************************
%*									*
\subsection[Unique-instances]{Instance declarations for @Unique@}
%*									*
%************************************************************************

And the whole point (besides uniqueness) is fast equality.  We don't
use `deriving' because we want {\em precise} control of ordering
(equality on @Uniques@ is v common).

\begin{code}
eqUnique (MkUnique u1) (MkUnique u2) = u1 ==# u2
ltUnique (MkUnique u1) (MkUnique u2) = u1 <#  u2
leUnique (MkUnique u1) (MkUnique u2) = u1 <=# u2

cmpUnique (MkUnique u1) (MkUnique u2)
  = if u1 ==# u2 then EQ else if u1 <# u2 then LT else GT

instance Eq Unique where
    a == b = eqUnique a b
    a /= b = not (eqUnique a b)

instance Ord Unique where
    a  < b = ltUnique a b
    a <= b = leUnique a b
    a  > b = not (leUnique a b)
    a >= b = not (ltUnique a b)
    compare a b = cmpUnique a b

-----------------
instance Uniquable Unique where
    getUnique u = u
\end{code}

We do sometimes make strings with @Uniques@ in them:
\begin{code}
pprUnique :: Unique -> SDoc
pprUnique uniq
  = case unpkUnique uniq of
      (tag, u) -> finish_ppr tag u (text (iToBase62 u))

#ifdef UNUSED
pprUnique10 :: Unique -> SDoc
pprUnique10 uniq	-- in base-10, dudes
  = case unpkUnique uniq of
      (tag, u) -> finish_ppr tag u (int u)
#endif

finish_ppr 't' u pp_u | u < 26
  =	-- Special case to make v common tyvars, t1, t2, ...
	-- come out as a, b, ... (shorter, easier to read)
    char (chr (ord 'a' + u))
finish_ppr tag u pp_u = char tag <> pp_u

instance Outputable Unique where
    ppr u = pprUnique u

instance Show Unique where
    showsPrec p uniq = showsPrecSDoc p (pprUnique uniq)
\end{code}

%************************************************************************
%*									*
\subsection[Utils-base62]{Base-62 numbers}
%*									*
%************************************************************************

A character-stingy way to read/write numbers (notably Uniques).
The ``62-its'' are \tr{[0-9a-zA-Z]}.  We don't handle negative Ints.
Code stolen from Lennart.

\begin{code}
iToBase62 :: Int -> String
iToBase62 n@(I# n#) 
  = ASSERT(n >= 0) go n# ""
  where
    go n# cs | n# <# 62# 
	     = case (indexCharOffAddr# chars62# n#) of { c# -> C# c# : cs }
	     | otherwise
	     =	case (quotRem (I# n#) 62)	     of { (I# q#, I# r#) ->
		case (indexCharOffAddr# chars62# r#) of { c#  ->
		go q# (C# c# : cs) }}

    chars62# = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"#
\end{code}

%************************************************************************
%*									*
\subsection[Uniques-prelude]{@Uniques@ for wired-in Prelude things}
%*									*
%************************************************************************

Allocation of unique supply characters:
	v,t,u : for renumbering value-, type- and usage- vars.
	B:   builtin
	C-E: pseudo uniques	(used in native-code generator)
	X:   uniques derived by deriveUnique
	_:   unifiable tyvars   (above)
	0-9: prelude things below

	other a-z: lower case chars for unique supplies.  Used so far:

	d	desugarer
	f	AbsC flattener
	g	SimplStg
	l	ndpFlatten
	n	Native codegen
	r	Hsc name cache
	s	simplifier

\begin{code}
mkAlphaTyVarUnique i            = mkUnique '1' i

mkPreludeClassUnique i		= mkUnique '2' i

-- Prelude type constructors occupy *three* slots.
-- The first is for the tycon itself; the latter two
-- are for the generic to/from Ids.  See TysWiredIn.mk_tc_gen_info.

mkPreludeTyConUnique i		= mkUnique '3' (3*i)
mkTupleTyConUnique Boxed   a	= mkUnique '4' (3*a)
mkTupleTyConUnique Unboxed a	= mkUnique '5' (3*a)

-- Data constructor keys occupy *two* slots.  The first is used for the
-- data constructor itself and its wrapper function (the function that
-- evaluates arguments as necessary and calls the worker). The second is
-- used for the worker function (the function that builds the constructor
-- representation).

mkPreludeDataConUnique i	= mkUnique '6' (2*i)	-- Must be alphabetic
mkTupleDataConUnique Boxed a	= mkUnique '7' (2*a)	-- ditto (*may* be used in C labels)
mkTupleDataConUnique Unboxed a	= mkUnique '8' (2*a)

-- This one is used for a tiresome reason
-- to improve a consistency-checking error check in the renamer
isTupleKey u = case unpkUnique u of
		(tag,_) -> tag == '4' || tag == '5' || tag == '7' || tag == '8'

mkPrimOpIdUnique op		= mkUnique '9' op
mkPreludeMiscIdUnique i		= mkUnique '0' i

-- No numbers left anymore, so I pick something different for the character
-- tag 
mkPArrDataConUnique a	        = mkUnique ':' (2*a)

-- The "tyvar uniques" print specially nicely: a, b, c, etc.
-- See pprUnique for details

initTyVarUnique :: Unique
initTyVarUnique = mkUnique 't' 0

mkPseudoUniqueC, mkPseudoUniqueD, mkPseudoUniqueE, mkPseudoUniqueH,
   mkBuiltinUnique :: Int -> Unique

mkBuiltinUnique i = mkUnique 'B' i
mkPseudoUniqueC i = mkUnique 'C' i -- used for getUnique on Regs
mkPseudoUniqueD i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs
mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs
mkPseudoUniqueH i = mkUnique 'H' i -- used in NCG spiller to create spill VirtualRegs
\end{code}