[Haskell-cafe] Re: [Haskell] State, StateT and lifting

Andrew Pimlott andrew at pimlott.net
Sat Mar 19 13:09:25 EST 2005


On Sat, Mar 19, 2005 at 03:25:32AM -0800, Juan Carlos Arevalo Baeza wrote:
> Andrew Pimlott wrote:
> >You might solve this by changing the type of matchRuleST:
> >
> >   matchRuleST :: MonadState RuleSet m => String -> m (maybe Rule)
> 
>   I don't know... The original using IO somehow offended me because it 
> was not an operation that required IO. This one leaves the inner monad 
> unspecified, but still looks like baggage to me.

Look again:  There is no inner monad there, only the constraint that m
is a state monad.  State and StateT are both instances of MonadState, so
you can use this matchRuleST both with plain State, or StateT with any
inner monad.

> >You can turn this into a one-liner if you work on it a bit.  But I would
> >go with the above.
> > 
> >
> 
>   Yes. I prefer clarity, too.

"Go with the above" wasn't clear.  I meant, go with the signature for
matchRuleST suggested above.  If you do this, matchRuleST can be used as
either a

    State RuleSet (Maybe Rule)
    
or a

    Monad m => StateT RuleSet m (Maybe Rule)

and you don't need liftState at all.

> >Aside:  It bugs me that this is not defined by Control.Monad.State
> >(alongside modify and gets):
> >
> >   state :: MonadState s m => (s -> (a, s)) -> m a
>
>   Cute, thanx! It's good to know I wasn't just missing something 
> obvious. So, this is my final implementation (works!):
> 
> state :: MonadState s m => (s -> (a, s)) -> m a
> state sm = do
>    s <- get
>    let (result, newState) = sm s
>    put newState
>    return result
> 
> liftState :: Monad m => State s a -> StateT s m a
> liftState (State f) = state f

Nice!  Note that the inferred signature for liftState is

    liftState :: (MonadState s m) => State s a -> m a

Andrew


More information about the Haskell-Cafe mailing list