Re: [Haskell-cafe] Using a monad to decompose a function into functions

On Friday 13 March 2009, you wrote:
2009/3/13 Marcin Kosiba
: On Thursday 12 March 2009, you wrote:
2009/3/12 Marcin Kosiba
: Hi, I'm doing a bit of research into mobility models and I'm currently exploring implementation language choices for the simulator (*snip*) The simulation algorithm requires expressing the node's mobility so that it is "stateless". The mobility model algorithm's type should be something like: mobility_model :: WorldState -> NodeState -> OtherInput -> (Action, NodeState)
where Action can alter WorldState and the second NodeState is an altered input NodeState. I perform a form of speculative execution on mobility_model so sometimes I need to backtrack to a previous world and node state. This is all fairly simple stuff, and was just an introduction. What I do now is store an enum in NodeState and implement mobility_model as one big case statement. Yes, this is very imperative of me, I know. What I'd like to do is to express mobility_model, so that the code would look like:
mobility_model world node input = do do_calculus emit_action if something then emit_action else emit_action do_calculus emit_action mobility_model world node input
Hi,
It seems you can use http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control- Mon ad-State-Lazy.html Just have a look at the exemple :
tick :: State Int Int tick = do n <- get put (n+1) return n
your code would become something like mobility_model :: OtherInput -> State (WorldState,NodeState) () mobility_model input = do world <- gets fst node <- gets snd .... let (world',node') = ... put (world',node')
ok, that solves part of the problem. what this doesn't solve is that somewhere between these lines (which corespond to emit_action in my example)
let (world',node') = ... put (world',node')
I need to return a value and an Action and NodeState to the simulation algorithm. and then, after the simulation algorithm calculates a new WorldState it will want the mobility_model to where it left off, but with a new WorldState.
I hope I'm clear about what I wish to achieve: each emit_action should return a value (Action, NodeState) and maybe a function mobility_model_cont which I then could call with the new WorldState to continue from where emit_action returned.
I'm not entirely sure ... but I think it doesn't matter that much :) Here is why.
This was just an exemple : mobility_model :: OtherInput -> State (WorldState,NodeState) ()
You could also have mobility_model :: OtherInput -> NodeState -> State WorldState (NodeState,Action) or whatever.
In fact, the State monad makes it easy to thread (in this context, it means 'pass around') an argument to many functions, providing a nice syntax reminiscent of imperative language. But it lets you completely free of what is passed around. It depends on what you want to be explicitely passed by argument, and what you want to pass in the state of the monad (that is, what you want to appear, inside the monad only, as some global variable).
So in your code, if you often need to pass a WorldState to a function which should return a modified WorldState, it makes sense to put WorldState inside the state monad. But, maybe, if there is just a few functions which act on NodeState, it has not to be part of the state carried by the state monad.
I'm not entirely sure of what is a problem to you : is it the use of the State monad, or something else ? If it can help you to formulate your question you can post some code (or past it to http://hpaste.org/)...
Threading the state is not the problem. Maybe this will help: what I have now: fsm world state = case state of first -> do_stuff_one (move_up, succ state) second -> do_stuff_two (move_left, succ state) third -> do_stuff_three (move_right, first) what I'd want to have is to say: fsm world state = do do_stuff_one yield move_up do_stuff_two yield move_left do_stuff_three yield move_right fsm world state and have it "translated" to: fsm world state = do_stuff_one (move_up, \world' state' -> do_stuff_two (move_left, \world'' state'' -> do_stuff_three (move_right, fsm world'' state'') Thanks! Marcin Kosiba

