Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

[Caml-list] Functional design for a basic simulation pipe.

0 views
Skip to first unread message

Hugo Ferreira

unread,
Oct 10, 2007, 3:40:01 AM10/10/07
to caml...@yquem.inria.fr
Hello,

I have been looking at how I may go about developing a very simple
simulation system for my experiments. The simulation consists in
generating a set of events, these events then cause a state change, the
state change is then analyzed and processed in several steps and finally
termination conditions are checked. When said termination condition is
true the simulation ends and the results are saved.

Now I figured this could be done using composition. For example:

# let ( |> ) f g x = g (f x) ;;
val ( |> ) : ('a -> 'b) -> ('b -> 'c) -> 'a -> 'c = <fun>

# let gen_events s0 = () ;;
val gen_events : 'a -> unit = <fun>

# let gen_states e = () ;;
val gen_states : 'a -> unit = <fun>

# let analyze_data s = () ;;
val analyze_data : 'a -> unit = <fun>

# let check_stop s = () ;;
val check_stop : 'a -> unit = <fun>

Then I could set-up an experiment so:

# let exp = gen_events |> gen_states |> analyze_data |> check_stop ;;
val exp : '_a -> unit = <fun>

And execute it so:

# let start_state = () ;;
val start_state : unit = ()

# let _ = exp start_state ;;
- : unit = ()

Please note that I have used any old types just to get the idea through.
Also note that experiments are set-up with a given set of parameters.
Such parameters can be defined when the "exp" composition is set up.

Ok, so far so good. Now notice how the data events and state change are
potentially infinite. I figured the best way to go about it is with lazy
evaluation so that the calculations terminate when the last function in
the pipe stop "pulling" data in.

This is all "fine and dandy" but the problem I have however is that the
"gen_events" function depends on the last state reached. In other words
"gen_states" updates the current state which should then be made
available to "gen_events" when the next events are "pulled in". Of
course this could be solved with a global reference but this is not
functional. Alternatively we could combine "gen_events" and "gen_state"
into one function (my best bet?).

My question is: how can one design and implement such a "pull pipe" and
solve the problem I have of propagating state back to a previous
function. If this is not possible functionally what other options do I
have? Better yet, what is the better way to implement such a system?

TIA,
Hugo F.

_______________________________________________
Caml-list mailing list. Subscription management:
http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
Archives: http://caml.inria.fr
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
Bug reports: http://caml.inria.fr/bin/caml-bugs

skaller

unread,
Oct 10, 2007, 4:35:37 AM10/10/07
to Hugo Ferreira, caml...@yquem.inria.fr
On Wed, 2007-10-10 at 08:39 +0100, Hugo Ferreira wrote:

> # let exp = gen_events |> gen_states |> analyze_data |> check_stop ;;
> val exp : '_a -> unit = <fun>
>
> And execute it so:
>
> # let start_state = () ;;
> val start_state : unit = ()
>
> # let _ = exp start_state ;;
> - : unit = ()

> My question is: how can one design and implement such a "pull pipe" and


> solve the problem I have of propagating state back to a previous
> function.

Assume

f : state_t -> state_t option

is your state transformer, then

let rec go state =
match f state with
| Some state -> go state
| None -> ()

will do it.

--
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net

Hugo Ferreira

unread,
Oct 10, 2007, 6:10:48 AM10/10/07
to skaller, caml...@yquem.inria.fr
Hello,

skaller wrote:
> On Wed, 2007-10-10 at 08:39 +0100, Hugo Ferreira wrote:
>
>> # let exp = gen_events |> gen_states |> analyze_data |> check_stop ;;
>> val exp : '_a -> unit = <fun>
>>
>> And execute it so:
>>
>> # let start_state = () ;;
>> val start_state : unit = ()
>>
>> # let _ = exp start_state ;;
>> - : unit = ()
>
>> My question is: how can one design and implement such a "pull pipe" and
>> solve the problem I have of propagating state back to a previous
>> function.
>

Apologies for being so obtuse but I cannot to see how this solves my
problem. Please note that I am not well versed in functional programming
so that what I am asking may not be possible. Lets say I have a small
pipe of 3 actions:

