Remove unused custom versions of monad combinators from UniqSupply
[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_,
22         lazyThenUs, lazyMapUs,
23         module MonadUtils, mapAndUnzipM,
24         MonadUnique(..),
25
26         mkSplitUniqSupply,
27         splitUniqSupply, listSplitUniqSupply
28   ) where
29
30 #include "HsVersions.h"
31
32 import Unique
33 import FastTypes
34
35 #if __GLASGOW_HASKELL__ >= 607
36 import GHC.IOBase (unsafeDupableInterleaveIO)
37 #else
38 import System.IO.Unsafe ( unsafeInterleaveIO )
39 unsafeDupableInterleaveIO :: IO a -> IO a
40 unsafeDupableInterleaveIO = unsafeInterleaveIO
41 #endif
42
43 \end{code}
44
45
46 %************************************************************************
47 %*                                                                      *
48 \subsection{Splittable Unique supply: @UniqSupply@}
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 FastInt   -- make the Unique with this
60                    UniqSupply UniqSupply
61                                 -- when split => these two supplies
62 \end{code}
63
64 \begin{code}
65 mkSplitUniqSupply :: Char -> IO UniqSupply
66
67 splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply)
68 listSplitUniqSupply :: UniqSupply -> [UniqSupply]   -- Infinite
69 uniqFromSupply  :: UniqSupply -> Unique
70 uniqsFromSupply :: UniqSupply -> [Unique]       -- Infinite
71 \end{code}
72
73 \begin{code}
74 mkSplitUniqSupply c
75   = case fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24) of
76      mask -> let
77         -- here comes THE MAGIC:
78
79         -- This is one of the most hammered bits in the whole compiler
80         mk_supply
81           = unsafeDupableInterleaveIO (
82                 genSymZh    >>= \ u_ -> case iUnbox u_ of { u -> (
83                 mk_supply   >>= \ s1 ->
84                 mk_supply   >>= \ s2 ->
85                 return (MkSplitUniqSupply (mask `bitOrFastInt` u) s1 s2)
86             )})
87        in
88        mk_supply
89
90 foreign import ccall unsafe "genSymZh" genSymZh :: IO Int
91
92 splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2)
93 listSplitUniqSupply  (MkSplitUniqSupply _ s1 s2) = s1 : listSplitUniqSupply s2
94 \end{code}
95
96 \begin{code}
97 uniqFromSupply  (MkSplitUniqSupply n _ _)  = mkUniqueGrimily (iBox n)
98 uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily (iBox n) : uniqsFromSupply s2
99 \end{code}
100
101 %************************************************************************
102 %*                                                                      *
103 \subsubsection[UniqSupply-monad]{@UniqSupply@ monad: @UniqSM@}
104 %*                                                                      *
105 %************************************************************************
106
107 \begin{code}
108 newtype UniqSM result = USM { unUSM :: UniqSupply -> (result, UniqSupply) }
109
110 instance Monad UniqSM where
111   return = returnUs
112   (>>=) = thenUs
113   (>>)  = thenUs_
114
115 -- the initUs function also returns the final UniqSupply; initUs_ drops it
116 initUs :: UniqSupply -> UniqSM a -> (a,UniqSupply)
117 initUs init_us m = case unUSM m init_us of { (r,us) -> (r,us) }
118
119 initUs_ :: UniqSupply -> UniqSM a -> a
120 initUs_ init_us m = case unUSM m init_us of { (r,us) -> r }
121
122 {-# INLINE thenUs #-}
123 {-# INLINE lazyThenUs #-}
124 {-# INLINE returnUs #-}
125 {-# INLINE splitUniqSupply #-}
126 \end{code}
127
128 @thenUs@ is where we split the @UniqSupply@.
129 \begin{code}
130 instance MonadFix UniqSM where
131     mfix m = USM (\us -> let (r,us') = unUSM (m r) us in (r,us'))
132
133 thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
134 thenUs (USM expr) cont
135   = USM (\us -> case (expr us) of 
136                    (result, us') -> unUSM (cont result) us')
137
138 lazyThenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
139 lazyThenUs (USM expr) cont
140   = USM (\us -> let (result, us') = expr us in unUSM (cont result) us')
141
142 thenUs_ :: UniqSM a -> UniqSM b -> UniqSM b
143 thenUs_ (USM expr) (USM cont)
144   = USM (\us -> case (expr us) of { (_, us') -> cont us' })
145
146 returnUs :: a -> UniqSM a
147 returnUs result = USM (\us -> (result, us))
148
149 withUs :: (UniqSupply -> (a, UniqSupply)) -> UniqSM a
150 withUs f = USM (\us -> f us)    -- Ha ha!
151                 
152 getUs :: UniqSM UniqSupply
153 getUs = USM (\us -> splitUniqSupply us)
154
155 -- | A monad for generating unique identifiers
156 class Monad m => MonadUnique m where
157     -- | Get a new UniqueSupply
158     getUniqueSupplyM :: m UniqSupply
159     -- | Get a new unique identifier
160     getUniqueM  :: m Unique
161     -- | Get an infinite list of new unique identifiers
162     getUniquesM :: m [Unique]
163     
164     getUniqueM  = liftM uniqFromSupply  getUniqueSupplyM
165     getUniquesM = liftM uniqsFromSupply getUniqueSupplyM
166
167 instance MonadUnique UniqSM where
168     getUniqueSupplyM = USM (\us -> splitUniqSupply us)
169     getUniqueM  = getUniqueUs
170     getUniquesM = getUniquesUs
171
172 getUniqueUs :: UniqSM Unique
173 getUniqueUs = USM (\us -> case splitUniqSupply us of
174                            (us1,us2) -> (uniqFromSupply us1, us2))
175
176 getUniquesUs :: UniqSM [Unique]
177 getUniquesUs = USM (\us -> case splitUniqSupply us of
178                               (us1,us2) -> (uniqsFromSupply us1, us2))
179 \end{code}
180
181 \begin{code}
182 {-# -- SPECIALIZE mapM          :: (a -> UniqSM b) -> [a] -> UniqSM [b] #-}
183 {-# -- SPECIALIZE mapAndUnzipM  :: (a -> UniqSM (b,c))   -> [a] -> UniqSM ([b],[c]) #-}
184 {-# -- SPECIALIZE mapAndUnzip3M :: (a -> UniqSM (b,c,d)) -> [a] -> UniqSM ([b],[c],[d]) #-}
185
186 lazyMapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
187 lazyMapUs f []     = returnUs []
188 lazyMapUs f (x:xs)
189   = f x             `lazyThenUs` \ r  ->
190     lazyMapUs f xs  `lazyThenUs` \ rs ->
191     returnUs (r:rs)
192
193 \end{code}