Is there a StateT but with resulting pair swapped?

Hi cafe, I'm playing with alex recently and noticed that: newtype Alex a = Alex {unAlex :: AlexState -> Either String (AlexState, a)} which is almost StateT AlexState (Except String), and looks like I can make a MonadError instance out of it. Therefore I'm curious if there's any existing package that has newtype StateT' s m a = StateT' (s -> m (s, a)) -- note the swapped pair here so that I can just deriving (MonadError String) via StateT' AlexState (Except String) to implement MonadError. Thanks! -- Javran (Fang) Cheng

On Thu, Feb 25, 2021 at 01:08:41PM -0800, Javran Cheng wrote:
I'm playing with alex recently and noticed that:
newtype Alex a = Alex {unAlex :: AlexState -> Either String (AlexState, a)}
which is almost StateT AlexState (Except String), and looks like I can make a MonadError instance out of it.
Therefore I'm curious if there's any existing package that has newtype StateT' s m a = StateT' (s -> m (s, a)) -- note the swapped pair here
I am not aware of any, so I gave a go at writing a prototype of a StateT that's agnostic as to the order in which the pair elements are stored, allowing the Alex type to be coerced to the variant that's stored in "reverse" order as (s, a). The use of coercion requires that all the relevant constructors be in scope, even those you're not otherwise explicitly using. Running the below program (also attached): module Main (main) where import Data.Coerce (coerce) import Control.Monad.Identity (Identity(..)) import Control.Monad.Trans.Except (ExceptT(..), Except, runExcept) import qualified GStateT as GS import GStateT ( GStateT(..), Swap(..) ) -- Fake Alex with state Int type AlexState = Int newtype Alex a = Alex {unAlex :: AlexState -> Either String (AlexState, a) } -- Alias the swapped GStateT as StateT type StateT = GS.SwapStateT runStateT :: Monad m => StateT s m a -> s -> m (s, a) runStateT m = GS.runSwapStateT m main :: IO () main = do let x = (Alex $ \i -> Right (i, i+1)) :: Alex Int y = coerce x :: StateT AlexState (Except String) Int print $ unAlex x 1 print $ runExcept $ runStateT y 1 print $ runExcept $ GS.execStateT y 1 print $ runExcept $ GS.evalStateT y 1 prints: Right (1,2) Right (1,2) Right 1 Right 2 showing that all the pieces appear to fit togher. I've not implemented MTL-style class instances, but those could also be added. -- Viktor.
participants (2)
-
Javran Cheng
-
Viktor Dukhovni