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

minh thu noteed at gmail.com
Fri Mar 13 05:09:13 EDT 2009


2009/3/13 Marcin Kosiba <marcin.kosiba at gmail.com>:
> On Friday 13 March 2009, you wrote:
>> 2009/3/13 Marcin Kosiba <marcin.kosiba at gmail.com>:
>> > On Thursday 12 March 2009, you wrote:
>> >> 2009/3/12 Marcin Kosiba <marcin.kosiba at gmail.com>:
>> >> > 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


More information about the Haskell-Cafe mailing list