let exp = a |> b |> c

a: requires the input of a state and outputs an event
b: requires input of a state and the event generated at that state and
outputs processed data
c: consumes n number elements of processed data and stops when it
requires no more such data

Note that "c" will "pull in" for example 10 states and check for
termination, "b" will therefore need "pull in" 10 events. Each time it
pulls in an event it generates a state. This last state must be made
available to "a" so that it may generate its next event.

The issue here is how can I implement this so that I can flexibly
configure experiments by "constructing" a chain of actions but still be
able to pass back the state to one of those actions. Something like:

let exp = a |> b (output 1 back to a) |> c

Regards,
Hugo F.

> Assume
>
> f : state_t -> state_t option
>
> is your state transformer, then
>
> let rec go state =
> match f state with
> | Some state -> go state
> | None -> ()
>
> will do it.
>

_______________________________________________

Vincent Aravantinos

unread,
Oct 10, 2007, 6:32:42 AM10/10/07
to Hugo Ferreira, caml...@yquem.inria.fr

Le 10 oct. 07 à 12:08, Hugo Ferreira a écrit :

> Apologies for being so obtuse but I cannot to see how this solves my
> problem. Please note that I am not well versed in functional
> programming
> so that what I am asking may not be possible. Lets say I have a small
> pipe of 3 actions:
>
> let exp = a |> b |> c
>
> a: requires the input of a state and outputs an event
> b: requires input of a state and the event generated at that state and
> outputs processed data
> c: consumes n number elements of processed data and stops when it
> requires no more such data
>
> Note that "c" will "pull in" for example 10 states and check for
> termination, "b" will therefore need "pull in" 10 events. Each time it
> pulls in an event it generates a state. This last state must be made
> available to "a" so that it may generate its next event.
>
> The issue here is how can I implement this so that I can flexibly
> configure experiments by "constructing" a chain of actions but
> still be
> able to pass back the state to one of those actions. Something like:
>
> let exp = a |> b (output 1 back to a) |> c

Just to be sure I understood well, here is a diagram:

--> a --> b -+-------------------------------------------------> output1
|
+--state1-> a --> b -+---------------------------->
output2
|
+-state2-> a --> b -+-------->
output3
|
...
->
outputn

|
|
|
V

c


Do you agree with this ? (n beeing a variable of course...)
Shall c also take the states ?

(I believe in good drawings to help finding an answer...)

Hugo Ferreira

unread,
Oct 10, 2007, 6:57:45 AM10/10/07
to Vincent Aravantinos, caml...@yquem.inria.fr
Hello,

Not quite. More like:

(_,s0)
-> a-> s0,e1 -> b -+--------------------------------------> s1
|
+--s1-> a -> s1,e2 -> b-+--------------> s2
|
...
-> sn
|
|
|
V
c

Note that "a" doesn't generates states "sn" it just passes it on.
It only generates events "en". "b" simple takes a state "sn-1" and the
events "en" and generates a new state "sn".

> Shall c also take the states ?
>

Yes. But the idea is to add other functions to the "pipe" that will
change states to other data types for further processing.

Note also that only the last function actually knows how much data is
required.

> (I believe in good drawings to help finding an answer...)

Well it certainly easier to express the flow of the data.

skaller

unread,
Oct 10, 2007, 11:01:07 AM10/10/07
to Hugo Ferreira, caml...@yquem.inria.fr
On Wed, 2007-10-10 at 11:08 +0100, Hugo Ferreira wrote:
> Hello,

>
> Apologies for being so obtuse but I cannot to see how this solves my
> problem.

> let exp = a |> b |> c


>
> a: requires the input of a state and outputs an event
> b: requires input of a state and the event generated at that state and
> outputs processed data
> c: consumes n number elements of processed data and stops when it
> requires no more such data

> Note that "c" will "pull in" for example 10 states and check for
> termination, "b" will therefore need "pull in" 10 events.

Functions cannot do that. You have to control invert.

A function is a slave, it is *called* with its argument.
you cant *read* the arguments.


--
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net

_______________________________________________

skaller

