How to use ST Monad with monad transformers
Asked Answered
E

1

6

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?

Emsmus answered 19/9, 2022 at 8:41 Comment(5)
Relevant package: hackage.haskell.org/package/STMonadTransArgybargy
I don't know of any liftST that can magically work on transformer stacks like liftIO does. Still, if there's no such magic around, we can still work using lift. We need to apply lift once of each transformer in the stack, so it's not as convenient, but it should work.Rubricate
What type would liftST have? The phantom type variable on ST seems to me like it would make things difficult.Fitz
@Fitz Interesting, but I wonder if that's really the case. I tried lift (newSTRef "hello" >>= \r -> readSTRef r) and GHCi typed it as MonadTrans t => t (ST s) [Char]. As long as we use a monad transformer stack on the base monad ST s, using the same s everywhere, I can see no obvious issues with one-step lifting. Regarding the more general liftST, perhaps it could be liftST :: MonadST s m => ST s a -> m a (note the s in the constraint)?Rubricate
reddit.com/r/haskell/comments/eh2obw/…Smoodge
F
2

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)
Faze answered 19/9, 2022 at 21:59 Comment(0)

© 2022 - 2025 — McMap. All rights reserved.