ST monad and monad tranformers

Tyson Whitehead twhitehead at gmail.com
Mon Feb 2 11:26:02 EST 2009


I have a situation in which I believe I need a parameterizable version of the 
strict ST monad.  My computation type is "StateT s' (STT s (ErrorT e m)) a" 
(i.e., fails or succeeds and has an internal state involving a state thread).

The STT type above is a version of ST like the ReaderT, StateT, etc. types.

newtype STT s m a = STT ( State# s -> m (STTBox s a) )
data STTBox s a = STTBox {-#UNPACK#-} !(State# s) {-#UNPACK#-} !a

(I'm guessing on the UNPACK paragmas here) with

runSTT :: (Monad m) => (forall s. STT s m a) -> m a
runSTT m = case m of STT m' -> do STTBox _ x <- m' realWorld# 
                                  return x

(writing this as "runSTT (STT m') = ..." doesn't typecheck with ghc 6.8.2)

instance Monad m => Monad (STT s m) where
    return x = STT $ \s -> return $ STTBox s x
    (STT m) >>= k = STT $ \s -> do STTBox s' x <- m s
                                   case k x of STT k' -> k' s'

plus all the assorted instances for Functor, MonadPlus, MonadFix, MonadTrans, 
MonadReader, MonadState, etc.  For example,

instance MonadWriter w m => MonadWriter w (STT s m) where
    tell = lift . tell
    listen (STT m) = STT $ \s -> do (STTBox s' x,w) <- listen $ m s
                                    return $ STTBox s' (x,w)
    pass   (STT m) = STT $ \s -> pass $ do STTBox s' (x,f) <- m s
                                           return (STTBox s' x,f)

I was looking for any comments, wondering if there is a reason for this not 
existing in the library already, and what I should do in terms of paragmas and 
such for speed?  I see the GHC-ST file has a mix of INLINE and NOINLINE.

http://www.haskell.org/ghc/dist/current/docs/libraries/base/src/GHC-ST.html

In particular, return, >>=, >>, and runST are marked INLINE, but there is a 
"regrettably delicate" comment that goes with the runST method.  Also, what 
about the Functor, MonadPlus, MonadFix, MonadTrans, MonadReader, etc. methods?

Thanks! -Tyson

PS:  I would be happy to provide the whole works to be added to the library if 
it is something that should be there.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: This is a digitally signed message part.
Url : http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20090202/27f993d1/attachment.bin


More information about the Glasgow-haskell-users mailing list