unread,
Oct 10, 2007, 11:57:07 AM10/10/07
to Hugo Ferreira, caml...@yquem.inria.fr, Raj Bandyopadhyay
On Thu, 2007-10-11 at 01:00 +1000, skaller wrote:
> On Wed, 2007-10-10 at 11:08 +0100, Hugo Ferreira wrote:
> > Hello,
>
> >
> > Apologies for being so obtuse but I cannot to see how this solves my
> > problem.
>
> > let exp = a |> b |> c

> A function is a slave, it is *called* with its argument.


> you cant *read* the arguments.

BTW: what you want is something like this 'concept demo'
I hacked up in Felix (notes below).

a -> b -> c -> d ->+
^ |
| |
+--------<---------+

////////////////////////////////////////////////////
// generate events 1 to limit
proc a
(
limit:ischannel[int],
chout: oschannel[int]
)
{
var event:int; var n:int;
forever {
read(&n,limit);
forall event in 1 upto n do
write(chout,event);
done;
};
}

// double it
proc b(chin: ischannel[int], chout: oschannel[int]) {
int event;
forever {
read(&event,chin);
write(chout,event*2);
};
}

// add 1
proc c(chin: ischannel[int], chout: oschannel[int]) {
int event;
forever {
read(&event,chin);
write(chout,event+1);
};
}

proc d
(
chin:ischannel[int],
limit: oschannel[int]
)
{
int count; int i; int event;
var total = 10;
while (total < 1000) {
println$ "subtotal " + str total;
n := total;
write(limit,total);
forall i in 1 upto n do
read(&event, chin);
//println$ f"Event %d = %d" (i,event);
total += event;
done;
};
println$ "total=" + str total;
}

proc pipeline() {
bin,aout := mk_ioschannel_pair[int]();
cin,bout := mk_ioschannel_pair[int]();
din,cout := mk_ioschannel_pair[int]();
limin,limout := mk_ioschannel_pair[int]();
spawn_fthread { a(limin, aout); };
spawn_fthread { b(bin, bout); };
spawn_fthread { c(cin, cout); };
spawn_fthread { d(din, limout); };
}

pipeline();
///////////////////////////////////////
$ f fl
subtotal 10
subtotal 130
total=17290
////////////////////////////////////////

Here we create procedures a,b,c,d which are templates
for "chips" with input and output "pins".

In the pipeline() procedure we create wires with named ends for input
and output, and plug them into instances of the 'chips'
to create a 'circuit'. (This is crude but it works and is
fully general).

In the pipeline the input state of 'a' is the 'limit' value,
which is written by 'd'. When 'd' gets the result sum, if it is
too small it writes the sum as the new limit back to the
chip 'a'.

Hugo Ferreira

unread,
Oct 11, 2007, 3:00:08 AM10/11/07
to skaller, caml...@yquem.inria.fr, Raj Bandyopadhyay
Hello,

skaller wrote:
> On Thu, 2007-10-11 at 01:00 +1000, skaller wrote:
>> On Wed, 2007-10-10 at 11:08 +0100, Hugo Ferreira wrote:
>>> Hello,
>>> Apologies for being so obtuse but I cannot to see how this solves my
>>> problem.
>>> let exp = a |> b |> c
>
>> A function is a slave, it is *called* with its argument.
>> you cant *read* the arguments.
>
> BTW: what you want is something like this 'concept demo'
> I hacked up in Felix (notes below).
>
> a -> b -> c -> d ->+
> ^ |
> | |
> +--------<---------+
>

Basically yes. Closer to this though:

a -> b -> c -> d ->+-> e -> f
^ |
| |
+--------<---------+


The solution below is basically the same suggestion I got (in Ocaml)
from someone else. I guess this is the way to go then.

Regards,
Hugo F.

_______________________________________________

skaller