2009/3/13 Marcin Kosiba
On Friday 13 March 2009, you wrote:
2009/3/13 Marcin Kosiba
: On Thursday 12 March 2009, you wrote:
2009/3/12 Marcin Kosiba
: Hi, I'm doing a bit of research into mobility models and I'm currently exploring implementation language choices for the simulator (*snip*) The simulation algorithm requires expressing the node's mobility so that it is "stateless". The mobility model algorithm's type should be something like: mobility_model :: WorldState -> NodeState -> OtherInput -> (Action, NodeState)
where Action can alter WorldState and the second NodeState is an altered input NodeState. I perform a form of speculative execution on mobility_model so sometimes I need to backtrack to a previous world and node state. This is all fairly simple stuff, and was just an introduction. What I do now is store an enum in NodeState and implement mobility_model as one big case statement. Yes, this is very imperative of me, I know. What I'd like to do is to express mobility_model, so that the code would look like:
mobility_model world node input = do do_calculus emit_action if something then emit_action else emit_action do_calculus emit_action mobility_model world node input
Hi,
It seems you can use http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control- Mon ad-State-Lazy.html Just have a look at the exemple :
tick :: State Int Int tick = do n <- get put (n+1) return n
your code would become something like mobility_model :: OtherInput -> State (WorldState,NodeState) () mobility_model input = do world <- gets fst node <- gets snd .... let (world',node') = ... put (world',node')
ok, that solves part of the problem. what this doesn't solve is that somewhere between these lines (which corespond to emit_action in my example)
let (world',node') = ... put (world',node')
I need to return a value and an Action and NodeState to the simulation algorithm. and then, after the simulation algorithm calculates a new WorldState it will want the mobility_model to where it left off, but with a new WorldState.
I hope I'm clear about what I wish to achieve: each emit_action should return a value (Action, NodeState) and maybe a function mobility_model_cont which I then could call with the new WorldState to continue from where emit_action returned.
I'm not entirely sure ... but I think it doesn't matter that much :) Here is why.
This was just an exemple : mobility_model :: OtherInput -> State (WorldState,NodeState) ()
You could also have mobility_model :: OtherInput -> NodeState -> State WorldState (NodeState,Action) or whatever.
In fact, the State monad makes it easy to thread (in this context, it means 'pass around') an argument to many functions, providing a nice syntax reminiscent of imperative language. But it lets you completely free of what is passed around. It depends on what you want to be explicitely passed by argument, and what you want to pass in the state of the monad (that is, what you want to appear, inside the monad only, as some global variable).
So in your code, if you often need to pass a WorldState to a function which should return a modified WorldState, it makes sense to put WorldState inside the state monad. But, maybe, if there is just a few functions which act on NodeState, it has not to be part of the state carried by the state monad.
I'm not entirely sure of what is a problem to you : is it the use of the State monad, or something else ? If it can help you to formulate your question you can post some code (or past it to http://hpaste.org/)...
Threading the state is not the problem. Maybe this will help: what I have now:
fsm world state = case state of first -> do_stuff_one (move_up, succ state) second -> do_stuff_two (move_left, succ state) third -> do_stuff_three (move_right, first)
what I'd want to have is to say: fsm world state = do do_stuff_one yield move_up do_stuff_two yield move_left do_stuff_three yield move_right fsm world state
and have it "translated" to:
fsm world state = do_stuff_one (move_up, \world' state' -> do_stuff_two (move_left, \world'' state'' -> do_stuff_three (move_right, fsm world'' state'')
Sorry, I never used continuations or coroutines in Haskell. But, if your goal is to be less imperative, I'm not sure using 'yield' is what you want. If what you do is well expressed by a fsm, maybe you should stick to it. Thu

2009/3/13 Marcin Kosiba
... Threading the state is not the problem. Maybe this will help: what I have now:
fsm world state = case state of first -> do_stuff_one (move_up, succ state) second -> do_stuff_two (move_left, succ state) third -> do_stuff_three (move_right, first)
what I'd want to have is to say: fsm world state = do do_stuff_one yield move_up do_stuff_two yield move_left do_stuff_three yield move_right fsm world state
and have it "translated" to:
fsm world state = do_stuff_one (move_up, \world' state' -> do_stuff_two (move_left, \world'' state'' -> do_stuff_three (move_right, fsm world'' state'')
Hi, I've not fully understood your exact problem but I think you might have a look to Continuations and Delimited Continuations. Both can help you solve the problem with implementing a yield statement. You can have a look at one of my (rather) old blog's posts about how to implement yield/send statements a-la-python: http://monadicheadaches.blogspot.com/2008/01/python-25s-iterators-in-haskell... Notice that blogspot messed up with code blocks so indentation looks bad and some character is even missing. Bye, Cristiano

On Friday 13 March 2009, Cristiano Paris wrote:
2009/3/13 Marcin Kosiba
: ... Threading the state is not the problem. Maybe this will help: what I have now:
fsm world state = case state of first -> do_stuff_one (move_up, succ state) second -> do_stuff_two (move_left, succ state) third -> do_stuff_three (move_right, first)
what I'd want to have is to say: fsm world state = do do_stuff_one yield move_up do_stuff_two yield move_left do_stuff_three yield move_right fsm world state
and have it "translated" to:
fsm world state = do_stuff_one (move_up, \world' state' -> do_stuff_two (move_left, \world'' state'' -> do_stuff_three (move_right, fsm world'' state'')
Hi,
I've not fully understood your exact problem but I think you might have a look to Continuations and Delimited Continuations.
Both can help you solve the problem with implementing a yield statement. You can have a look at one of my (rather) old blog's posts about how to implement yield/send statements a-la-python:
http://monadicheadaches.blogspot.com/2008/01/python-25s-iterators-in-haskel l-sort-of.html
Notice that blogspot messed up with code blocks so indentation looks bad and some character is even missing.
Hi, I've already checked those out. I tried using your yield implementation and while it works, I couldn't get it to work with the state monad. So while: data RecPair a b = Nil | RP (b, a -> RecPair a b) yield x = Cont $ \k -> RP (x, k) got me half-way to my goal, I couldn't figure out how to make something like: yield' = do state <- get state' <- yield state put state' Thanks! Marcin Kosiba

2009/3/13 Marcin Kosiba
Hi, I've already checked those out. I tried using your yield implementation and while it works, I couldn't get it to work with the state monad. So while: data RecPair a b = Nil | RP (b, a -> RecPair a b) yield x = Cont $ \k -> RP (x, k)
got me half-way to my goal, I couldn't figure out how to make something like:
yield' = do state <- get state' <- yield state put state'
Basically, the yield is built upon the Cont monad which has a transformer counter part, ContT. You could try and re-implement the yield under ContT instead of just Cont then you can stack ContT on top of State (or StateT if you need more monads) and have a state (i.e. get/put) and the yield. Hope this helps. Cristiano

On Friday 13 March 2009, Cristiano Paris wrote:
2009/3/13 Marcin Kosiba
: Hi, I've already checked those out. I tried using your yield implementation and while it works, I couldn't get it to work with the state monad. So while: data RecPair a b = Nil | RP (b, a -> RecPair a b) yield x = Cont $ \k -> RP (x, k)
got me half-way to my goal, I couldn't figure out how to make something like:
yield' = do state <- get state' <- yield state put state'
Basically, the yield is built upon the Cont monad which has a transformer counter part, ContT. You could try and re-implement the yield under ContT instead of just Cont then you can stack ContT on top of State (or StateT if you need more monads) and have a state (i.e. get/put) and the yield.
Great! That helped a lot. I'm attaching a ConT yield implementation and another one which also handles a return statement with a different type. Hope someone finds them useful. Thanks! Marcin Kosiba

2009/3/13 Marcin Kosiba
Threading the state is not the problem. Maybe this will help: what I have now:
fsm world state = case state of first -> do_stuff_one (move_up, succ state) second -> do_stuff_two (move_left, succ state) third -> do_stuff_three (move_right, first)
what I'd want to have is to say: fsm world state = do do_stuff_one yield move_up do_stuff_two yield move_left do_stuff_three yield move_right fsm world state
and have it "translated" to:
fsm world state = do_stuff_one (move_up, \world' state' -> do_stuff_two (move_left, \world'' state'' -> do_stuff_three (move_right, fsm world'' state'')
Do you really need yield? Most of the time, you should be able to
implement move_up and the rest directly using bits of the run
function.
But assuming you do need yield, you probably want a resumption monad.
Here's a variant of an implementation I've worked with recently.
data Thunk r m a = Val a | Suspend r (m (Thunk r m a))
newtype Suspend r m a = C { unC :: forall b. (a -> m (Thunk r m a)) ->
m (Thunk r m a) }
instance Monad (Suspend r m) where
return a = C (\k -> k a)
m >>= f = C (\k -> unC m (\a -> unC (f a) k))
instance MonadTrans (Suspend r) where
lift m = C (\k -> m >>= k)
suspend :: Monad m => r -> Suspend r m ()
suspend r = C (\k -> return $ Suspend r (k ()))
run :: Monad m => Suspend r m a -> m (Thunk r m a)
run m = unC m (return . Val)
These laws should give an idea of how it works:
run (return a) = return (Val a)
run (lift m >>= f) = m >>= \a -> run (f a)
run (suspend r >> m) = return (Suspend r (run m))
There's also a function that undoes run, although you shouldn't need it.
enter :: Monad m => Thunk r m a -> Suspend r m a
enter (Val a) = return a
enter (Suspend r m) = suspend r >> lift m >>= enter
--
Dave Menendez
participants (4)
-
Cristiano Paris
-
David Menendez
-
Marcin Kosiba
-
minh thu