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

Andrew Pimlott andrew at pimlott.net
Sat Mar 19 18:06:09 EST 2005


On Sat, Mar 19, 2005 at 01:42:11PM -0800, Juan Carlos Arevalo Baeza wrote:
> Andrew Pimlott wrote:
> 
> >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.
> 
>   Oh, I see now. It does work, too. Even after using this, it still 
> looks quite strange to me. I dunno... it's odds like this one that make 
> Haskell into a naturally obfuscated language, IMHO. You can only see 
> this by "thinking mathematically", if you know what I mean. The way I 
> was doing it before, I was thinking... relatively little in comparison. 
> It's what came naturally (and still does).

Well, there's nothing wrong with that. :-)  It's a matter of style.

>   I can prove I'm not a hopeless case :). So... same thing for the 
> other functions. Following your example, I switched them to:
> 
> makeListST :: (MonadState RuleSet m, MonadIO m) => [String] -> m ()
> makeST :: (MonadState RuleSet m, MonadIO m) => String -> m ()
> 
>   and that works, too. No more StateT either. Just like with STate, the 
> question is... would I ever use it directly? Now, I still need 
> execStateT to implement the main entry point into the engine, right?

Right, that's the only time you need to commit to what type of state
monad you're actually running.

>   No I don't. I don't need State either. Are there any situations where 
> it makes sense to use State directly?

Probably not.  Except that as you said, it's sometimes easier to wrap
your mind around a concrete type, especially in the beginning.

> >Nice!  Note that the inferred signature for liftState is
> >
> >   liftState :: (MonadState s m) => State s a -> m a
> 
>   Ah, yes! Even more general-purpose. so... liftState and state are 
> both gone. You say you end up having to define "state" anyway. What 
> situations are there which require it?

It's simply convenient for writing state transformers.  For example, if
I want to get and increment a numeric state,

    addOne :: (Num n, MonadState n m) => m n
    addOne = state (\x -> (x, x + 1))

If I used some combination of get, put, modify, and gets, it would be
slightly longer and no clearer.  Plus, those other four can all be
implemented directly in terms of state, so its absence is conspicuous.
You could argue that it should be part of the class definition, so that

    instance MonadState s (State s) where
        state = State

>   So... about liftIO... I implemented the main function of my make 
> engine like this:
[snip]
>   As you can see, I'm using liftIO quite a lot. I guess that's 
> necessary. I just wanted to double-check that it really is, and that I'm 
> doing it correctly.

Looks fine to me!

Andrew


More information about the Haskell-Cafe mailing list