Mailing list for all users of the OCaml language and system.
 help / color / mirror / Atom feed
* Language Design
@ 2000-08-21 21:44 David McClain
  2000-08-23  5:55 ` John Max Skaller
  0 siblings, 1 reply; 13+ messages in thread
From: David McClain @ 2000-08-21 21:44 UTC (permalink / raw)
  To: caml-list

John Max Skaller said:
> I am designing a programming language (the compiler is written
in ocaml) which is a procedural language with 'purely functional'
expressions (using eager evaluation). Function closures can
access their context, which procedural statements my change between
building the closure and evaulating it. Procedural closures may
mutate their environment.

DM says:

I, for one, have fought for many years with languages that insisted on a
division between functions and procedures as you describe them. I have found
the unified "everything is a function" approach to be most appealing. In
particular, the worst offenders are those languages that insist on syntactic
distinctions such as Fortran, RSI/IDL, and Basic. I cannot be alone in
having difficulty remembering when a routine, whose result I don't really
need, is to be called as a function, or as a procedure.

I hope you find an answer to your question, but I do not look forward to
another such language.

Sincerely

David McClain, Sr. Scientist, Raytheon Systems Co., Tucson, AZ




^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-21 21:44 Language Design David McClain
@ 2000-08-23  5:55 ` John Max Skaller
  2000-08-24  9:12   ` Francois Pottier
  0 siblings, 1 reply; 13+ messages in thread
From: John Max Skaller @ 2000-08-23  5:55 UTC (permalink / raw)
  To: David McClain; +Cc: caml-list

David McClain wrote:

> I, for one, have fought for many years with languages that insisted on a
> division between functions and procedures as you describe them. I have found
> the unified "everything is a function" approach to be most appealing. In
> particular, the worst offenders are those languages that insist on syntactic
> distinctions such as Fortran, RSI/IDL, and Basic. I cannot be alone in
> having difficulty remembering when a routine, whose result I don't really
> need, is to be called as a function, or as a procedure.

There are two reasons for the distinction. The crucial one is this:
my translator performs an operation called 'control inversion',
in which a primitive 'read x', which reads input, is implemented
by returning a continuation, that is, by yielding control
and waiting until the input is available. Any procedure containing
a read (directly or indirectly on the call chain) must also return
a continuation (which is immediately invoked) so that the dynamic 
call chain is not represented on the machine stack.

This technique allows a dispatcher to _call_ the program with messages,
that is, it translates an algorithmic form of the code into
an event driven form. This allows a program handling millions
of instances of something (telephone calls in my case), to dispatch
in log n time (amortised constant time in fact), rather than
the linear time required for OS threads. [the alternative,
writing event driven code, is a severe regression back to the bad
old days of totally unstructured coding]

On the other hand, returning continuations has a high constant
time overhead. To solve this problem, purely functional code
is executed using the machine stack.

The second reason for the distinction is the 'usual' one:
purely functional code has a useful property, namely
referential transparency.

[Technically, the identification of 'needs to be control inverted'
with 'procedure' is incorrect: only some procedures can lead
to elaboration of the read primitive: I plan to handle this later
by analysis and optimisation, but without a further distinction
in the procedure type, this analysis cannot cross compilation
unit boundaries, and I suspect that users will be less than 
happy with two kinds of procedures as well as functions :-]

What is _actually_ required is a seamless way to integrate
stateful and function code: the recent (obvious :-) discovery
that the basic duality principle of category theory when applied
to functional theory yields a stateful theory promises
to yield significant progress in the near future.
But this is too cutting edge for me to try for in what my employer
thinks is a simple 4GL for handling telephone calls. :-)

-- 
John (Max) Skaller, mailto:skaller@maxtal.com.au
10/1 Toxteth Rd Glebe NSW 2037 Australia voice: 61-2-9660-0850
checkout Vyper http://Vyper.sourceforge.net
download Interscript http://Interscript.sourceforge.net



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-23  5:55 ` John Max Skaller
@ 2000-08-24  9:12   ` Francois Pottier
  2000-08-24 20:16     ` John Max Skaller
  0 siblings, 1 reply; 13+ messages in thread
