State monad within ST monad

The following code gives the error: "No instance for ‘MArray (STArray s) Char Identity’ arising from a use of ‘readArray’. Can someone help me understand what’s wrong? Thanks!

foo = runST do
    ary <- newListArray (0,4) "hello" :: ST s (STArray s Int Char)
    pure $ flip execState "" do
        for_ [0..4] \i -> do
            c <- lift $ readArray ary i
            modify' (c:)
1 Like

You can do it the other way around: use StateT and embed ST into that. This works type checks:

foo = runST do
    ary <- newListArray (0,4) "hello" :: ST s (STArray s Int Char)
    flip execStateT "" do
        for_ [0..4] \i -> do
            c <- lift $ readArray ary i
            modify' (c:)

The error message is indeed bad, though.

2 Likes

omg it’s the execStateT vs the execState that was messing me up… thank you!

As an aside, it’s probably not terribly useful to use StateT if you’re already in ST. You can just do this:

{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE BlockArguments #-}

import Control.Monad.ST
import Data.STRef
import Data.Array.ST
import Control.Monad.Trans.State
import Control.Monad.Trans
import Data.Foldable

foo = runST do
    ary <- newListArray (0,4) "hello" :: ST s (STArray s Int Char)
    s <- newSTRef ""
    for_ [0..4] \i -> do
        c <- readArray ary i
        modifySTRef' s (c:)
    readSTRef s

EDIT: fixed thanks to @noina

4 Likes

your missing a ‘readSTRef s’ at the end now though :wink:

2 Likes

I’d imagine it could be useful if you’re doing some sort of stateful recursion with backtracking while also actually mutating things along the way. Kinda contrived, but not inconceivable!

Ah yes, the inability to “partially run” ST is quite limiting in that regard (a limitation that Bluefin doesn’t share, incidentally).

EDIT: In fact, I’m not sure it’s really a weakness of ST because you can still copy values between states and achieve some form of “transactionality” or ability to “partially run”.

Immutable data is the real solution, so an STRef of something immutable can work too. But because StateT is just a function, you can use the recursion as an implicit data structure sometimes to more naturally do fun things. But yeah you can emulate that with ST data too.

1 Like