Properly comment out unused pragmas
[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
9         UniqSupply, -- Abstractly
10
11         uniqFromSupply, uniqsFromSupply, -- basic ops
12
13         UniqSM, -- type: unique supply monad
14         initUs, initUs_,
15         lazyThenUs, lazyMapUs,
16         mapAndUnzipM,
17         MonadUnique(..),
18
19         mkSplitUniqSupply,
20         splitUniqSupply, listSplitUniqSupply,
21
22         -- Deprecated:
23         getUniqueUs, getUs, returnUs, thenUs, mapUs
24   ) where
25
26 import Unique
27 import FastTypes
28
29 import MonadUtils
30 import Control.Monad
31 import Control.Monad.Fix
32 #if __GLASGOW_HASKELL__ >= 607
33 import GHC.IOBase (unsafeDupableInterleaveIO)
34 #else
35 import System.IO.Unsafe ( unsafeInterleaveIO )
36 unsafeDupableInterleaveIO :: IO a -> IO a
37 unsafeDupableInterleaveIO = unsafeInterleaveIO
38 #endif
39
40 \end{code}
41
42
43 %************************************************************************
44 %*                                                                      *
45 \subsection{Splittable Unique supply: @UniqSupply@}
46 %*                                                                      *
47 %************************************************************************
48
49 A value of type @UniqSupply@ is unique, and it can
50 supply {\em one} distinct @Unique@.  Also, from the supply, one can
51 also manufacture an arbitrary number of further @UniqueSupplies@,
52 which will be distinct from the first and from all others.
53
54 \begin{code}
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
64 splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply)
65 listSplitUniqSupply :: UniqSupply -> [UniqSupply] -- Infinite
66 uniqFromSupply  :: UniqSupply -> Unique
67 uniqsFromSupply :: UniqSupply -> [Unique] -- Infinite
68 \end{code}
69
70 \begin{code}
71 mkSplitUniqSupply c
72   = case fastOrd (cUnbox c) `shiftLFastInt` _ILIT(24) of
73      mask -> let
74         -- here comes THE MAGIC:
75
76         -- This is one of the most hammered bits in the whole compiler
77         mk_supply
78           = unsafeDupableInterleaveIO (
79                 genSymZh    >>= \ u_ -> case iUnbox u_ of { u -> (
80                 mk_supply   >>= \ s1 ->
81                 mk_supply   >>= \ s2 ->
82                 return (MkSplitUniqSupply (mask `bitOrFastInt` u) s1 s2)
83             )})
84        in
85        mk_supply
86
87 foreign import ccall unsafe "genSymZh" genSymZh :: IO Int
88
89 splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2)
90 listSplitUniqSupply  (MkSplitUniqSupply _ s1 s2) = s1 : listSplitUniqSupply s2
91 \end{code}
92
93 \begin{code}
94 uniqFromSupply  (MkSplitUniqSupply n _ _)  = mkUniqueGrimily (iBox n)
95 uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily (iBox n) : uniqsFromSupply s2
96 \end{code}
97
98 %************************************************************************
99 %*                                                                      *
100 \subsubsection[UniqSupply-monad]{@UniqSupply@ monad: @UniqSM@}
101 %*                                                                      *
102 %************************************************************************
103
104 \begin{code}
105 newtype UniqSM result = USM { unUSM :: UniqSupply -> (result, UniqSupply) }
106
107 instance Monad UniqSM where
108   return = returnUs
109   (>>=) = thenUs
110   (>>)  = thenUs_
111
112 instance Functor UniqSM where
113     fmap f (USM x) = USM (\us -> case x us of
114                                  (r, us') -> (f r, us'))
115
116 instance Applicative UniqSM where
117     pure = returnUs
118     (USM f) <*> (USM x) = USM $ \us -> case f us of
119                             (ff, us')  -> case x us' of
120                               (xx, us'') -> (ff xx, us'')
121
122 -- the initUs function also returns the final UniqSupply; initUs_ drops it
123 initUs :: UniqSupply -> UniqSM a -> (a,UniqSupply)
124 initUs init_us m = case unUSM m init_us of { (r,us) -> (r,us) }
125
126 initUs_ :: UniqSupply -> UniqSM a -> a
127 initUs_ init_us m = case unUSM m init_us of { (r, _) -> r }
128
129 {-# INLINE thenUs #-}
130 {-# INLINE lazyThenUs #-}
131 {-# INLINE returnUs #-}
132 {-# INLINE splitUniqSupply #-}
133 \end{code}
134
135 @thenUs@ is where we split the @UniqSupply@.
136 \begin{code}
137 instance MonadFix UniqSM where
138     mfix m = USM (\us -> let (r,us') = unUSM (m r) us in (r,us'))
139
140 thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
141 thenUs (USM expr) cont
142   = USM (\us -> case (expr us) of
143                    (result, us') -> unUSM (cont result) us')
144
145 lazyThenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b
146 lazyThenUs (USM expr) cont
147   = USM (\us -> let (result, us') = expr us in unUSM (cont result) us')
148
149 thenUs_ :: UniqSM a -> UniqSM b -> UniqSM b
150 thenUs_ (USM expr) (USM cont)
151   = USM (\us -> case (expr us) of { (_, us') -> cont us' })
152
153 returnUs :: a -> UniqSM a
154 returnUs result = USM (\us -> (result, us))
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
184 mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
185 mapUs _ []     = returnUs []
186 mapUs f (x:xs)
187   = f x         `thenUs` \ r  ->
188     mapUs f xs  `thenUs` \ rs ->
189     returnUs (r:rs)
190 \end{code}
191
192 \begin{code}
193 -- {-# SPECIALIZE mapM          :: (a -> UniqSM b) -> [a] -> UniqSM [b] #-}
194 -- {-# SPECIALIZE mapAndUnzipM  :: (a -> UniqSM (b,c))   -> [a] -> UniqSM ([b],[c]) #-}
195 -- {-# SPECIALIZE mapAndUnzip3M :: (a -> UniqSM (b,c,d)) -> [a] -> UniqSM ([b],[c],[d]) #-}
196
197 lazyMapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
198 lazyMapUs _ []     = returnUs []
199 lazyMapUs f (x:xs)
200   = f x             `lazyThenUs` \ r  ->
201     lazyMapUs f xs  `lazyThenUs` \ rs ->
202     returnUs (r:rs)
203 \end{code}