a4c16fdc05180d5376cf5fa4b3564571bccf3e4c
[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 module UniqSupply (
8         -- * Main data type
9         UniqSupply, -- Abstractly
10
11         -- ** Operations on supplies
12         uniqFromSupply, uniqsFromSupply, -- basic ops
13         takeUniqFromSupply,
14
15         mkSplitUniqSupply,
16         splitUniqSupply, listSplitUniqSupply,
17
18         -- * Unique supply monad and its abstraction
19         UniqSM, MonadUnique(..),
20
21         -- ** Operations on the monad
22         initUs, initUs_,
23         lazyThenUs, lazyMapUs,
24
25         -- ** Deprecated operations on 'UniqSM'
26         getUniqueUs, getUs, returnUs, thenUs, mapUs
27   ) where
28
29 import Unique
30 import FastTypes
31
32 import MonadUtils
33 import Control.Monad
34 #if __GLASGOW_HASKELL__ >= 611
35 import GHC.IO (unsafeDupableInterleaveIO)
36 #else
37 import GHC.IOBase (unsafeDupableInterleaveIO)
38 #endif
39
40 \end{code}
41
42 %************************************************************************
43 %*                                                                      *
44 \subsection{Splittable Unique supply: @UniqSupply@}
45 %*                                                                      *
46 %************************************************************************
47
48 \begin{code}
49 -- | A value of type 'UniqSupply' is unique, and it can
50 -- supply /one/ distinct 'Unique'.  Also, from the supply, one can
51 -- also manufacture an arbitrary number of further 'UniqueSupply' values,
52 -- which will be distinct from the first and from all others.
53 data UniqSupply
54   = MkSplitUniqSupply FastInt   -- make the Unique with this
55                    UniqSupply UniqSupply
56                                 -- when split => these two supplies
57 \end{code}
58
59 \begin{code}
60 mkSplitUniqSupply :: Char -> IO UniqSupply
61 -- ^ Create a unique supply out of thin air. The character given must
62 -- be distinct from those of all calls to this function in the compiler
63 -- for the values generated to be truly unique.
64
65 splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply)
66 -- ^ Build two 'UniqSupply' from a single one, each of which
67 -- can supply its own 'Unique'.
68 listSplitUniqSupply :: UniqSupply -> [UniqSupply]
69 -- ^ Create an infinite list of 'UniqSupply' from a single one
70 uniqFromSupply  :: UniqSupply -> Unique
71 -- ^ Obtain the 'Unique' from this particular 'UniqSupply'
72 uniqsFromSupply :: UniqSupply -> [Unique] -- Infinite
73 -- ^ Obtain an infinite list of 'Unique' that can be generated by constant splitting of the supply
74 takeUniqFromSupply :: UniqSupply -> (Unique, UniqSupply)
75 -- ^ Obtain the 'Unique' from this particular 'UniqSupply', and a new supply
76 \end{code}
77
78 \begin{code}
79 mkSplitUniqSupply c
80   = case fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24) of
81      mask -> let
82         -- here comes THE MAGIC:
83
84         -- This is one of the most hammered bits in the whole compiler
85         mk_supply
86           = unsafeDupableInterleaveIO (
87                 genSymZh    >>= \ u_ -> case iUnbox u_ of { u -> (
88                 mk_supply   >>= \ s1 ->
89                 mk_supply   >>= \ s2 ->
90                 return (MkSplitUniqSupply (mask `bitOrFastInt` u) s1 s2)
91             )})
92        in
93        mk_supply
94
95 foreign import ccall unsafe "genSymZh" genSymZh :: IO Int
96
97 splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2)
98 listSplitUniqSupply  (MkSplitUniqSupply _ s1 s2) = s1 : listSplitUniqSupply s2
99 \end{code}
100
101 \begin{code}
102 uniqFromSupply  (MkSplitUniqSupply n _ _)  = mkUniqueGrimily (iBox n)
103 uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily (iBox n) : uniqsFromSupply s2
104 takeUniqFromSupply (MkSplitUniqSupply n s1 _) = (mkUniqueGrimily (iBox n), s1)
105 \end{code}
106
107 %************************************************************************
108 %*                                                                      *
109 \subsubsection[UniqSupply-monad]{@UniqSupply@ monad: @UniqSM@}
110 %*                                                                      *
111 %************************************************************************
112
113 \begin{code}
114 -- | A monad which just gives the ability to obtain 'Unique's
115 newtype UniqSM result = USM { unUSM :: UniqSupply -> (result, UniqSupply) }
116
117 instance Monad UniqSM where
118   return = returnUs
119   (>>=) = thenUs
120   (>>)  = thenUs_
121
122 instance Functor UniqSM where
123     fmap f (USM x) = USM (\us -> case x us of
124                                  (r, us') -> (f r, us'))
125
126 instance Applicative UniqSM where
127     pure = returnUs
128     (USM f) <*> (USM x) = USM $ \us -> case f us of
129                             (ff, us')  -> case x us' of
130                               (xx, us'') -> (ff xx, us'')
131
132 -- | Run the 'UniqSM' action, returning the final 'UniqSupply'
133 initUs :: UniqSupply -> UniqSM a -> (a, UniqSupply)
134 initUs init_us m = case unUSM m init_us of { (r,us) -> (r,us) }
135
136 -- | Run the 'UniqSM' action, discarding the final 'UniqSupply'
137 initUs_ :: UniqSupply -> UniqSM a -> a
138 initUs_ init_us m = case unUSM m init_us of { (r, _) -> r }
139
140 {-# INLINE thenUs #-}
141 {-# INLINE lazyThenUs #-}
142 {-# INLINE returnUs #-}
143 {-# INLINE splitUniqSupply #-}
144 \end{code}
145
146 @thenUs@ is where we split the @UniqSupply@.
147 \begin{code}
148 instance MonadFix UniqSM where
149     mfix m = USM (\us -> let (r,us') = unUSM (m r) us in (r,us'))
150
151 thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
152 thenUs (USM expr) cont
153   = USM (\us -> case (expr us) of
154                    (result, us') -> unUSM (cont result) us')
155
156 lazyThenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
157 lazyThenUs (USM expr) cont
158   = USM (\us -> let (result, us') = expr us in unUSM (cont result) us')
159
160 thenUs_ :: UniqSM a -> UniqSM b -> UniqSM b
161 thenUs_ (USM expr) (USM cont)
162   = USM (\us -> case (expr us) of { (_, us') -> cont us' })
163
164 returnUs :: a -> UniqSM a
165 returnUs result = USM (\us -> (result, us))
166
167 getUs :: UniqSM UniqSupply
168 getUs = USM (\us -> splitUniqSupply us)
169
170 -- | A monad for generating unique identifiers
171 class Monad m => MonadUnique m where
172     -- | Get a new UniqueSupply
173     getUniqueSupplyM :: m UniqSupply
174     -- | Get a new unique identifier
175     getUniqueM  :: m Unique
176     -- | Get an infinite list of new unique identifiers
177     getUniquesM :: m [Unique]
178
179     getUniqueM  = liftM uniqFromSupply  getUniqueSupplyM
180     getUniquesM = liftM uniqsFromSupply getUniqueSupplyM
181
182 instance MonadUnique UniqSM where
183     getUniqueSupplyM = USM (\us -> splitUniqSupply us)
184     getUniqueM  = getUniqueUs
185     getUniquesM = getUniquesUs
186
187 getUniqueUs :: UniqSM Unique
188 getUniqueUs = USM (\us -> case splitUniqSupply us of
189                           (us1,us2) -> (uniqFromSupply us1, us2))
190
191 getUniquesUs :: UniqSM [Unique]
192 getUniquesUs = USM (\us -> case splitUniqSupply us of
193                            (us1,us2) -> (uniqsFromSupply us1, us2))
194
195 mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
196 mapUs _ []     = returnUs []
197 mapUs f (x:xs)
198   = f x         `thenUs` \ r  ->
199     mapUs f xs  `thenUs` \ rs ->
200     returnUs (r:rs)
201 \end{code}
202
203 \begin{code}
204 -- {-# SPECIALIZE mapM          :: (a -> UniqSM b) -> [a] -> UniqSM [b] #-}
205 -- {-# SPECIALIZE mapAndUnzipM  :: (a -> UniqSM (b,c))   -> [a] -> UniqSM ([b],[c]) #-}
206 -- {-# SPECIALIZE mapAndUnzip3M :: (a -> UniqSM (b,c,d)) -> [a] -> UniqSM ([b],[c],[d]) #-}
207
208 lazyMapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
209 lazyMapUs _ []     = returnUs []
210 lazyMapUs f (x:xs)
211   = f x             `lazyThenUs` \ r  ->
212     lazyMapUs f xs  `lazyThenUs` \ rs ->
213     returnUs (r:rs)
214 \end{code}