unread,
Oct 11, 2007, 4:10:32 AM10/11/07
to Hugo Ferreira, caml...@yquem.inria.fr, Raj Bandyopadhyay
On Thu, 2007-10-11 at 07:57 +0100, Hugo Ferreira wrote:
> Hello,
>
> skaller wrote:
> > On Thu, 2007-10-11 at 01:00 +1000, skaller wrote:
> >> On Wed, 2007-10-10 at 11:08 +0100, Hugo Ferreira wrote:
> >>> Hello,
> >>> Apologies for being so obtuse but I cannot to see how this solves my
> >>> problem.
> >>> let exp = a |> b |> c
> >
> >> A function is a slave, it is *called* with its argument.
> >> you cant *read* the arguments.
> >
> > BTW: what you want is something like this 'concept demo'
> > I hacked up in Felix (notes below).
> >
> > a -> b -> c -> d ->+
> > ^ |
> > | |
> > +--------<---------+
> >
>
> Basically yes. Closer to this though:
>
> a -> b -> c -> d ->+-> e -> f
> ^ |
> | |
> +--------<---------+
>

I know the design I showed didn't match your specifications:
it was only intended as a (working) demo of the idea of
a 'chips and wires' model.

> The solution below is basically the same suggestion I got (in Ocaml)
> from someone else. I guess this is the way to go then.

Unfortunately (at least without control inversion patch) it is not
possible to do this in Ocaml without using pthreads.

It is possible to *emulate* it, as I mentioned, using some
combinator libraries, but to make this work you have to structure
your code in a rather 'peculiar' way to allow the combinators
to actually work: the combinator style approach has the disadvantage
(in Ocaml without control inversion patch) of an un-natural
programming form.

The pthreads/Event module based approach is fully natural
but doesn't scale because pthreads don't, and it is inefficient
because it synchronises using primitives designed to support
multi-processing when basic circuits do not need any
parallelism.

In addition, pthreads have a termination and deadlocking problem
the cooperative system does not: it cannot deadlock, and there
is no facility to explicitly terminate fibres -- they die when
they become unreachable, so the programmer simply has to ensure
there is no gratuitous visibility. Fibres CAN livelock/starve,
and sometimes you find they die from deadlock unexpectedly
due to a bug. The bottom line is that the chips and wires model
has nice properties BUT it is quite low level and requires
some care to ensure it will work properly. It is, however,
the only option for simulations with a high object count.
Pthreads fail on small numbers (a few K threads). Stack
swapping solutions cannot work on 32 bit machines. On 64 bit
machines they're more viable but either suffer a performance
hit copying the stack or a memory usage hit using VM paging.
[i.e. 4K on most systems, which could be way above the object
size which might be only a few bytes in a cellular automata]

Using the heap works best for large object counts, however
it requires continuation passing support of some kind.

I would have to mention Mlton in passing because it uses a rather
clever system with VM based stack swapping, but the stacks are
actually compacted like the heap: it is quite clever IMO.
I think Mlton also offers more or less transparent interfaces
so code can work with either fibres or pthreads in various mixes
without rewriting the algorithms, which is quite cool.
[But I'm no expert, perhaps Steven Weeks will comment more
authoritatively]

--
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net

_______________________________________________

Hugo Ferreira

unread,
Oct 11, 2007, 5:57:25 AM10/11/07
to skaller, caml...@yquem.inria.fr, Raj Bandyopadhyay
skaller wrote:
> On Thu, 2007-10-11 at 07:57 +0100, Hugo Ferreira wrote:
>> Hello,
>>
>> skaller wrote:
>>> On Thu, 2007-10-11 at 01:00 +1000, skaller wrote:
>>>> On Wed, 2007-10-10 at 11:08 +0100, Hugo Ferreira wrote:
>>>>> Hello,
>>>>> Apologies for being so obtuse but I cannot to see how this solves my
>>>>> problem.
>>>>> let exp = a |> b |> c
>>>> A function is a slave, it is *called* with its argument.
>>>> you cant *read* the arguments.
>>> BTW: what you want is something like this 'concept demo'
>>> I hacked up in Felix (notes below).
>>>
>>> a -> b -> c -> d ->+
>>> ^ |
>>> | |
>>> +--------<---------+
>>>
>> Basically yes. Closer to this though:
>>
>> a -> b -> c -> d ->+-> e -> f
>> ^ |
>> | |
>> +--------<---------+
>>
>
> I know the design I showed didn't match your specifications:
> it was only intended as a (working) demo of the idea of
> a 'chips and wires' model.
>