From: Francois Pottier @ 2000-08-24  9:12 UTC (permalink / raw)
  To: John Max Skaller; +Cc: caml-list, François Pottier


John,

On Wed, Aug 23, 2000 at 03:55:36PM +1000, John Max Skaller wrote:
> What is _actually_ required is a seamless way to integrate
> stateful and function code:

Have you thought about employing some kind of monadic type system?
The type system would allow you to isolate those program parts which
eventually involve `read' (and thus must be control-inverted during
compilation) from those which do not (and thus may be compiled in
direct style).

I am no expert in monads, but this seems to sound rather natural.
Maybe a look at how Haskell is typed and compiled may help?

-- 
François Pottier
Francois.Pottier@inria.fr
http://pauillac.inria.fr/~fpottier/



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-24  9:12   ` Francois Pottier
@ 2000-08-24 20:16     ` John Max Skaller
  2000-08-25  9:52       ` Andreas Rossberg
  2000-08-25 15:41       ` Jerome Vouillon
  0 siblings, 2 replies; 13+ messages in thread
From: John Max Skaller @ 2000-08-24 20:16 UTC (permalink / raw)
  To: Francois.Pottier; +Cc: caml-list

Francois Pottier wrote:
 
> On Wed, Aug 23, 2000 at 03:55:36PM +1000, John Max Skaller wrote:
> > What is _actually_ required is a seamless way to integrate
> > stateful and function code:
> 
> Have you thought about employing some kind of monadic type system?

	Yes, but I don't know enough to do it at the moment.
[Also, it turns out monads are not general enough to write
web services in, which puts me off a bit]

-- 
John (Max) Skaller, mailto:skaller@maxtal.com.au
10/1 Toxteth Rd Glebe NSW 2037 Australia voice: 61-2-9660-0850
checkout Vyper http://Vyper.sourceforge.net
download Interscript http://Interscript.sourceforge.net



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-24 20:16     ` John Max Skaller
@ 2000-08-25  9:52       ` Andreas Rossberg
  2000-08-27 22:00         ` John Max Skaller
  2000-08-25 15:41       ` Jerome Vouillon
  1 sibling, 1 reply; 13+ messages in thread
From: Andreas Rossberg @ 2000-08-25  9:52 UTC (permalink / raw)
  To: John Max Skaller; +Cc: caml-list

John Max Skaller wrote:
> 
> Francois Pottier wrote:
> >
> > Have you thought about employing some kind of monadic type system?
> 
>         Yes, but I don't know enough to do it at the moment.
> [Also, it turns out monads are not general enough to write
> web services in, which puts me off a bit]

The following tutorial gives quite a comprehensive explanation of how to
integrate I/O, stateful computation, and stuff into a purely functional
language using Monads. And coincidentally it uses a web server as a
running example ;-)

	http://research.microsoft.com/Users/simonpj/#marktoberdorf

-- 
Andreas Rossberg, rossberg@ps.uni-sb.de

:: be declarative. be functional. just be. ::



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-24 20:16     ` John Max Skaller
  2000-08-25  9:52       ` Andreas Rossberg
@ 2000-08-25 15:41       ` Jerome Vouillon
  2000-08-27 22:21         ` John Max Skaller
  1 sibling, 1 reply; 13+ messages in thread
From: Jerome Vouillon @ 2000-08-25 15:41 UTC (permalink / raw)
  To: John Max Skaller, Francois.Pottier; +Cc: caml-list

On Fri, Aug 25, 2000 at 06:16:06AM +1000, John Max Skaller wrote:
> Francois Pottier wrote:
>  
> > On Wed, Aug 23, 2000 at 03:55:36PM +1000, John Max Skaller wrote:
> > > What is _actually_ required is a seamless way to integrate
> > > stateful and function code:
> > 
> > Have you thought about employing some kind of monadic type system?
> 
> 	Yes, but I don't know enough to do it at the moment.
> [Also, it turns out monads are not general enough to write
> web services in, which puts me off a bit]

I think you should really consider using monads. Here is an example.

We define a value of type void to be either a continuation expecting a
string or a final function that do not expect anything.

    type void = Cont of (string -> void)
              | Term of (unit -> unit)

This is a procedure that does nothing.

    let unit : void = Term (fun () -> ())

And here is a possible implementation for read: the input string is
assigned to v and then there is nothing more to do.

    let read (v : string ref) : void = Cont (fun s -> v := s; unit)

The following combinator takes two procedures p and p' and make them
be evaluated in order.

    let rec seq (p : void) (p': void) : void =
      match p, p' with
        Cont c, _ ->
          Cont (fun s -> seq (c s) p')
      | Term t, Cont c ->
          Cont (fun s -> t (); c s)
      | Term t, Term t' ->
          Term (fun () -> t (); t' ())

Finally, we have an operator to assign a value v to a reference x.

    let set (x : 'a ref) (v : unit -> 'a) : void = Term (fun () -> x := v ())

Now we can for instance define a procedure that reads to strings and
returns their concatenation. This procedure does not need to know the
actual definition of type void.

    let read2 x =
      let a = ref "" in let b = ref "" in
      seq (read a) (seq (read b) (set x (fun () -> !a ^ !b)))

You can also use some symbols to make it more readable:

    let ($) = seq
    let (-<-) = set
    let read2 x =
      let a = ref "" in
      let b = ref "" in
      read a $
      read b $
      x -<- (fun () -> !a ^ !b)

We can try this procedure. First we define an evaluator. It takes the
input stream and a procedure call as inputs.

    let rec eval l p =
      match l, p with
        _,      Term t -> t ()
      | s :: r, Cont c -> eval r (c s)
      | _              -> ((* Stuck evaluation *))

Then we evaluate read2 when two strings "a" and "b" are given as
input:

  let x = ref "" in eval ["a"; "b"] (read2 x); !x

-- Jerome



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-25  9:52       ` Andreas Rossberg
@ 2000-08-27 22:00         ` John Max Skaller
  2000-08-28 23:11           ` Daan Leijen
  0 siblings, 1 reply; 13+ messages in thread
