[project @ 2003-09-05 17:36:40 by ross]
[haskell-directory.git] / Control / Monad / ST / Lazy.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Monad.ST.Lazy
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  provisional
9 -- Portability :  non-portable (requires universal quantification for runST)
10 --
11 -- This module presents an identical interface to "Control.Monad.ST",
12 -- but the underlying implementation of the state thread is /lazy/ (in
13 -- the sense that (@_|_ >> a@ is not necessarily equal to @_|_@).
14 --
15 -----------------------------------------------------------------------------
16
17 module Control.Monad.ST.Lazy (
18         -- * The 'ST' monad
19         ST,
20         runST,
21         fixST,
22
23         -- * Converting between strict and lazy 'ST'
24         strictToLazyST, lazyToStrictST,
25
26         -- * Converting 'ST' To 'IO'
27         RealWorld,
28         stToIO,
29
30         -- * Unsafe operations
31         unsafeInterleaveST,
32         unsafeIOToST
33     ) where
34
35 import Prelude
36
37 import Control.Monad.Fix
38
39 import Control.Monad.ST (RealWorld)
40 import qualified Control.Monad.ST as ST
41
42 #ifdef __GLASGOW_HASKELL__
43 import qualified GHC.ST
44 import GHC.Base
45 import Control.Monad
46 #endif
47
48 #ifdef __HUGS__
49 import Hugs.LazyST
50 #endif
51
52 #ifdef __GLASGOW_HASKELL__
53 -- | The lazy state-transformer monad.
54 -- The first parameter is used solely to keep the states of different
55 -- invocations of 'runST' separate from each other and from invocations
56 -- of 'Control.Monad.ST.stToIO'.  In the first case the type parameter
57 -- is not instantiated; in the second it is 'RealWorld'.
58 newtype ST s a = ST (State s -> (a, State s))
59 data State s = S# (State# s)
60
61 instance Functor (ST s) where
62     fmap f m = ST $ \ s ->
63       let 
64        ST m_a = m
65        (r,new_s) = m_a s
66       in
67       (f r,new_s)
68
69 instance Monad (ST s) where
70
71         return a = ST $ \ s -> (a,s)
72         m >> k   =  m >>= \ _ -> k
73         fail s   = error s
74
75         (ST m) >>= k
76          = ST $ \ s ->
77            let
78              (r,new_s) = m s
79              ST k_a = k r
80            in
81            k_a new_s
82
83 {-# NOINLINE runST #-}
84 -- | Return the value computed by a state transformer computation.
85 -- The @forall@ is a technical device to ensure that the state used
86 -- by the 'ST' computation is inaccessible to the rest of the program.
87 runST :: (forall s. ST s a) -> a
88 runST st = case st of ST the_st -> let (r,_) = the_st (S# realWorld#) in r
89
90 -- | Allow the result of a state transformer computation to be used (lazily)
91 -- inside the computation.
92 -- Note that if @f@ is strict, @'fixST' f@ will diverge.
93 fixST :: (a -> ST s a) -> ST s a
94 fixST m = ST (\ s -> 
95                 let 
96                    ST m_r = m r
97                    (r,s') = m_r s
98                 in
99                    (r,s'))
100 #endif
101
102 instance MonadFix (ST s) where
103         mfix = fixST
104
105 -- ---------------------------------------------------------------------------
106 -- Strict <--> Lazy
107
108 #ifdef __GLASGOW_HASKELL__
109 {-|
110 Convert a strict 'ST' computation into a lazy one.  The strict state
111 thread passed to 'strictToLazyST' is not performed until the result of
112 the lazy state thread it returns is demanded.
113 -}
114 strictToLazyST :: ST.ST s a -> ST s a
115 strictToLazyST m = ST $ \s ->
116         let 
117            pr = case s of { S# s# -> GHC.ST.liftST m s# }
118            r  = case pr of { GHC.ST.STret _ v -> v }
119            s' = case pr of { GHC.ST.STret s2# _ -> S# s2# }
120         in
121         (r, s')
122
123 {-| 
124 Convert a lazy 'ST' computation into a strict one.
125 -}
126 lazyToStrictST :: ST s a -> ST.ST s a
127 lazyToStrictST (ST m) = GHC.ST.ST $ \s ->
128         case (m (S# s)) of (a, S# s') -> (# s', a #)
129
130 unsafeInterleaveST :: ST s a -> ST s a
131 unsafeInterleaveST = strictToLazyST . ST.unsafeInterleaveST . lazyToStrictST
132 #endif
133
134 unsafeIOToST :: IO a -> ST s a
135 unsafeIOToST = strictToLazyST . ST.unsafeIOToST
136
137 -- | A monad transformer embedding lazy state transformers in the 'IO'
138 -- monad.  The 'RealWorld' parameter is a technical device to keep the
139 -- state used by such computations separate from those inside 'runST'.
140 stToIO :: ST RealWorld a -> IO a
141 stToIO = ST.stToIO . lazyToStrictST