Understood.

>> The solution below is basically the same suggestion I got (in Ocaml)
>> from someone else. I guess this is the way to go then.
>
> Unfortunately (at least without control inversion patch) it is not
> possible to do this in Ocaml without using pthreads.
>
> It is possible to *emulate* it, as I mentioned, using some
> combinator libraries, but to make this work you have to structure
> your code in a rather 'peculiar' way to allow the combinators
> to actually work: the combinator style approach has the disadvantage
> (in Ocaml without control inversion patch) of an un-natural
> programming form.
>
> The pthreads/Event module based approach is fully natural
> but doesn't scale because pthreads don't, and it is inefficient
> because it synchronises using primitives designed to support
> multi-processing when basic circuits do not need any
> parallelism.
>

Actually if I am not mistaken the example I refer to was using
pthreads. When I read your code I assumed they were the equivalent of
pthreads or some lighter version (user land, green threads). I guess
this is not so.

As for combinators I had initially thought there would be some kind of
"functional magic" that could solve my problem without resorting to
heavier duty stuff such as process or threads (at least for now because
I am only testing ideas).

> In addition, pthreads have a termination and deadlocking problem
> the cooperative system does not: it cannot deadlock, and there
> is no facility to explicitly terminate fibres -- they die when
> they become unreachable, so the programmer simply has to ensure
> there is no gratuitous visibility. Fibres CAN livelock/starve,
> and sometimes you find they die from deadlock unexpectedly
> due to a bug. The bottom line is that the chips and wires model
> has nice properties BUT it is quite low level and requires
> some care to ensure it will work properly. It is, however,
> the only option for simulations with a high object count.
> Pthreads fail on small numbers (a few K threads). Stack
> swapping solutions cannot work on 32 bit machines. On 64 bit
> machines they're more viable but either suffer a performance
> hit copying the stack or a memory usage hit using VM paging.
> [i.e. 4K on most systems, which could be way above the object
> size which might be only a few bytes in a cellular automata]
>
> Using the heap works best for large object counts, however
> it requires continuation passing support of some kind.
>

Again I figured someone would already have such an example using CPS so
that I could use that without the trouble of learning the "low level"
stuff that "requires some care to ensure it will work properly".

> I would have to mention Mlton in passing because it uses a rather
> clever system with VM based stack swapping, but the stacks are
> actually compacted like the heap: it is quite clever IMO.
> I think Mlton also offers more or less transparent interfaces
> so code can work with either fibres or pthreads in various mixes
> without rewriting the algorithms, which is quite cool.
> [But I'm no expert, perhaps Steven Weeks will comment more
> authoritatively]
>

Hmmm... this is way over my head. I will stick to Ocaml and the simpler
coding. Appreciate your feedback and explanation.

Thanks.

Zheng Li

unread,
Oct 11, 2007, 7:16:49 AM10/11/07
to caml...@inria.fr
Hi,

Hugo Ferreira <h...@inescporto.pt> writes:
> My question is: how can one design and implement such a "pull pipe" and
> solve the problem I have of propagating state back to a previous
> function. If this is not possible functionally what other options do I
> have? Better yet, what is the better way to implement such a system?

It seems that you want to program in a dataflow paradigm in OCaml. You don't
have to use concurrent programming if you find it heavyweight, instead you
should use stream (or lazy, or other sth alike) which is already provided by
OCaml.

Usually, you'll define a set of combinators include: map, dup, pipe, filter,
until, combine/split, merge/switch etc to facile your work. The only difficulty
I can foresee is that OCaml only supports recursive value in a quite restrictive
form. E.g.

let rec s = [<'1; s>] or let rec s1 = [<'1; s2>] and s2 = map f s1

is not directly supported. One can make use of recursive function as
workaround, but the semantics may not always identical. However, if you have
control over your data structure, you can usually define your specific version
of stream type, then this won't be a problem any more.