From: John Max Skaller @ 2000-08-27 22:00 UTC (permalink / raw)
  To: Andreas Rossberg; +Cc: caml-list

Andreas Rossberg wrote:

> > [Also, it turns out monads are not general enough to write
> > web services in, which puts me off a bit]
> 
> The following tutorial gives quite a comprehensive explanation of how to
> integrate I/O, stateful computation, and stuff into a purely functional
> language using Monads. And coincidentally it uses a web server as a
> running example ;-)
> 
>         http://research.microsoft.com/Users/simonpj/#marktoberdorf

Thanks. Now, somewhere linked to the Haskell web site,
is an article about 'Arrows', which explains why it was found
Monads are inadequate. I recall the issue was related
to interfacing to CGI scripts and preserving state between
interactions. Sorry I don't have URL handy :-(

-- 
John (Max) Skaller, mailto:skaller@maxtal.com.au
10/1 Toxteth Rd Glebe NSW 2037 Australia voice: 61-2-9660-0850
checkout Vyper http://Vyper.sourceforge.net
download Interscript http://Interscript.sourceforge.net



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-25 15:41       ` Jerome Vouillon
@ 2000-08-27 22:21         ` John Max Skaller
  0 siblings, 0 replies; 13+ messages in thread
From: John Max Skaller @ 2000-08-27 22:21 UTC (permalink / raw)
  To: Jerome Vouillon; +Cc: Francois.Pottier, caml-list

Jerome Vouillon wrote:

