d9ae896f2b79efb030eb337b607781c9b7b300e4
[ghc-hetmet.git] / ghc / compiler / basicTypes / UniqSupply.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[UniqSupply]{The @UniqueSupply@ data type and a (monadic) supply thereof}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module UniqSupply (
10
11         UniqSupply,             -- Abstractly
12
13         getUnique, getUniques,  -- basic ops
14
15         UniqSM(..),             -- type: unique supply monad
16         initUs, thenUs, returnUs,
17         mapUs, mapAndUnzipUs, mapAndUnzip3Us,
18         thenMaybeUs, mapAccumLUs,
19
20         mkSplitUniqSupply,
21         splitUniqSupply,
22
23         -- and the access functions for the `builtin' UniqueSupply
24         getBuiltinUniques, mkBuiltinUnique,
25         mkPseudoUnique1, mkPseudoUnique2, mkPseudoUnique3
26   ) where
27
28 import Ubiq{-uitous-}
29
30 import Unique
31 import Util
32
33 import PreludeGlaST
34
35 w2i x = word2Int# x
36 i2w x = int2Word# x
37 i2w_s x = (x :: Int#)
38 \end{code}
39
40
41 %************************************************************************
42 %*                                                                      *
43 \subsection{Splittable Unique supply: @UniqSupply@}
44 %*                                                                      *
45 %************************************************************************
46
47 %************************************************************************
48 %*                                                                      *
49 \subsubsection[UniqSupply-type]{@UniqSupply@ type and operations}
50 %*                                                                      *
51 %************************************************************************
52
53 A value of type @UniqSupply@ is unique, and it can
54 supply {\em one} distinct @Unique@.  Also, from the supply, one can
55 also manufacture an arbitrary number of further @UniqueSupplies@,
56 which will be distinct from the first and from all others.
57
58 \begin{code}
59 data UniqSupply
60   = MkSplitUniqSupply Int       -- make the Unique with this
61                    UniqSupply UniqSupply
62                                 -- when split => these two supplies
63 \end{code}
64
65 \begin{code}
66 mkSplitUniqSupply :: Char -> IO UniqSupply
67
68 splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply)
69 getUnique :: UniqSupply -> Unique
70 getUniques :: Int -> UniqSupply -> [Unique]
71 \end{code}
72
73 \begin{code}
74 mkSplitUniqSupply (MkChar c#)
75   = let
76         mask# = (i2w (ord# c#)) `shiftL#` (i2w_s 24#)
77
78         -- here comes THE MAGIC:
79
80         mk_supply#
81           = unsafe_interleave (
82                 mk_unique   `thenPrimIO` \ uniq ->
83                 mk_supply#  `thenPrimIO` \ s1 ->
84                 mk_supply#  `thenPrimIO` \ s2 ->
85                 returnPrimIO (MkSplitUniqSupply uniq s1 s2)
86             )
87           where
88             -- inlined copy of unsafeInterleavePrimIO;
89             -- this is the single-most-hammered bit of code
90             -- in the compiler....
91             unsafe_interleave m s
92               = let
93                     (r, new_s) = m s
94                 in
95                 (r, s)
96
97         mk_unique = _ccall_ genSymZh            `thenPrimIO` \ (W# u#) ->
98                     returnPrimIO (MkInt (w2i (mask# `or#` u#)))
99     in
100     mk_supply#  `thenPrimIO` \ s ->
101     return s
102
103 splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2)
104 \end{code}
105
106 \begin{code}
107 getUnique (MkSplitUniqSupply (MkInt n) _ _) = mkUniqueGrimily n
108
109 getUniques i@(MkInt i#) supply = i# `get_from` supply
110   where
111     get_from 0# _ = []
112     get_from n# (MkSplitUniqSupply (MkInt u#) _ s2)
113       = mkUniqueGrimily u# : get_from (n# `minusInt#` 1#) s2
114 \end{code}
115
116 %************************************************************************
117 %*                                                                      *
118 \subsubsection[UniqSupply-monad]{@UniqSupply@ monad: @UniqSM@}
119 %*                                                                      *
120 %************************************************************************
121
122 \begin{code}
123 type UniqSM result = UniqSupply -> result
124
125 -- the initUs function also returns the final UniqSupply
126
127 initUs :: UniqSupply -> UniqSM a -> (UniqSupply, a)
128
129 initUs init_us m
130   = case (splitUniqSupply init_us) of { (s1, s2) ->
131     (s2, m s1) }
132
133 {-# INLINE thenUs #-}
134 {-# INLINE returnUs #-}
135 {-# INLINE splitUniqSupply #-}
136 \end{code}
137
138 @thenUs@ is where we split the @UniqSupply@.
139 \begin{code}
140 thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
141
142 thenUs expr cont us
143   = case (splitUniqSupply us) of { (s1, s2) ->
144     case (expr s1)            of { result ->
145     cont result s2 }}
146 \end{code}
147
148 \begin{code}
149 returnUs :: a -> UniqSM a
150 returnUs result us = result
151
152 mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
153
154 mapUs f []     = returnUs []
155 mapUs f (x:xs)
156   = f x         `thenUs` \ r  ->
157     mapUs f xs  `thenUs` \ rs ->
158     returnUs (r:rs)
159
160 mapAndUnzipUs  :: (a -> UniqSM (b,c))   -> [a] -> UniqSM ([b],[c])
161 mapAndUnzip3Us :: (a -> UniqSM (b,c,d)) -> [a] -> UniqSM ([b],[c],[d])
162
163 mapAndUnzipUs f [] = returnUs ([],[])
164 mapAndUnzipUs f (x:xs)
165   = f x                 `thenUs` \ (r1,  r2)  ->
166     mapAndUnzipUs f xs  `thenUs` \ (rs1, rs2) ->
167     returnUs (r1:rs1, r2:rs2)
168
169 mapAndUnzip3Us f [] = returnUs ([],[],[])
170 mapAndUnzip3Us f (x:xs)
171   = f x                 `thenUs` \ (r1,  r2,  r3)  ->
172     mapAndUnzip3Us f xs `thenUs` \ (rs1, rs2, rs3) ->
173     returnUs (r1:rs1, r2:rs2, r3:rs3)
174
175 thenMaybeUs :: UniqSM (Maybe a) -> (a -> UniqSM (Maybe b)) -> UniqSM (Maybe b)
176 thenMaybeUs m k
177   = m   `thenUs` \ result ->
178     case result of
179       Nothing -> returnUs Nothing
180       Just x  -> k x
181
182 mapAccumLUs :: (acc -> x -> UniqSM (acc, y))
183             -> acc
184             -> [x]
185             -> UniqSM (acc, [y])
186
187 mapAccumLUs f b []     = returnUs (b, [])
188 mapAccumLUs f b (x:xs)
189   = f b x                           `thenUs` \ (b__2, x__2) ->
190     mapAccumLUs f b__2 xs           `thenUs` \ (b__3, xs__2) ->
191     returnUs (b__3, x__2:xs__2)
192 \end{code}
193
194 %************************************************************************
195 %*                                                                      *
196 \subsubsection[UniqueSupplies-compiler]{@UniqueSupplies@ specific to the compiler}
197 %*                                                                      *
198 %************************************************************************
199
200 \begin{code}
201 mkPseudoUnique1, mkPseudoUnique2, mkPseudoUnique3,
202  mkBuiltinUnique :: Int -> Unique
203
204 mkBuiltinUnique i = mkUnique 'B' i
205 mkPseudoUnique1 i = mkUnique 'C' i -- used for uniqueOf on Regs
206 mkPseudoUnique2 i = mkUnique 'D' i -- ditto
207 mkPseudoUnique3 i = mkUnique 'E' i -- ditto
208
209 getBuiltinUniques :: Int -> [Unique]
210 getBuiltinUniques n = map (mkUnique 'B') [1 .. n]
211 \end{code}
212
213 The following runs a uniq monad expression, using builtin uniq values:
214 \begin{code}
215 --runBuiltinUs :: UniqSM a -> a
216 --runBuiltinUs m = snd (initUs uniqSupply_B m)
217 \end{code}