In some dataflow languages I know, such kind of recursion is often represented
through a special form -- "delay" which is provided as system primitive. If
written in plain OCaml, the "delay" primitive won't be combinatorial as you
want, so you have to require programmers to handle it specially. Fortunately,
in most cases, a higer-level combinatorial form is usually sufficient, so that
you can use it to hide the "delay" with sth like "recur".

IIRC, OCaml was uses as the basis of some dataflow languages developed in
french universities. Maybe they can give you more suggestions.

HTH.

--
Zheng Li
http://www.pps.jussieu.fr/~li

Pietro Abate

unread,
Oct 11, 2007, 8:02:52 AM10/11/07
to caml...@yquem.inria.fr
Hi,

On Wed, Oct 10, 2007 at 11:56:02AM +0100, Hugo Ferreira wrote:
> >> a: requires the input of a state and outputs an event
> >> b: requires input of a state and the event generated at that state and
> >> outputs processed data
> >> c: consumes n number elements of processed data and stops when it
> >> requires no more such data
> >>
> >> Note that "c" will "pull in" for example 10 states and check for
> >> termination, "b" will therefore need "pull in" 10 events. Each time it
> >> pulls in an event it generates a state. This last state must be made
> >> available to "a" so that it may generate its next event.
> >>
> >> The issue here is how can I implement this so that I can flexibly
> >> configure experiments by "constructing" a chain of actions but still be
> >> able to pass back the state to one of those actions. Something like:
> >>
> >> let exp = a |> b (output 1 back to a) |> c

I'm not entirely sure this is correct. Note that I've used an exception
to get out of the loop just because I'm too lazy to wrap my head around
the exception monad. I'm also not sure that is the best way of using a
state monad... Any monad-experts out there to comment ?

This is the code:

type inputstate = int
type output = int
type final = int
type event = int

module StateMonadMake(T:sig type t end) =
struct
type 'state mt = 'state -> T.t * 'state

let return a = fun s -> a, s
let bind m f = fun s -> let a, s = m s in f a s
let fetch = fun s -> return s s
let store = fun s -> fun _ -> return () s
let modify f = fun s -> return () (f s)
end

module SM = StateMonadMake(struct type t = inputstate end)
exception Stop of final

let a (s : inputstate) : event = 1

let b (e : event) ( s : inputstate ) : (inputstate * output) =
match s with
0 -> print_endline "final state" ; (0,1)
|_ -> Printf.printf "at state %i\n" s ; (s-1,s+1)

let c ( l : output list ) : final =
List.iter print_int l ;
List.fold_left (+) 0 l

let rec exp inputstate =
SM.bind inputstate (fun state ->
let newevent = a state in
let (newstate,newdata) = b newevent state in
SM.bind (SM.modify (fun olddata -> newdata::olddata)) (fun _ ->
if newstate = 0 then
SM.bind (SM.fetch) (fun data ->
raise ( Stop ( c (data) ))
)
else exp (SM.return newstate)
)
)
;;

let run =
try exp (SM.return 10) []
with Stop(i) -> Printf.printf "final %i\n" i

$ocaml hf.ml
at state 10
at state 9
at state 8
at state 7
at state 6
at state 5
at state 4
at state 3
at state 2
at state 1
234567891011final 65


pietro

--
++
++ "All great truths begin as blasphemies." -George Bernard Shaw
++ Please avoid sending me Word or PowerPoint attachments.
See http://www.gnu.org/philosophy/no-word-attachments.html

skaller

unread,
Oct 11, 2007, 9:48:59 AM10/11/07
to Hugo Ferreira, caml...@yquem.inria.fr, Raj Bandyopadhyay
On Thu, 2007-10-11 at 10:54 +0100, Hugo Ferreira wrote:
> skaller wrote:

> > The pthreads/Event module based approach is fully natural
> > but doesn't scale because pthreads don't, and it is inefficient
> > because it synchronises using primitives designed to support
> > multi-processing when basic circuits do not need any
> > parallelism.
> >
>
> Actually if I am not mistaken the example I refer to was using
> pthreads. When I read your code I assumed they were the equivalent of
> pthreads or some lighter version (user land, green threads). I guess
> this is not so.

Yes they're user land (green) threads, cooperative multi-tasking,
fibres, or whatever you want to call them.

