657752ec9fd30cce5d7d0c4db336dcfc4b2deada
[ghc-base.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 -- except that the monad delays evaluation of state operations until
13 -- a value depending on them is required.
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 qualified Control.Monad.ST as ST
40
41 #ifdef __GLASGOW_HASKELL__
42 import qualified GHC.ST
43 import GHC.Base
44 #endif
45
46 #ifdef __HUGS__
47 import Hugs.LazyST
48 #endif
49
50 #ifdef __GLASGOW_HASKELL__
51 -- | The lazy state-transformer monad.
52 -- A computation of type @'ST' s a@ transforms an internal state indexed
53 -- by @s@, and returns a value of type @a@.
54 -- The @s@ parameter is either
55 --
56 -- * an unstantiated type variable (inside invocations of 'runST'), or
57 --
58 -- * 'RealWorld' (inside invocations of 'stToIO').
59 --
60 -- It serves to keep the internal states of different invocations of
61 -- 'runST' separate from each other and from invocations of 'stToIO'.
62 --
63 -- The '>>=' and '>>' operations are not strict in the state.  For example,
64 --
65 -- @'runST' (writeSTRef _|_ v >>= readSTRef _|_ >> return 2) = 2@
66 newtype ST s a = ST (State s -> (a, State s))
67 data State s = S# (State# s)
68
69 instance Functor (ST s) where
70     fmap f m = ST $ \ s ->
71       let 
72        ST m_a = m
73        (r,new_s) = m_a s
74       in
75       (f r,new_s)
76
77 instance Monad (ST s) where
78
79         return a = ST $ \ s -> (a,s)
80         m >> k   =  m >>= \ _ -> k
81         fail s   = error s
82
83         (ST m) >>= k
84          = ST $ \ s ->
85            let
86              (r,new_s) = m s
87              ST k_a = k r
88            in
89            k_a new_s
90
91 {-# NOINLINE runST #-}
92 -- | Return the value computed by a state transformer computation.
93 -- The @forall@ ensures that the internal state used by the 'ST'
94 -- computation is inaccessible to the rest of the program.
95 runST :: (forall s. ST s a) -> a
96 runST st = case st of ST the_st -> let (r,_) = the_st (S# realWorld#) in r
97
98 -- | Allow the result of a state transformer computation to be used (lazily)
99 -- inside the computation.
100 -- Note that if @f@ is strict, @'fixST' f = _|_@.
101 fixST :: (a -> ST s a) -> ST s a
102 fixST m = ST (\ s -> 
103                 let 
104                    ST m_r = m r
105                    (r,s') = m_r s
106                 in
107                    (r,s'))
108 #endif
109
110 instance MonadFix (ST s) where
111         mfix = fixST
112
113 -- ---------------------------------------------------------------------------
114 -- Strict <--> Lazy
115
116 #ifdef __GLASGOW_HASKELL__
117 {-|
118 Convert a strict 'ST' computation into a lazy one.  The strict state
119 thread passed to 'strictToLazyST' is not performed until the result of
120 the lazy state thread it returns is demanded.
121 -}
122 strictToLazyST :: ST.ST s a -> ST s a
123 strictToLazyST m = ST $ \s ->
124         let 
125            pr = case s of { S# s# -> GHC.ST.liftST m s# }
126            r  = case pr of { GHC.ST.STret _ v -> v }
127            s' = case pr of { GHC.ST.STret s2# _ -> S# s2# }
128         in
129         (r, s')
130
131 {-| 
132 Convert a lazy 'ST' computation into a strict one.
133 -}
134 lazyToStrictST :: ST s a -> ST.ST s a
135 lazyToStrictST (ST m) = GHC.ST.ST $ \s ->
136         case (m (S# s)) of (a, S# s') -> (# s', a #)
137
138 unsafeInterleaveST :: ST s a -> ST s a
139 unsafeInterleaveST = strictToLazyST . ST.unsafeInterleaveST . lazyToStrictST
140 #endif
141
142 unsafeIOToST :: IO a -> ST s a
143 unsafeIOToST = strictToLazyST . ST.unsafeIOToST
144
145 -- | A monad transformer embedding lazy state transformers in the 'IO'
146 -- monad.  The 'RealWorld' parameter indicates that the internal state
147 -- used by the 'ST' computation is a special one supplied by the 'IO'
148 -- monad, and thus distinct from those used by invocations of 'runST'.
149 stToIO :: ST RealWorld a -> IO a
150 stToIO = ST.stToIO . lazyToStrictST