> I think you should really consider using monads. Here is an example.

I will have to study this example in more detail: thank you very
much for spending the time writing it. My translator generates C++,
but it looks as if the generated code follows the pattern below.
 
> We define a value of type void to be either a continuation expecting a
> string or a final function that do not expect anything.
> 
>     type void = Cont of (string -> void)
>               | Term of (unit -> unit)
> 
> This is a procedure that does nothing.

My equivalent: a pointer to a C++ object of class 'continuation_t' 
is returned when reading is desired, the dispatcher comes back 
later with the message and stores it in the continuation object. 
If there is no work to do, the routine returns a null pointer.

In fact, each procedure call returns control, and a flag tells whether
a read is desired, or whether to call the returned continuation
immediately.

> We can try this procedure. First we define an evaluator. It takes the
> input stream and a procedure call as inputs.
> 
>     let rec eval l p =
>       match l, p with
>         _,      Term t -> t ()
>       | s :: r, Cont c -> eval r (c s)
>       | _              -> ((* Stuck evaluation *))
> 
> Then we evaluate read2 when two strings "a" and "b" are given as
> input:
> 
>   let x = ref "" in eval ["a"; "b"] (read2 x); !x

This is very nice. It's much less code than my C++ version :-)

-- 
John (Max) Skaller, mailto:skaller@maxtal.com.au
10/1 Toxteth Rd Glebe NSW 2037 Australia voice: 61-2-9660-0850
checkout Vyper http://Vyper.sourceforge.net
download Interscript http://Interscript.sourceforge.net



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-08-27 22:00         ` John Max Skaller
@ 2000-08-28 23:11           ` Daan Leijen
  0 siblings, 0 replies; 13+ messages in thread
From: Daan Leijen @ 2000-08-28 23:11 UTC (permalink / raw)
  To: John Max Skaller; +Cc: caml-list

> Thanks. Now, somewhere linked to the Haskell web site,
> is an article about 'Arrows', which explains why it was found
> Monads are inadequate. I recall the issue was related
> to interfacing to CGI scripts and preserving state between
> interactions. Sorry I don't have URL handy :-(

Hello John,

The excellent article about arrows was written by John Hughes:
http://www.cs.chalmers.se/~rjmh/

I don't think that the article says that "Monads are inadequate"
(since monads are more general than arrows) but you can say
that Arrows are sometimes a better choice than monads depending
on your problem domain.

I think that in general Monads are easier to use (and understand) than arrows
and would urge you to try the monadic way first.  I believe that there are
only 2 significant reasons why one should prefer arrows over monads.

*The first reason is about control over evalutation time. Let me elaborate
this with an example of an arrow-style parser (1) and a monadic style parser (2).
The main operators of the monadic parser are return and bind:

return :: a -> Parser a
(>>=) :: Parser a -> (a -> Parser b) -> Parser b

The main operators of the arrow style parser are also a return (succeed) and some flavor of bind:

succeed :: a -> Parser a
(<*>)    :: Parser a -> Parser (a->b) -> Parser b

Now, from the type of the monadic bind, it becomes clear that a program can never access the
second parser (Parser b) until you have executed the first one, since the second one depends on
the returned runtime value 'a'.  Not so for the arrow style combinator. Allthough you still have to
execute the parsers to get the runtime values, it is possible to do something with the "Parser x"
data type before actually parsing anything.
This is exactly what Doaiste Swierstra does in his paper (1) to construct parse tables before
running the parser.

Arrow style parser can only parse context-free grammars  (since a parser cannot depend on the result
of another parser) whereas Monadic style parsers can parse any (even a context-sensitive) grammar.

The second reason for choosing arrow style combinators is for finer control about life-times.
I will elaborate on this using the CGI example. The example of John Hughes is something
like this:

test = arr (\z -> "give the question ?") >>> ask >>>
         (arr id &&& ask) >>>
         arr (\(q,a) -> "The answer to '" ++ q ++ "' is " ++ a)

