[Haskell] ST vs State
David Menendez
zednenem at psualum.com
Thu May 31 00:54:40 EDT 2007
Federico Squartini writes:
> Hello dear Haskellers,
>
> Could someone be kind and explain with some detail what are the
> differences between the two monads:
>
> Control.Monad.ST
> And
> Control.Monad.State
> ?
>
> They are both meant to model stateful computation but they are not the
> same monad. The first one represents state with in place update?
Conceptually, the difference is in the API. State can be thought of as
an ST with a single, implicit reference cell. Alternately, ST can be
thought of as a State which manipulates a store of values.
Here's a simple implementation of State using ST:
newtype State s a = State
{ unState :: forall r. ReaderT (STRef r s) (ST r) a }
runState :: State s a -> s -> (a,s)
runState m s0 = runST (do
r <- newSTRef s0
a <- runReaderT (unState m) r
s <- readSTRef r
return (a,s))
instance Monad (State s) where
return a = State (return a)
m >>= f = State (unState m >>= unState . f)
instance MonadState s (State s) where
get = State (ask >>= lift . readSTRef)
put x = State (ask >>= \s -> lift (writeSTRef s x))
It's also possible to write ST in terms of State.
Assume we have a Store ADT with this interface:
data Store r
data STRef r a
withStore :: (forall r. Store r -> a) -> a
newRef :: a -> Store r -> (STRef r a, Store r)
readRef :: STRef r a -> Store r -> a
writeRef :: STRef r a -> a -> Store r -> Store r
(The 'r' parameter is to make sure that references are only used with
the Store that created them. The signature of withStore effectively
gives every Store a unique value for r.)
Then we can define ST like so:
newtype ST r a = ST { unST :: State (Store r) a } deriving Monad
runST :: (forall r. ST r a) -> a
runST m = withStore (evalState (unST m))
newSTRef :: a -> ST r (STRef r a)
newSTRef a = ST $ do
s <- get
let (r,s') = newRef a s
put s'
return r
readSTRef :: STRef r a -> ST r a
readSTRef r = ST $ gets (readRef r)
writeSTRef :: STRef r a -> a -> ST r ()
writeSTRef r a = ST $ modify (writeRef r a)
There are two subtleties. The first is that you can't implement Store
without cheating at some level (e.g., unsafeCoerce). The second is that
the real ST implementation uses in-place update, which is only safe
because the Store is implicit and used single-threadedly.
--
David Menendez <zednenem at psualum.com> | "In this house, we obey the laws
<http://www.eyrie.org/~zednenem> | of thermodynamics!"
More information about the Haskell
mailing list