
I have two pieces of state I'm managing: type FooState = State Foo Foo type BarState = State Bar Bar There is a bit of interplay between them, and I want a function that does something like: importantFunction :: Foo -> Bar -> (Foo, Bar) The problem is, >>= only works when I'm chaining all of the same type of state. So I can't do: modifiesFoo >>= \foo -> modifiesBar foo >>= \bar -> return (foo, bar) So how do I get the results of both modifications back? I hope that makes sense. Programming in Haskell is proving to be very difficult; I once again fear I'm too stupid.

I doubt it's an issue of being too stupid. If you come from more
traditional languages, then Haskell requires that to rewire your brain
to think in Haskell. It's very different. It appears hard because
there is a lot of work to re-learning things you thought you knew.
As for combining two state monads, is there a reason you cannot
combine them into one large state?
It looks what you are doing is:
importantFunction initialFoo initialBar =
let foo = execState modifiesFoo initialFoo
in (foo, execState (modifiesBar foo) initialBar)
Which would have the type signature you are expecting and wouldn't
need to be monadic.
Drew Haven
drew.haven@gmail.com
On Wed, Jun 23, 2010 at 2:10 PM, Jordan Cooper
I have two pieces of state I'm managing: type FooState = State Foo Foo type BarState = State Bar Bar
There is a bit of interplay between them, and I want a function that does something like: importantFunction :: Foo -> Bar -> (Foo, Bar)
The problem is, >>= only works when I'm chaining all of the same type of state. So I can't do: modifiesFoo >>= \foo -> modifiesBar foo >>= \bar -> return (foo, bar)
So how do I get the results of both modifications back? I hope that makes sense. Programming in Haskell is proving to be very difficult; I once again fear I'm too stupid. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 6/23/10, Drew Haven
I doubt it's an issue of being too stupid. If you come from more traditional languages, then Haskell requires that to rewire your brain to think in Haskell. It's very different. It appears hard because there is a lot of work to re-learning things you thought you knew.
You're probably right, but I can't help but have some doubts :)
As for combining two state monads, is there a reason you cannot combine them into one large state?
It looks what you are doing is:
importantFunction initialFoo initialBar = let foo = execState modifiesFoo initialFoo in (foo, execState (modifiesBar foo) initialBar)
Which would have the type signature you are expecting and wouldn't need to be monadic.
Well, two things that I guess are important to mention: In my program, it's not Foo and Bar, but Cards and Players. Any player can potentially act on any card, even if it's not their own, thus I felt they probably shouldn't be part of the same state (though perhaps I am wrong in this). Secondly, as to why I wanted to use a monad here, importantFunction (which is called playerTurn in the real program) would contain a series of functions that would modify Cards and Players, not just one each as in my initial example. Thus it seems like I'd have to end up with let foo... let foo'... etc. which, from my reading in RWH, seems to be an acceptable use for a State monad. Thanks for your answer, and to Matthew for the encouragement :)

On Wednesday 23 June 2010 23:48:42, Jordan Cooper wrote:
Well, two things that I guess are important to mention:
In my program, it's not Foo and Bar, but Cards and Players. Any player can potentially act on any card, even if it's not their own, thus I felt they probably shouldn't be part of the same state (though perhaps I am wrong in this).
Secondly, as to why I wanted to use a monad here, importantFunction (which is called playerTurn in the real program) would contain a series of functions that would modify Cards and Players, not just one each as in my initial example. Thus it seems like I'd have to end up with let foo... let foo'... etc. which, from my reading in RWH, seems to be an acceptable use for a State monad.
Thanks for your answer, and to Matthew for the encouragement :)
Maybe a Monad transformer would be helpful, something along the lines of StateT Player (State Card) foo then you can work in the inner Monad (State Card) via lift. fooBar = do cardResult <- lift cardAction playerResult <- playerAction cardResult return (cardResult, playerResult)

Alright, I'll give this a shot. I've never used monad transformers
before, so it should be interesting :)
On 6/23/10, Daniel Fischer
On Wednesday 23 June 2010 23:48:42, Jordan Cooper wrote:
Well, two things that I guess are important to mention:
In my program, it's not Foo and Bar, but Cards and Players. Any player can potentially act on any card, even if it's not their own, thus I felt they probably shouldn't be part of the same state (though perhaps I am wrong in this).
Secondly, as to why I wanted to use a monad here, importantFunction (which is called playerTurn in the real program) would contain a series of functions that would modify Cards and Players, not just one each as in my initial example. Thus it seems like I'd have to end up with let foo... let foo'... etc. which, from my reading in RWH, seems to be an acceptable use for a State monad.
Thanks for your answer, and to Matthew for the encouragement :)
Maybe a Monad transformer would be helpful, something along the lines of
StateT Player (State Card) foo
then you can work in the inner Monad (State Card) via lift.
fooBar = do cardResult <- lift cardAction playerResult <- playerAction cardResult return (cardResult, playerResult)

Jordan Cooper wrote:
Secondly, as to why I wanted to use a monad here, importantFunction (which is called playerTurn in the real program) would contain a series of functions that would modify Cards and Players, not just one each as in my initial example. Thus it seems like I'd have to end up with let foo... let foo'... etc. which, from my reading in RWH, seems to be an acceptable use for a State monad.
While your use of the state monad may well be sensible, keep in mind that many cases of "threading state" are covered by ordinary functional programming idioms, like function composition process = take 3 . sort . map length . filter (not . null) . lines and accumulating parameters average xs = foldl' step (0,0) xs where step (!s,!n) x = (s+x, n+1) reverse xs = go xs where go ys [] = ys go ys (x:xs) = go (x:ys) xs The functions in Data.Map are a good example as well: most of them "change" the map, but a state monad would be overkill for that. The state monad is mainly beneficial when you otherwise would have many functions of type :: s -> (a,s) with ugly plumbing like let (a,s') = foo s; (b,s'') = foo s' in .. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Daniel Fischer
-
Drew Haven
-
Heinrich Apfelmus
-
Jordan Cooper