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