Added MonadUnique class for monads that have a unique supply
[ghc-hetmet.git] / compiler / basicTypes / UniqSupply.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 \begin{code}
7 {-# OPTIONS -w #-}
8 -- The above warning supression flag is a temporary kludge.
9 -- While working on this module you are encouraged to remove it and fix
10 -- any warnings in the module. See
11 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
12 -- for details
13
14 module UniqSupply (
15
16         UniqSupply,             -- Abstractly
17
18         uniqFromSupply, uniqsFromSupply,        -- basic ops
19
20         UniqSM,         -- type: unique supply monad
21         initUs, initUs_, thenUs, thenUs_, returnUs, fixUs, getUs, withUs,
22         getUniqueUs, getUniquesUs,
23         mapUs, mapAndUnzipUs, mapAndUnzip3Us,
24         thenMaybeUs, mapAccumLUs,
25         lazyThenUs, lazyMapUs,
26         module MonadUtils, mapAndUnzipM,
27         MonadUnique(..),
28
29         mkSplitUniqSupply,
30         splitUniqSupply, listSplitUniqSupply
31   ) where
32
33 #include "HsVersions.h"
34
35 import Unique
36 import FastTypes
37
38 #if __GLASGOW_HASKELL__ >= 607
39 import GHC.IOBase (unsafeDupableInterleaveIO)
40 #else
41 import System.IO.Unsafe ( unsafeInterleaveIO )
42 unsafeDupableInterleaveIO :: IO a -> IO a
43 unsafeDupableInterleaveIO = unsafeInterleaveIO
44 #endif
45
46 \end{code}
47
48
49 %************************************************************************
50 %*                                                                      *
51 \subsection{Splittable Unique supply: @UniqSupply@}
52 %*                                                                      *
53 %************************************************************************
54
55 A value of type @UniqSupply@ is unique, and it can
56 supply {\em one} distinct @Unique@.  Also, from the supply, one can
57 also manufacture an arbitrary number of further @UniqueSupplies@,
58 which will be distinct from the first and from all others.
59
60 \begin{code}
61 data UniqSupply
62   = MkSplitUniqSupply FastInt   -- make the Unique with this
63                    UniqSupply UniqSupply
64                                 -- when split => these two supplies
65 \end{code}
66
67 \begin{code}
68 mkSplitUniqSupply :: Char -> IO UniqSupply
69
70 splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply)
71 listSplitUniqSupply :: UniqSupply -> [UniqSupply]   -- Infinite
72 uniqFromSupply  :: UniqSupply -> Unique
73 uniqsFromSupply :: UniqSupply -> [Unique]       -- Infinite
74 \end{code}
75
76 \begin{code}
77 mkSplitUniqSupply c
78   = case fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24) of
79      mask -> let
80         -- here comes THE MAGIC:
81
82         -- This is one of the most hammered bits in the whole compiler
83         mk_supply
84           = unsafeDupableInterleaveIO (
85                 genSymZh    >>= \ u_ -> case iUnbox u_ of { u -> (
86                 mk_supply   >>= \ s1 ->
87                 mk_supply   >>= \ s2 ->
88                 return (MkSplitUniqSupply (mask `bitOrFastInt` u) s1 s2)
89             )})
90        in
91        mk_supply
92
93 foreign import ccall unsafe "genSymZh" genSymZh :: IO Int
94
95 splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2)
96 listSplitUniqSupply  (MkSplitUniqSupply _ s1 s2) = s1 : listSplitUniqSupply s2
97 \end{code}
98
99 \begin{code}
100 uniqFromSupply  (MkSplitUniqSupply n _ _)  = mkUniqueGrimily (iBox n)
101 uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily (iBox n) : uniqsFromSupply s2
102 \end{code}
103
104 %************************************************************************
105 %*                                                                      *
106 \subsubsection[UniqSupply-monad]{@UniqSupply@ monad: @UniqSM@}
107 %*                                                                      *
108 %************************************************************************
109
110 \begin{code}
111 newtype UniqSM result = USM { unUSM :: UniqSupply -> (result, UniqSupply) }
112
113 instance Monad UniqSM where
114   return = returnUs
115   (>>=) = thenUs
116   (>>)  = thenUs_
117
118 -- the initUs function also returns the final UniqSupply; initUs_ drops it
119 initUs :: UniqSupply -> UniqSM a -> (a,UniqSupply)
120 initUs init_us m = case unUSM m init_us of { (r,us) -> (r,us) }
121
122 initUs_ :: UniqSupply -> UniqSM a -> a
123 initUs_ init_us m = case unUSM m init_us of { (r,us) -> r }
124
125 {-# INLINE thenUs #-}
126 {-# INLINE lazyThenUs #-}
127 {-# INLINE returnUs #-}
128 {-# INLINE splitUniqSupply #-}
129 \end{code}
130
131 @thenUs@ is where we split the @UniqSupply@.
132 \begin{code}
133 fixUs :: (a -> UniqSM a) -> UniqSM a
134 fixUs m = USM (\us -> let (r,us') = unUSM (m r) us in (r,us'))
135
136 thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
137 thenUs (USM expr) cont
138   = USM (\us -> case (expr us) of 
139                    (result, us') -> unUSM (cont result) us')
140
141 lazyThenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
142 lazyThenUs (USM expr) cont
143   = USM (\us -> let (result, us') = expr us in unUSM (cont result) us')
144
145 thenUs_ :: UniqSM a -> UniqSM b -> UniqSM b
146 thenUs_ (USM expr) (USM cont)
147   = USM (\us -> case (expr us) of { (_, us') -> cont us' })
148
149
150 returnUs :: a -> UniqSM a
151 returnUs result = USM (\us -> (result, us))
152
153 withUs :: (UniqSupply -> (a, UniqSupply)) -> UniqSM a
154 withUs f = USM (\us -> f us)    -- Ha ha!
155                 
156 getUs :: UniqSM UniqSupply
157 getUs = USM (\us -> splitUniqSupply us)
158
159 -- | A monad for generating unique identifiers
160 class Monad m => MonadUnique m where
161     -- | Get a new UniqueSupply
162     getUniqueSupplyM :: m UniqSupply
163     -- | Get a new unique identifier
164     getUniqueM  :: m Unique
165     -- | Get an infinite list of new unique identifiers
166     getUniquesM :: m [Unique]
167     
168     getUniqueM  = liftM uniqFromSupply  getUniqueSupplyM
169     getUniquesM = liftM uniqsFromSupply getUniqueSupplyM
170
171 instance MonadUnique UniqSM where
172     getUniqueSupplyM = USM (\us -> splitUniqSupply us)
173     getUniqueM  = getUniqueUs
174     getUniquesM = getUniquesUs
175
176 getUniqueUs :: UniqSM Unique
177 getUniqueUs = USM (\us -> case splitUniqSupply us of
178                            (us1,us2) -> (uniqFromSupply us1, us2))
179
180 getUniquesUs :: UniqSM [Unique]
181 getUniquesUs = USM (\us -> case splitUniqSupply us of
182                               (us1,us2) -> (uniqsFromSupply us1, us2))
183 \end{code}
184
185 \begin{code}
186 mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
187 mapUs f []     = returnUs []
188 mapUs f (x:xs)
189   = f x         `thenUs` \ r  ->
190     mapUs f xs  `thenUs` \ rs ->
191     returnUs (r:rs)
192
193 lazyMapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
194 lazyMapUs f []     = returnUs []
195 lazyMapUs f (x:xs)
196   = f x             `lazyThenUs` \ r  ->
197     lazyMapUs f xs  `lazyThenUs` \ rs ->
198     returnUs (r:rs)
199
200 mapAndUnzipUs  :: (a -> UniqSM (b,c))   -> [a] -> UniqSM ([b],[c])
201 mapAndUnzip3Us :: (a -> UniqSM (b,c,d)) -> [a] -> UniqSM ([b],[c],[d])
202
203 mapAndUnzipUs f [] = returnUs ([],[])
204 mapAndUnzipUs f (x:xs)
205   = f x                 `thenUs` \ (r1,  r2)  ->
206     mapAndUnzipUs f xs  `thenUs` \ (rs1, rs2) ->
207     returnUs (r1:rs1, r2:rs2)
208
209 mapAndUnzip3Us f [] = returnUs ([],[],[])
210 mapAndUnzip3Us f (x:xs)
211   = f x                 `thenUs` \ (r1,  r2,  r3)  ->
212     mapAndUnzip3Us f xs `thenUs` \ (rs1, rs2, rs3) ->
213     returnUs (r1:rs1, r2:rs2, r3:rs3)
214
215 thenMaybeUs :: UniqSM (Maybe a) -> (a -> UniqSM (Maybe b)) -> UniqSM (Maybe b)
216 thenMaybeUs m k
217   = m   `thenUs` \ result ->
218     case result of
219       Nothing -> returnUs Nothing
220       Just x  -> k x
221
222 mapAccumLUs :: (acc -> x -> UniqSM (acc, y))
223             -> acc
224             -> [x]
225             -> UniqSM (acc, [y])
226
227 mapAccumLUs f b []     = returnUs (b, [])
228 mapAccumLUs f b (x:xs)
229   = f b x                           `thenUs` \ (b__2, x__2) ->
230     mapAccumLUs f b__2 xs           `thenUs` \ (b__3, xs__2) ->
231     returnUs (b__3, x__2:xs__2)
232 \end{code}