ST monad and monad tranformers

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.

Hi Tyson,
I also needed something like this a while ago so I knocked up a really
simple module and put it on hackage:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans
If you have any suggestions for improvement they are most welcome.
Patches even more so.
Josef
2009/2/2 Tyson Whitehead
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.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Mon, Feb 02, 2009 at 06:03:15PM +0100, Josef Svenningsson wrote:
Hi Tyson,
I also needed something like this a while ago so I knocked up a really simple module and put it on hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans
Warning! The STMonadTrans package uses State# nonlinearly, and as a result, can violate referential transparency:
import Control.Monad import Control.Monad.Trans import Control.Monad.ST.Trans
data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show
instance Monad Tree where return = Leaf Leaf a >>= k = k a Branch l r >>= k = Branch (l >>= k) (r >>= k)
foo :: STT s Tree Integer foo = do x <- newSTRef 0 y <- lift (Branch (Leaf 1) (Leaf 2)) when (odd y) (writeSTRef x y) readSTRef x
main = do print $ runST foo let Branch _ (Leaf x) = runST foo print x
prints Branch (Leaf 1) (Leaf 1) 0 Evaluating the thunk in the left branch affects the value seen in the right branch. In general a monad transformer version of ST would need to duplicate its state for each branch when used in conjunction with a nondeterminism monad like Tree, which would make it not really different from State, I think. Regards, Reid

On Mon, Feb 2, 2009 at 8:50 PM, Reid Barton
On Mon, Feb 02, 2009 at 06:03:15PM +0100, Josef Svenningsson wrote:
Hi Tyson,
I also needed something like this a while ago so I knocked up a really simple module and put it on hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans
Warning! The STMonadTrans package uses State# nonlinearly, and as a result, can violate referential transparency:
Indeed, thanks for pointing this out. I really should have a warning sign on the package saying that it only works for certain monads. Cheers, /Josef

On February 2, 2009 14:50:10 Reid Barton wrote:
On Mon, Feb 02, 2009 at 06:03:15PM +0100, Josef Svenningsson wrote:
I also needed something like this a while ago so I knocked up a really simple module and put it on hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans
Warning! The STMonadTrans package uses State# nonlinearly, and as a result, can violate referential transparency:
So, if I understand correctly, the underlying issue is that newtype STT s m a = STT (State# s -> m (STTRet s a)) data STTRet s a = STTRet (State# s) a along with STT m >>= k = STT $ \st -> do ret <- m st case ret of STTRet new_st a -> unSTT (k a) new_st (or my equivalent versions) can multithread the "State #s" token depending on how the underlying m monad implements it's bind operator. As in your example data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show Leaf a >>= k = k a Branch l r >>= k = Branch (l >>= k) (r >>= k) things breaks as multithreading the "State# s" token is a strict no-no because it doesn't actually duplicate the underlying real word it represents. StateT doesn't have this problem as it real has a state that would then branch. I guess then, if you wanted to salvage anything out of this, you would need something like a MonadSingleThreaded class that tags single threaded monads and is a class requirement for combining with the STT monad. Is this correct? And, apart from this, is it correct that ghc optimizations can't shuffle code in such a way that things break due to the single threading of the state token through the primitive operations such as newMutVar#? Thanks -Tyson

On February 2, 2009 11:26:02 Tyson Whitehead wrote:
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
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
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'
Of course, I forgot the method to actually use state threaded code stToSTT :: Monad m => ST s a -> STT s m a stToSTT (ST m) = STT $ \s -> case m s of (# s',x #) -> return $ STTBox s' x In re-reading my original email, I also thought I might not have been clear that I did write the instance methods (MonadCont, etc.), I just didn't include them as they would have made the email too lengthy. Cheers! -Tyson PS: Thanks for all the comments so far.
participants (3)
-
Josef Svenningsson
-
Reid Barton
-
Tyson Whitehead