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

Juan Carlos Arevalo Baeza jcab at JCABs-Rumblings.com
Sat Mar 19 16:42:11 EST 2005


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).

   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?

-- Main entry point into the make engine.

make :: RuleSet -> String -> IO RuleSet
make ruleSet ruleName = execStateT (makeST ruleName) ruleSet

>you don't need liftState at all.
>  
>

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

>>>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
>  
>

   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?

   So... about liftIO... I implemented the main function of my make 
engine like this:

makeST ruleName = do
    rule <- matchRuleST ruleName -- (thanx!)
    case rule of
        Just (File dst srcList action) -> do
            makeListST srcList
            older <- liftIO $ isOlderFile dst srcList
            if older then do
                    liftIO $ do
                        print $ "Running file " ++ dst ++ "\n"
                        action dst srcList
                    return ()
                else
                    return ()
        Just (DoneRule _) -> return ()
        Nothing -> liftIO $ do
            exists <- doesFileExist ruleName
            if exists    then return ()
                        else ioError $ userError $ "Rule not found: " ++ 
ruleName

   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.

   Thanx a lot for your patience!

JCAB


More information about the Haskell-Cafe mailing list