[project @ 1996-03-19 08:58:34 by partain]
[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,
18
19         mkSplitUniqSupply,
20         splitUniqSupply,
21
22         -- and the access functions for the `builtin' UniqueSupply
23         getBuiltinUniques, mkBuiltinUnique,
24         mkPseudoUnique1, mkPseudoUnique2, mkPseudoUnique3
25   ) where
26
27 import Ubiq{-uitous-}
28
29 import Unique
30 import Util
31
32 import PreludeGlaST
33
34 w2i x = word2Int# x
35 i2w x = int2Word# x
36 i2w_s x = (x :: Int#)
37 \end{code}
38
39
40 %************************************************************************
41 %*                                                                      *
42 \subsection{Splittable Unique supply: @UniqSupply@}
43 %*                                                                      *
44 %************************************************************************
45
46 %************************************************************************
47 %*                                                                      *
48 \subsubsection[UniqSupply-type]{@UniqSupply@ type and operations}
49 %*                                                                      *
50 %************************************************************************
51
52 A value of type @UniqSupply@ is unique, and it can
53 supply {\em one} distinct @Unique@.  Also, from the supply, one can
54 also manufacture an arbitrary number of further @UniqueSupplies@,
55 which will be distinct from the first and from all others.
56
57 \begin{code}
58 data UniqSupply
59   = MkSplitUniqSupply Int       -- make the Unique with this
60                    UniqSupply UniqSupply
61                                 -- when split => these two supplies
62 \end{code}
63
64 \begin{code}
65 mkSplitUniqSupply :: Char -> PrimIO UniqSupply
66
67 splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply)
68 getUnique :: UniqSupply -> Unique
69 getUniques :: Int -> UniqSupply -> [Unique]
70 \end{code}
71
72 \begin{code}
73 mkSplitUniqSupply (MkChar c#)
74   = let
75         mask# = (i2w (ord# c#)) `shiftL#` (i2w_s 24#)
76
77         -- here comes THE MAGIC:
78
79         mk_supply#
80           = unsafe_interleave (
81                 mk_unique   `thenPrimIO` \ uniq ->
82                 mk_supply#  `thenPrimIO` \ s1 ->
83                 mk_supply#  `thenPrimIO` \ s2 ->
84                 returnPrimIO (MkSplitUniqSupply uniq s1 s2)
85             )
86           where
87             -- inlined copy of unsafeInterleavePrimIO;
88             -- this is the single-most-hammered bit of code
89             -- in the compiler....
90             unsafe_interleave m s
91               = let
92                     (r, new_s) = m s
93                 in
94                 (r, s)
95
96         mk_unique = _ccall_ genSymZh            `thenPrimIO` \ (W# u#) ->
97                     returnPrimIO (MkInt (w2i (mask# `or#` u#)))
98     in
99     mk_supply#
100
101 splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2)
102 \end{code}
103
104 \begin{code}
105 getUnique (MkSplitUniqSupply (MkInt n) _ _) = mkUniqueGrimily n
106
107 getUniques i@(MkInt i#) supply = i# `get_from` supply
108   where
109     get_from 0# _ = []
110     get_from n# (MkSplitUniqSupply (MkInt u#) _ s2)
111       = mkUniqueGrimily u# : get_from (n# `minusInt#` 1#) s2
112 \end{code}
113
114 %************************************************************************
115 %*                                                                      *
116 \subsubsection[UniqSupply-monad]{@UniqSupply@ monad: @UniqSM@}
117 %*                                                                      *
118 %************************************************************************
119
120 \begin{code}
121 type UniqSM result = UniqSupply -> result
122
123 -- the initUs function also returns the final UniqSupply
124
125 initUs :: UniqSupply -> UniqSM a -> (UniqSupply, a)
126
127 initUs init_us m
128   = case (splitUniqSupply init_us) of { (s1, s2) ->
129     (s2, m s1) }
130
131 {-# INLINE thenUs #-}
132 {-# INLINE returnUs #-}
133 {-# INLINE splitUniqSupply #-}
134 \end{code}
135
136 @thenUs@ is where we split the @UniqSupply@.
137 \begin{code}
138 thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
139
140 thenUs expr cont us
141   = case (splitUniqSupply us) of { (s1, s2) ->
142     case (expr s1)            of { result ->
143     cont result s2 }}
144 \end{code}
145
146 \begin{code}
147 returnUs :: a -> UniqSM a
148 returnUs result us = result
149
150 mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
151
152 mapUs f []     = returnUs []
153 mapUs f (x:xs)
154   = f x         `thenUs` \ r  ->
155     mapUs f xs  `thenUs` \ rs ->
156     returnUs (r:rs)
157
158 mapAndUnzipUs  :: (a -> UniqSM (b,c))   -> [a] -> UniqSM ([b],[c])
159
160 mapAndUnzipUs f [] = returnUs ([],[])
161 mapAndUnzipUs f (x:xs)
162   = f x                 `thenUs` \ (r1,  r2)  ->
163     mapAndUnzipUs f xs  `thenUs` \ (rs1, rs2) ->
164     returnUs (r1:rs1, r2:rs2)
165 \end{code}
166
167 %************************************************************************
168 %*                                                                      *
169 \subsubsection[UniqueSupplies-compiler]{@UniqueSupplies@ specific to the compiler}
170 %*                                                                      *
171 %************************************************************************
172
173 \begin{code}
174 mkPseudoUnique1, mkPseudoUnique2, mkPseudoUnique3,
175  mkBuiltinUnique :: Int -> Unique
176
177 mkBuiltinUnique i = mkUnique 'B' i
178 mkPseudoUnique1 i = mkUnique 'C' i -- used for getItsUnique on Regs
179 mkPseudoUnique2 i = mkUnique 'D' i -- ditto
180 mkPseudoUnique3 i = mkUnique 'E' i -- ditto
181
182 getBuiltinUniques :: Int -> [Unique]
183 getBuiltinUniques n = map (mkUnique 'B') [1 .. n]
184 \end{code}
185
186 The following runs a uniq monad expression, using builtin uniq values:
187 \begin{code}
188 --runBuiltinUs :: UniqSM a -> a
189 --runBuiltinUs m = snd (initUs uniqSupply_B m)
190 \end{code}