--
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net

_______________________________________________

Hugo Ferreira

unread,
Oct 11, 2007, 9:54:28 AM10/11/07
to Zheng Li, caml...@inria.fr
Hello,

Zheng Li wrote:
> Hi,
>
> Hugo Ferreira <h...@inescporto.pt> writes:
>> My question is: how can one design and implement such a "pull pipe" and
>> solve the problem I have of propagating state back to a previous
>> function. If this is not possible functionally what other options do I
>> have? Better yet, what is the better way to implement such a system?
>
> It seems that you want to program in a dataflow paradigm in OCaml. You don't
> have to use concurrent programming if you find it heavyweight, instead you
> should use stream (or lazy, or other sth alike) which is already provided by
> OCaml.
>

Original idea was to use lazy data/functions and composition of
functions to do this. Issue is how to pass back a value so as to provide
feedback and alter the stream's output.

> Usually, you'll define a set of combinators include: map, dup, pipe, filter,
> until, combine/split, merge/switch etc to facile your work.

Hmmm... these combinators seem to be well understood. Know of any
description (article, blog, etc) of these in a functional programming
setting?

> The only difficulty
> I can foresee is that OCaml only supports recursive value in a quite restrictive
> form. E.g.
>
> let rec s = [<'1; s>] or let rec s1 = [<'1; s2>] and s2 = map f s1
>
> is not directly supported.

I see that recursion as shown above could be useful: one of the
outputs would simply be an input to another stream generator.

> One can make use of recursive function as
> workaround, but the semantics may not always identical. However, if you have
> control over your data structure,

This is the case.

> you can usually define your specific version
> of stream type, then this won't be a problem any more.
>
> In some dataflow languages I know, such kind of recursion is often represented
> through a special form -- "delay" which is provided as system primitive. If
> written in plain OCaml, the "delay" primitive won't be combinatorial as you
> want, so you have to require programmers to handle it specially. Fortunately,
> in most cases, a higer-level combinatorial form is usually sufficient, so that
> you can use it to hide the "delay" with sth like "recur".
>

I (think) I see what you mean. Things seem to be coming together. What
you are saying is that I could use this "delay" so that only when the
value is available would it be "passed back" to the "stream generator"
thereby providing the "feedback" I need. In fact this "delay" is more
general and could be used to define various types of flows. Nice!

Assuming a standard definition of list, do you have any example of how
one would go about implementing this "delay"? I need to gives this some
thought.

> IIRC, OCaml was uses as the basis of some dataflow languages developed in
> french universities. Maybe they can give you more suggestions.
>
> HTH.

It has.

Thanks.

Hugo Ferreira

unread,
Oct 11, 2007, 9:54:38 AM10/11/07
to Pietro Abate, caml...@yquem.inria.fr
Hi,

Pietro Abate wrote:
> Hi,
>
> On Wed, Oct 10, 2007 at 11:56:02AM +0100, Hugo Ferreira wrote:
>>>> a: requires the input of a state and outputs an event
>>>> b: requires input of a state and the event generated at that state and
>>>> outputs processed data
>>>> c: consumes n number elements of processed data and stops when it
>>>> requires no more such data
>>>>
>>>> Note that "c" will "pull in" for example 10 states and check for
>>>> termination, "b" will therefore need "pull in" 10 events. Each time it
>>>> pulls in an event it generates a state. This last state must be made
>>>> available to "a" so that it may generate its next event.
>>>>
>>>> The issue here is how can I implement this so that I can flexibly
>>>> configure experiments by "constructing" a chain of actions but still be
>>>> able to pass back the state to one of those actions. Something like:
>>>>
>>>> let exp = a |> b (output 1 back to a) |> c
> I'm not entirely sure this is correct. Note that I've used an exception
> to get out of the loop just because I'm too lazy to wrap my head around
> the exception monad. I'm also not sure that is the best way of using a
> state monad... Any monad-experts out there to comment ?
>

I am going to have to look at this very carefully (read: learn something
about monads). Comment below.

