Re: [Haskell] State, StateT and lifting

Andrew Pimlott wrote:
[I think it is preferred to post this on haskell-cafe.]
Oops! I guess you're right.
On Fri, Mar 18, 2005 at 02:00:37PM -0800, Juan Carlos Arevalo Baeza wrote:
matchRuleST :: String -> State RuleSet (Maybe Rule) makeST :: String -> StateT RuleSet IO ()
matchRuleST doesn't really need IO for anything (it just works on the current state "RuleSet"). makeST needs IO (it does file date comparisons, actions on the files, etc... the usual "make" stuff). The problem is how to properly use matchRuleST from makeST.
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.
Then, I decided to try again, and came up with this function:
liftState :: State s a -> StateT s m a
(I think you left out the constraint (Monad m).)
Yes, I did, thanx. I wrote the message a tad little bit too early :-P
liftState s = do state1 <- get ( let (result, state) = evalState (do {result <- s; state <- get; return (result, state)}) state1 in do put state return result )
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. And I did it ugly (still groping with the syntax). This is the final version: liftState :: Monad m => State s a -> StateT s m a liftState s = do state1 <- get let (result, state) = evalState (do {result <- s; state <- get; return (result, state)}) state1 put state return result
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
I almost always end up defining it myself and use it to implement other state transformers. I would do the same for other monad classes (Writer, etc): provide a function that captures the general operation.
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 JCAB

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

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

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
participants (3)
-
Andrew Pimlott
-
Juan Carlos Arevalo Baeza
-
Juan Carlos Arevalo Baeza