The haskell transformers
library provides MonadIO
class and liftIO
to lift IO operations in a monad transformer stack. It seems to me that the same could be done for the ST monad, but I couldn't find it in any monad transformer library. Is there a reason for this omission? How do I use ST monad with e.g., MaybeT
or ReaderT
?
How to use ST Monad with monad transformers
Asked Answered
I gave it a shot, and it looks like if you only want to use ST
as a base monad, the following is probably sufficient for use with the "usual" transformers.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
module TransST
(liftST, MonadST)
where
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Control.Monad.Trans.State
import Control.Monad.Trans.Writer
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.RWS
import Control.Monad.Trans.Except
import Control.Monad.ST
class Monad m => MonadST s m where
liftST :: ST s a -> m a
instance MonadST s (ST s) where
liftST act = act
instance (MonadST s m) => MonadST s (ReaderT r m) where
liftST act = lift (liftST act)
instance (MonadST s m) => MonadST s (StateT st m) where
liftST act = lift (liftST act)
instance (Monoid w, MonadST s m) => MonadST s (WriterT w m) where
liftST act = lift (liftST act)
instance (Monoid w, MonadST s m) => MonadST s (RWST r w s m) where
liftST act = lift (liftST act)
instance (MonadST s m) => MonadST s (MaybeT m) where
liftST act = lift (liftST act)
instance (MonadST s m) => MonadST s (ExceptT e m) where
liftST act = lift (liftST act)
You may find you occasionally need to add a type application to liftST
or other functions to resolve ambiguous uses of the ST monad parameter, as in this test case:
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
import TransST
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Writer
import Control.Monad.Except
import Control.Monad.Trans.Maybe
import Control.Monad.ST
import Data.STRef
import Data.Char
type M s = ReaderT Int (WriterT [String] (StateT Char (ExceptT String (MaybeT (ST s)))))
runM :: (forall s. M s a) -> Int -> Char -> Maybe (Either String ((a, [String]), Char))
runM act r s = runST $ runMaybeT $ runExceptT
$ flip runStateT s $ runWriterT $ runReaderT act r
someSTOperation :: (MonadST s m) => Int -> m (STRef s Int)
someSTOperation x = liftST (newSTRef x)
test :: Maybe (Either String ((Int, [String]), Char))
test = runM act 5 'a'
where
act :: forall s. M s Int
act = do
tell ["starting"]
x <- gets ord
s <- someSTOperation @s x -- needs a type annotation
r <- ask
liftST (writeSTRef s (x + r))
put . chr =<< liftST (readSTRef s)
c <- get
return (ord c)
© 2022 - 2025 — McMap. All rights reserved.
liftST
that can magically work on transformer stacks likeliftIO
does. Still, if there's no such magic around, we can still work usinglift
. We need to applylift
once of each transformer in the stack, so it's not as convenient, but it should work. – RubricateliftST
have? The phantom type variable on ST seems to me like it would make things difficult. – Fitzlift (newSTRef "hello" >>= \r -> readSTRef r)
and GHCi typed it asMonadTrans t => t (ST s) [Char]
. As long as we use a monad transformer stack on the base monadST s
, using the sames
everywhere, I can see no obvious issues with one-step lifting. Regarding the more generalliftST
, perhaps it could beliftST :: MonadST s m => ST s a -> m a
(note thes
in the constraint)? – Rubricate