I can however see that "exp" seems to be a loop. Cannot see however were
you tie the latest state of "a" with the next use of "b" 8-(. I will
really have to see how this stuff works.

Thanks.

Hugo F.

Pietro Abate

unread,
Oct 11, 2007, 10:21:12 AM10/11/07
to caml...@yquem.inria.fr
On Thu, Oct 11, 2007 at 02:52:13PM +0100, Hugo Ferreira wrote:
> > I'm not entirely sure this is correct. Note that I've used an exception
> > to get out of the loop just because I'm too lazy to wrap my head around
> > the exception monad. I'm also not sure that is the best way of using a
> > state monad... Any monad-experts out there to comment ?
> I am going to have to look at this very carefully (read: learn something
> about monads). Comment below.
>
> > This is the code:
[...]

> > let rec exp inputstate =
> > SM.bind inputstate (fun state ->
> > let newevent = a state in
> > let (newstate,newdata) = b newevent state in
> > SM.bind (SM.modify (fun olddata -> newdata::olddata)) (fun _ ->
> > if newstate = 0 then
> > SM.bind (SM.fetch) (fun data ->
> > raise ( Stop ( c (data) ))
> > )
> > else exp (SM.return newstate)
> > )
> > )
>
> I can however see that "exp" seems to be a loop. Cannot see however were
> you tie the latest state of "a" with the next use of "b" 8-(. I will
> really have to see how this stuff works.

There are two states. One is the state of the state monad, that is hidden and
that is basically the list of partial results. The other one is the state of
the function (your state), that is explicit. the latest explicit state is the
variable "state" and the new state, result of the function b, is "newstate", that is
passed back in the loop with a recursive call. To avoid the (horrible)
exception in the middle of the computation, you can try to wrap the state monad
with and exception monad, so to make it more elegant. This is a simple
exception monad functor that you can use to compose the two monads
together.

module ExceptionMonadMake(T:sig type t end) =
struct
type mt = Just of T.t| Nothing
let return a = Just a


let bind m f =

match m with
|Just v -> f v
|Nothing -> Nothing
let mzero = Nothing
let mplus = function
|Just v -> fun _ -> Just v
|Nothing -> fun m -> m
let trywith = mplus
let lift f m = bind m f
end

Something that I haven't figure out yet is how to encode branching
computations using the same pattern to implement a finite state
machine.

pietro

Zheng Li

unread,
Oct 15, 2007, 7:03:22 PM10/15/07
to caml...@inria.fr

Hi,

Hugo Ferreira <h...@inescporto.pt> writes:
> Hmmm... these combinators seem to be well understood. Know of any
> description (article, blog, etc) of these in a functional programming
> setting?

These combinators pervasively exist in functional languages and other
declarative style languages. There's no authoritative definition though,
they vary from language to language, with some slight differences.

> I see that recursion as shown above could be useful: one of the
> outputs would simply be an input to another stream generator.

Yes. This _could_ be directly simulated with OCaml's recursive values if not
for the restriction I mentioned before.

> I (think) I see what you mean. Things seem to be coming together. What
> you are saying is that I could use this "delay" so that only when the
> value is available would it be "passed back" to the "stream generator"
> thereby providing the "feedback" I need. In fact this "delay" is more
> general and could be used to define various types of flows. Nice!

The "delay" like facilities are usually provided as language primitives in
dataflow languages, not in the library space. I can't figure out how to
simulate it through plain OCaml and still keeping a combinatorial interface at
the same time. I can image some workarounds to relax the restriction: recursive
function, reference, variants, but all of them come with some syntactic burdens
and can hardly used as combinators directly. On the other hand, there is still
some possibility of making camlp4 extension to do that. I just haven't got
chance to do any investigation on that.

Btw, I just cleaned up some old code and will release it right now. I'm not
sure whether it can help directly in your case, but I hope so.

Regards

_______________________________________________

Hugo Ferreira

unread,
Oct 22, 2007, 3:49:06 AM10/22/07
to Zheng Li, caml...@inria.fr
Hi Zheng,

Apologies for not answering earlier (Took a fee days off).
I am going to look at your code and see how that works.

Thanks once again.
Hugo F.

_______________________________________________

0 new messages