it first sends the string "give the question" over to the client (ask), the response is kept in two
places (&&&), one just to send it to the third action (arr id) and one where the response is
immediately send to the client (ask), the result of this ((q,a)) is then printed.

Note that the lifetime of each value is kept within the function in the 'arr' combinator. (=
succeed).
That is why we need to explicitly thread the response through the second action with the "arr id"
expression,
in order to get it finally in the "q" of the last action. By being so explicit about the lifetimes,
it is possible
to only save the minimal state necessary between client/server interactions in the CGI problem
domain.

With monads, each time we bind a value, the values will be accessible by all following actions. The
same
CGI example in monadic style looks easier in my opinion:

test   = do{ question <- ask "what is the question ?"
                ; answer   <- ask question
                ; return ("the answer to '" ++ question ++ "' is " ++ answer)
                }

The same techniques to implement the CGI server work also with the monadic style, the only
difference is
that we now always save the entire set of values that could be accessed, instead of a more minimal
set.
For example, we don't have to thread the value of "question" around, it can be immediately accessed
on the third action.  (I have a small example implementation of both a monadic and arrow style CGI
framework
that works with Hugs, if you are interested in the different approaches it might be interesting to
look at it,
just send me an email)


 Pheew, I hope this helps you in determining the best implementation technique.
For now, I would advise you to stick with monads and adapt later if necessary.

All the best,
    Daan.

(1) Doaitse Swierstra and Luc Duponcheel. (1996)
Deterministic, Error-Correcting Combinator Parsers.
Advanced Functional Programming. LNCS 1129: 185-207.
http://www.cs.uu.nl/groups/ST/Software.

(2) Graham Hutton and Erik Meijer. (1996)
Monadic Parser Combinators.
Technical report NOTTCS-TR-96-4. Department of Computer Science, University of Nottingham.
http://www.cs.nott.ac.uk/Department/Staff/gmh/monparsing.ps.
(this article is highly recommended :-)



> --
> John (Max) Skaller, mailto:skaller@maxtal.com.au
> 10/1 Toxteth Rd Glebe NSW 2037 Australia voice: 61-2-9660-0850
> checkout Vyper http://Vyper.sourceforge.net
> download Interscript http://Interscript.sourceforge.net
>
>



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
       [not found]   ` <39B5DD81.E2500203@maxtal.com.au>
@ 2000-09-06  6:33     ` Marcin 'Qrczak' Kowalczyk
  0 siblings, 0 replies; 13+ messages in thread
From: Marcin 'Qrczak' Kowalczyk @ 2000-09-06  6:33 UTC (permalink / raw)
  To: caml-list

Wed, 06 Sep 2000 17:00:33 +1100, John Max Skaller <skaller@maxtal.com.au> pisze:

> A smarter implementation would be lazy, and buffer all data which
> was actually read, until it could no longer be accessed.

Assuming that primitive tape reading lives in the IO monad,
implementation of this reading would have to rely on unofficial
constructs that allow escaping from IO, or at least delaying
an IO action until a value is evaluated.

The function would no longer be pure, even though its type says so.
Examining its result causes a side effect of reading the tape further.
This light effect may nevertheless matter.

This is the case of Haskell's reading of whole files, which is lazy and
unimplementable using official single-character IO primitives. It has
its problems, recently discussed: what if I later write to that file
back? The meaning may depend on how much of the input was evaluated.
Implementations should probably detect this case and read the remaining
input immediately...

