gcnew
gcnew

Reputation: 55

Composing State and State transformer actions

I have several State monad actions. Some of the actions make decisions based on the current state and other input optionally generating result. The two types of actions invoke each other.

I have modeled these two action types with State and StateT Maybe. The following (contrived) example shows my current approach.

{-# LANGUAGE MultiWayIf #-}

import Control.Monad (guard)
import Control.Monad.Identity (runIdentity)
import Control.Monad.Trans.State

type Producer      = Int -> State  [Int] Int
type MaybeProducer = Int -> StateT [Int] Maybe Int

produce :: Producer
produce n
    | n <= 0    = return 0

    | otherwise = do accum <- get
                     let mRes = runStateT (maybeProduce n) accum

                     if | Just res <- mRes -> StateT $ const (return res)
                        | otherwise        -> do res <- produce (n - 1)
                                                 return $ res + n

maybeProduce :: MaybeProducer
maybeProduce n = do guard $ odd n
                    modify (n:)

                    mapStateT (return . runIdentity) $
                        do res <- produce (n - 1)
                           return $ res + n

I have factored out separating the checks from the actions (thus transforming them into simple State actions) because the check itself is very involved (80% of the work) and provides the bindings needed in the action. I don't want to promote the State actions to StateT Maybe either, because it poses an inaccurate model.

Is there a better or more elegan way that I'm missing? In particular I don't like the mapStateT/runStateT duo, but it seems necessary.

PS: I know the example is actually a Writer, but I used State to better reflect the real case

Upvotes: 2

Views: 197

Answers (1)

Luis Casillas
Luis Casillas

Reputation: 30227

I don't want to promote the State actions to StateT Maybe either, because it poses an inaccurate model.

What do you mean by "promote"? I can't tell which of these you mean:

  1. Rewrite the definitions of the State actions so that their type is now StateT Maybe, even though they don't rely on Maybe at all;
  2. Use an adapter function that transforms State s a into StateT s Maybe a.

I agree with rejecting (1), but to me that mean either:

  • Go for (2). One useful tool for this is to use the mmorph library (blog entry).
  • Rewrite the actions from State s a to use Monad m => StateT s m a.

In the second case, the type is compatible with any Monad m but does not allow the code to assume any specific base monad, so you get the same purity as State s a.

I'd give mmorph a shot. Note that:

  • State s a = StateT s Identity a;
  • hoist generalize :: (MFunctor t, Monad m) => t Identity a -> t m a;
  • And that specializes to hoist generalize :: State s a -> StateT s Maybe a.

EDIT: It's worth nothing that there is an isomorphism between the State s a and forall m. StateT s m a types, given by these inverse functions:

{-# LANGUAGE RankNTypes #-}

import Control.Monad.Morph
import Control.Monad.Trans
import Control.Monad.Trans.State
import Control.Monad.Identity

fwd :: (MFunctor t, Monad m) => t Identity a -> t m a
fwd = hoist generalize

-- The `forall` in the signature forbids callers from demanding any
-- specific choice of type for `m`, which allows *us* to choose 
-- `Identity` for `m` here.
bck :: MFunctor t => (forall m. t m a) -> t Identity a
bck = hoist generalize

So the Monad m => StateT s m a and mmorph solutions are, effectively, the same. I prefer using mmorph here, though.

Upvotes: 1

Related Questions