Providing input from I/O as a lazy list is very convenient but
unfortunately tricky.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-09-01 11:57 Dave Berry
  2000-09-01 17:48 ` Markus Mottl
@ 2000-09-01 19:12 ` Marcin 'Qrczak' Kowalczyk
       [not found]   ` <39B5DD81.E2500203@maxtal.com.au>
  1 sibling, 1 reply; 13+ messages in thread
From: Marcin 'Qrczak' Kowalczyk @ 2000-09-01 19:12 UTC (permalink / raw)
  To: caml-list; +Cc: Dave Berry

Fri, 1 Sep 2000 12:57:13 +0100, Dave Berry <dave@kal.com> pisze:

> Given a value in a monad, e.g. IO v, how can I remove v from the Monad?

For Haskell's IO monad, you don't have a function of type IO v -> v.
IO is carried up to main, the "action of the whole program".

Other monads may or may not provide a similar function.

> Surely this would be required to seamlessly integrate stateful and
> functional code?

In a pure language it is not possible to create a function which does
I/O when applied. If an operation may do I/O, it is reflected in its
type and usage. It may be considered a good thing, and is practically
a must in a lazy language.

In some Haskell implementations there is monad called ST (state
transformer) which provides mutable references and arrays, and can
be wrapped in a pure function. Not all stateful code requires IO.

Actually in some implementations there is unsafePerformIO :: IO a -> a
but it's, well, unsafe. It's sometimes very useful for real life
problems.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: Language Design
  2000-09-01 11:57 Dave Berry
@ 2000-09-01 17:48 ` Markus Mottl
  2000-09-01 19:12 ` Marcin 'Qrczak' Kowalczyk
  1 sibling, 0 replies; 13+ messages in thread
From: Markus Mottl @ 2000-09-01 17:48 UTC (permalink / raw)
  To: Dave Berry; +Cc: OCAML

On Fri, 01 Sep 2000, Dave Berry wrote:
> Given a value in a monad, e.g. IO v, how can I remove v from the Monad?
> Surely this would be required to seamlessly integrate stateful and
> functional code?

Well, that's the idea behind monads that you (normally) shouldn't: you must
not be able to run a function with the same arguments and get a different
result. That's the way I/O-monads work in e.g. Haskell.

However, there are different monads, e.g. "state monads", which allow for a
function that takes a state, the computation (in the monad) and runs the
computation on (in) the given state, returning the result as "normal"
value. This does not circumvent referential transparancy unless running the
computation in the monad in the same state can yield different results
(e.g. you use I/O, random numbers, etc.).

You can find an OCaml-implementation of state monads here (with an example
application, namely an interpreter for a simple imperative language):

  http://miss.wu-wien.ac.at/~mottl/ocaml_sources/IMP-1.0-2/monad

E.g. the following program:

---------------------------------------------------------------------------
open State_monad
open Printf

let test =
  fetchST                                     >>= fun state ->
  unitST (printf "First state: %d\n" state)   >>
  assignST 2                                  >>
  unitST "is 42"                              >>= fun answer ->
  unitST (printf "Answer %s\n" answer)        >>
  fetchST                                     >>= fun state ->
  unitST (printf "Second state: %d\n" state)  >>
  assignST 3

let _ = printf "State in monad: %d\n" (initST 1 (test >> fetchST))
---------------------------------------------------------------------------

prints:

  First state: 1
  Answer is 42
  Second state: 2
  State in monad: 3

As you seen in the code, the state is propagated implicitely. Only when you
want to "look" at it, you use "fetchST", and you use "assignST" to
overwrite it.

"initST" does what you asked for: it "runs" the computation in "test"
starting with a specific state (the integer 1) and returns whatever the
monad wants to return. In this case we force the monad to return the
internal state by attaching "fetchST" to "test".

Best regards,
Markus Mottl

-- 
Markus Mottl, mottl@miss.wu-wien.ac.at, http://miss.wu-wien.ac.at/~mottl



^ permalink raw reply	[flat|nested] 13+ messages in thread

* RE: Language Design
@ 2000-09-01 11:57 Dave Berry
  2000-09-01 17:48 ` Markus Mottl
  2000-09-01 19:12 ` Marcin 'Qrczak' Kowalczyk
  0 siblings, 2 replies; 13+ messages in thread
From: Dave Berry @ 2000-09-01 11:57 UTC (permalink / raw)
  To: caml-list

Given a value in a monad, e.g. IO v, how can I remove v from the Monad?
Surely this would be required to seamlessly integrate stateful and
functional code?

Dave the ingenue.


-----Original Message-----
From: Jerome Vouillon [mailto:Jerome.Vouillon@inria.fr]
Sent: Friday, August 25, 2000 4:42 PM
To: John Max Skaller; Francois.Pottier@inria.fr
Cc: caml-list@inria.fr
Subject: Re: Language Design


On Fri, Aug 25, 2000 at 06:16:06AM +1000, John Max Skaller wrote:
> Francois Pottier wrote:
>  
> > On Wed, Aug 23, 2000 at 03:55:36PM +1000, John Max Skaller wrote:
> > > What is _actually_ required is a seamless way to integrate
> > > stateful and function code:
> > 
> > Have you thought about employing some kind of monadic type system?
> 
> 	Yes, but I don't know enough to do it at the moment.
> [Also, it turns out monads are not general enough to write
> web services in, which puts me off a bit]

I think you should really consider using monads. Here is an example.

We define a value of type void to be either a continuation expecting a
string or a final function that do not expect anything.

    type void = Cont of (string -> void)
              | Term of (unit -> unit)

This is a procedure that does nothing.

    let unit : void = Term (fun () -> ())

And here is a possible implementation for read: the input string is
assigned to v and then there is nothing more to do.

    let read (v : string ref) : void = Cont (fun s -> v := s; unit)

The following combinator takes two procedures p and p' and make them
be evaluated in order.

    let rec seq (p : void) (p': void) : void =
      match p, p' with
        Cont c, _ ->
          Cont (fun s -> seq (c s) p')
      | Term t, Cont c ->
          Cont (fun s -> t (); c s)
      | Term t, Term t' ->
          Term (fun () -> t (); t' ())

Finally, we have an operator to assign a value v to a reference x.

    let set (x : 'a ref) (v : unit -> 'a) : void = Term (fun () -> x := v
())

Now we can for instance define a procedure that reads to strings and
returns their concatenation. This procedure does not need to know the
actual definition of type void.

    let read2 x =
      let a = ref "" in let b = ref "" in
      seq (read a) (seq (read b) (set x (fun () -> !a ^ !b)))

You can also use some symbols to make it more readable:

    let ($) = seq
    let (-<-) = set
    let read2 x =
      let a = ref "" in
      let b = ref "" in
      read a $
      read b $
      x -<- (fun () -> !a ^ !b)

We can try this procedure. First we define an evaluator. It takes the
input stream and a procedure call as inputs.

    let rec eval l p =
      match l, p with
        _,      Term t -> t ()
      | s :: r, Cont c -> eval r (c s)
      | _              -> ((* Stuck evaluation *))

Then we evaluate read2 when two strings "a" and "b" are given as
input:

  let x = ref "" in eval ["a"; "b"] (read2 x); !x

-- Jerome



^ permalink raw reply	[flat|nested] 13+ messages in thread

end of thread, other threads:[~2000-09-06 19:42 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2000-08-21 21:44 Language Design David McClain
2000-08-23  5:55 ` John Max Skaller
2000-08-24  9:12   ` Francois Pottier
2000-08-24 20:16     ` John Max Skaller
2000-08-25  9:52       ` Andreas Rossberg
2000-08-27 22:00         ` John Max Skaller
2000-08-28 23:11           ` Daan Leijen
2000-08-25 15:41       ` Jerome Vouillon
2000-08-27 22:21         ` John Max Skaller
2000-09-01 11:57 Dave Berry
2000-09-01 17:48 ` Markus Mottl
2000-09-01 19:12 ` Marcin 'Qrczak' Kowalczyk
     [not found]   ` <39B5DD81.E2500203@maxtal.com.au>
2000-09-06  6:33     ` Marcin 'Qrczak' Kowalczyk

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox