caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* RE: [Caml-list] variant with tuple arg in pattern match?
@ 2001-04-08  0:22 jgm
  0 siblings, 0 replies; 42+ messages in thread
From: jgm @ 2001-04-08  0:22 UTC (permalink / raw)
  To: caml-list

> Type-based compilation strategies such as TAL and FLINT can deal with
> this issue, but at considerable cost in complexity of the compiler and
> execution speed.

Er, you mean TIL :-)  TAL doesn't care which one you choose.

> Frankly, I think there is no point in maintaining the illusion that
> datatype constructors are either nullary (constant) or unary.  The
> only efficient implementation model is N-ary constructors, so let's
> reflect this in the language.

I agree.  Besides, if you're going to go the uniform route, why not
have all constructors be unary?  This always annoyed me in SML.  

> I agree that in an ideal world the syntax of the declaration should
> make this more explicit, e.g. the CamlP4 way ("Foo of int and int"
> vs. "Foo of int * int").  The current "syntactic overloading" of "*"
> in constructor declarations is sometimes misleading, but did make the
> conversion from Caml V3.1 code convenient a long, long time ago...

What's wrong with "Foo of int,int" or "Foo of (int,int)"?

JGM
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 17:25 Dave Berry
@ 2001-04-10 23:16 ` Marcin 'Qrczak' Kowalczyk
  0 siblings, 0 replies; 42+ messages in thread
From: Marcin 'Qrczak' Kowalczyk @ 2001-04-10 23:16 UTC (permalink / raw)
  To: caml-list

Tue, 10 Apr 2001 18:25:27 +0100, Dave Berry <Dave@kal.com> pisze:

> There are two levels of semantics here.  At the higher level, we have
> the behaviour that the programmer is trying to communicate, which
> distinguishes returning a function as a result on the one hand from
> passing multiple arguments on the other.

Sometimes it distinguishes that, sometimes not.

Cases when they are not distinguished seems to be common among
functions taking functions as *arguments*. Consider
    let flip f x y = f y x
How would you write it in the uncurried style?
    let flip (f,x,y) = f y x
    let flip (f,x,y) = f (y,x)
    let flip f = fun (x,y) -> f y x
    let flip f = fun (x,y) -> f (y,x)
    let flip (f,x) -> fun y -> f y x
    let flip (f,x) -> fun y -> f (y,x)

It tries to distinguish too much. flip transforms a binary function
to a function which takes its arguments in the opposite order. flip
transforms a multi-argument function to let it take its first two
arguments in the opposite order. flip takes a binary function with
its second argument and returns the appropriate partial application.
flip takes a binary function and its arguments and applies the function
to the arguments in the opposite order.

All these interpretations are correct. They describe the same thing
in different ways. I see no point in being forced to distinguish them.

> The lower level is how this is encoded in the programming language.
> With currying, there is no difference between the two, so information
> has been lost.  With multiple arguments, the distinction is
> maintained.

I would say the opposite. The uncurried style requires to introduce
some grouping of arguments. This grouping is not necessarily inherent
to the problem at hand. The concrete syntax introduced an unnecessary
distinction.

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

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 21:26   ` Bruce Hoult
@ 2001-04-10 22:34     ` John Prevost
  0 siblings, 0 replies; 42+ messages in thread
From: John Prevost @ 2001-04-10 22:34 UTC (permalink / raw)
  To: Bruce Hoult; +Cc: caml-list

>>>>> "bh" == Bruce Hoult <bruce@hoult.org> writes:

    bh> Multiple return values.  Unless you want to make continuations
    bh> explicit (and that doesn't seem to be what Caml folk want),
    bh> arguments in a tuple merely mirror results in a tuple.

    bh> Curried continuations ... yummm.

And this is another reason to consider functions to all be from one
value to another value.  If you want to work with tuples, fine, you
can use tuples to model multiple arguments.  You can use a tuple to
model multiple return values.  Both are actually single values.

In Scheme, where functions are considered to take and return multiple
values, you have a mess where you need special syntax to return
multiple values at once and to accept those multiple values.  This
mess exists specifically because of continuations, where a
continuation could be called with more than one argument.

In ML, where you never have more than one argument or return value, it
is simpler.  Even with continuations, you don't need a new concept of
"multiple-return-value".

John.
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 17:33 Dave Berry
@ 2001-04-10 22:34 ` John Prevost
  0 siblings, 0 replies; 42+ messages in thread
From: John Prevost @ 2001-04-10 22:34 UTC (permalink / raw)
  To: Dave Berry; +Cc: Frank Atanassow, Daniel de Rauglaudre, caml-list

>>>>> "db" == Dave Berry <Dave@kal.com> writes:

    db> As for syntax versus semantics, I nearly wrote "semantic
    db> hack", until I realised that it only works if the syntax also
    db> supports it.

Actually, it works regardless.  It's just that a convenient syntax
makes it nicer.  For example:

(define (map f)
  (let ((map' l)
        (cond ((cons? l) (cons (f (car l)) (map' (cdr l))))
              (t         l))
    map'))

((map (lamba (x) (+ x 2))) '(1 2 3 4 5))

This is a curried function in Scheme: it's not as nice as in a
language with a simpler (juxtaposition) application syntax, but it's
the same operation.  It's just that ML makes using curried functions
simpler.

The fact that this is more possible in Scheme, by the way, is one of
the things that makes Scheme superior to Lisp.  The fact that function
values and normal values are considered to be different in Lisp just
complicates things.

John.
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* RE: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 13:12 ` Marcin 'Qrczak' Kowalczyk
@ 2001-04-10 21:26   ` Bruce Hoult
  2001-04-10 22:34     ` John Prevost
  0 siblings, 1 reply; 42+ messages in thread
From: Bruce Hoult @ 2001-04-10 21:26 UTC (permalink / raw)
  To: caml-list

>  > 1. Multiple arguments.  Fine for the calculus, but in any language with
>>  tuples or records we can just write f(x,y), like everybody else.
>
>This is as much of a hack as currying. Why to pack arguments in a tuple
>when you could simply use currying?

Multiple return values.  Unless you want to make continuations 
explicit (and that doesn't seem to be what Caml folk want), arguments 
in a tuple merely mirror results in a tuple.

Curried continuations ... yummm.

-- Bruce
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10  2:54         ` Patrick M Doane
@ 2001-04-10 19:04           ` John Max Skaller
  0 siblings, 0 replies; 42+ messages in thread
From: John Max Skaller @ 2001-04-10 19:04 UTC (permalink / raw)
  To: Patrick M Doane; +Cc: Pierre Weis, caml-list

Patrick M Doane wrote:

> I think it is good to have these syntax discussions from time to time.
> Obviously it should not be the main focus of attention, but syntax really
> matters for the first impressions a user has with a new programming
> language.

	I don't agree with the first part: syntax is a vitally
important part of any language. It it the concrete representation
of the underlying semantic concepts. If you can't get a clean
and unified syntax .. there is probably a problem in the
underlying semantics.

-- 
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
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* RE: [Caml-list] variant with tuple arg in pattern match?
@ 2001-04-10 17:33 Dave Berry
  2001-04-10 22:34 ` John Prevost
  0 siblings, 1 reply; 42+ messages in thread
From: Dave Berry @ 2001-04-10 17:33 UTC (permalink / raw)
  To: Frank Atanassow; +Cc: Daniel de Rauglaudre, caml-list

> From: Frank Atanassow [mailto:franka@cs.uu.nl]
> Sent: Tuesday, April 10, 2001 14:51
> 
> When you say "currying" you are talking about a syntactic 
> matter which arises
> due to positional application. When Daniel said that "currying" is
> basic to the lambda-calculus, he was talking about a more fundamental,
> semantic matter.

Daniel did not write the sentence you attribute to him.  He said that
currying is basic to functional programming.  There are many differences
between functional programming and the pure lambda calculus.  Consider:
let-abstraction, the value polymorphism rule, restrictive type systems,
syntax, tuples, records, exceptions, assignment, modules, IO, size of
programs, etc.

As for syntax versus semantics, I nearly wrote "semantic hack", until I
realised that it only works if the syntax also supports it.

> If you look at lambda-calculus from a sufficiently abstract 
> perspective where
> the syntax is immaterial,...

... then you're not talking about functional programming.  

> And how do you define g in the first case if you don't have 
> semantical currying?

Possibly there is some terminological confusion here.  I've only ever
seen "currying" used to mean the encoding of multiple arguments using
higher order functions.  I certainly do not oppose the use of
higher-order functions for other uses, and of course this requires the
building of closures as you describe.

Dave. 
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* RE: [Caml-list] variant with tuple arg in pattern match?
@ 2001-04-10 17:25 Dave Berry
  2001-04-10 23:16 ` Marcin 'Qrczak' Kowalczyk
  0 siblings, 1 reply; 42+ messages in thread
From: Dave Berry @ 2001-04-10 17:25 UTC (permalink / raw)
  To: Marcin 'Qrczak' Kowalczyk, caml-list

> From: Marcin 'Qrczak' Kowalczyk [mailto:qrczak@knm.org.pl]
> Sent: Tuesday, April 10, 2001 14:12

> It's not a hack. When functions can return functions, there 
> is no need of inventing the concept of multiparameter functions.

>From a theoretical perspective, of course not.  From a programming
perspective, there are several reasons, many of which I gave in my
message.  Others include ease of compilation, and familiarity to
mainstream programmers.

> > In cases where a function is explicitly returning another 
> > (as opposed to
> > just simulating multiple arguments), I think the explicit binding
> > describes what is happening more clearly.
> 
> It's not opposition. This is semantically the same, so there 
> is no need of introducing a syntactic difference.

There are two levels of semantics here.  At the higher level, we have
the behaviour that the programmer is trying to communicate, which
distinguishes returning a function as a result on the one hand from
passing multiple arguments on the other.  The lower level is how this is
encoded in the programming language.  With currying, there is no
difference between the two, so information has been lost.  With multiple
arguments, the distinction is maintained.

> Does map take a function and a list, returning a list, or does it lift
> a function to a function operating on a list? 

Or does it raise a list to a function operating on a function?  Oops,
no, it can't do that, because the person who defined the function didn't
anticipate this use of it.  Time to eta-expand and flip...

Dave.
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 12:17 Dave Berry
  2001-04-10 13:12 ` Marcin 'Qrczak' Kowalczyk
@ 2001-04-10 13:51 ` Frank Atanassow
  1 sibling, 0 replies; 42+ messages in thread
From: Frank Atanassow @ 2001-04-10 13:51 UTC (permalink / raw)
  To: Dave Berry; +Cc: Daniel de Rauglaudre, caml-list

Dave Berry wrote (on 10-04-01 13:17 +0100):
> You certainly can avoid currying in functional languages.  Currying is a
> hack that was created to keep the lambda calculus as simple as possible.

When you say "currying" you are talking about a syntactic matter which arises
due to positional application. When Daniel said that "currying" is
basic to the lambda-calculus, he was talking about a more fundamental,
semantic matter.

If you look at lambda-calculus from a sufficiently abstract perspective where
the syntax is immaterial, then the essential difference between a first-order
and higher-order language is that in the second case you can represent a
function of two arguments (or a function whose argument is a 2-tuple) as a
higher-order function of one argument (and be able to apply it), and vice
versa. This characterization says nothing about positional application, labels
or what-have-you, because they are only a means of notation.

> Daniel points out that you will always be able to return a function from
> a function.  But currying is a partly syntactic hack; it relies on
> function application being notated by juxtaposition.  Without this hack,
> you have to write:
> 	let f = g (x, y)
> 	f (z)
> instead of:
> 	g x y z

Whichever way you write it, the same thing is still going on. If your calculus
is really equivalent to lambda-calculus, I should be able to transform the first
example to:

  (g (x,y)) (z)

which still uses positional application. Otherwise, you are just forcing me to
name all my function terms.

And how do you define g in the first case if you don't have semantical currying?
You need lambda:

  let g = fun (x, y) -> fun z -> h(x,y,z)

In a traditional denotational model, every term t is modeled as a function f
from (the product of) its environment to t. To bind a free variable, say z,
you need to curry f w.r.t. to z. So you still need currying to define lambda.

-- 
Frank Atanassow, Information & Computing Sciences, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-3261 Fax +31 (030) 251-379
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* RE: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 12:17 Dave Berry
@ 2001-04-10 13:12 ` Marcin 'Qrczak' Kowalczyk
  2001-04-10 21:26   ` Bruce Hoult
  2001-04-10 13:51 ` Frank Atanassow
  1 sibling, 1 reply; 42+ messages in thread
From: Marcin 'Qrczak' Kowalczyk @ 2001-04-10 13:12 UTC (permalink / raw)
  To: caml-list

On Tue, 10 Apr 2001, Dave Berry wrote:

> You certainly can avoid currying in functional languages.  Currying is a
> hack that was created to keep the lambda calculus as simple as possible.

It's not a hack. When functions can return functions, there is no need of
inventing the concept of multiparameter functions.

> 1. Multiple arguments.  Fine for the calculus, but in any language with
> tuples or records we can just write f(x,y), like everybody else.

This is as much of a hack as currying. Why to pack arguments in a tuple
when you could simply use currying?

> In cases where a function is explicitly returning another (as opposed to
> just simulating multiple arguments), I think the explicit binding
> describes what is happening more clearly.

It's not opposition. This is semantically the same, so there is no need of
introducing a syntactic difference.

Does map take a function and a list, returning a list, or does it lift
a function to a function operating on a list? There is no difference.

-- 
Marcin 'Qrczak' Kowalczyk

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 12:10                       ` reig
  2001-04-10 12:35                         ` Michel Mauny
@ 2001-04-10 12:49                         ` Marcin 'Qrczak' Kowalczyk
  1 sibling, 0 replies; 42+ messages in thread
From: Marcin 'Qrczak' Kowalczyk @ 2001-04-10 12:49 UTC (permalink / raw)
  To: caml-list

On Tue, 10 Apr 2001 reig@dcs.gla.ac.uk wrote:

> After all, we already use juxtaposition for curried function
> definitions:

But not function types. Clean goes further and the type of e.g. map can be
written thus: (a -> b) [a] -> [b]

-- 
Marcin 'Qrczak' Kowalczyk

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 12:10                       ` reig
@ 2001-04-10 12:35                         ` Michel Mauny
  2001-04-10 12:49                         ` Marcin 'Qrczak' Kowalczyk
  1 sibling, 0 replies; 42+ messages in thread
From: Michel Mauny @ 2001-04-10 12:35 UTC (permalink / raw)
  To: reig; +Cc: caml-list

reig@dcs.gla.ac.uk wrote/écrivait (Apr 10 2001, 01:10PM +0100):

> In fact, the syntax for the type definition could be like in haskell:
> use juxtaposition.
> 
> type 'a t = Curried  : ('a t) ('a t)
> 	  | Function : 'a t -> 'a t
> 

In this case, there is an ambiguity between curryfication and type
constructors application.

In

  type t = C : int bool

is C of type int -> bool -> t, or is bool a unary type constructor,
with int as argument. Compare with

  type t = C : int list

for instance. Parsing would need typing information, here.

Haskell avoids this in using the same notation (juxtaposition) all the
way long. That is, the examples above would be written as

  type t = C int bool

  type t = C (int list)

and made unambiguous using parens. Using  a `:' right after the data
constructor is (to me) less clear than the Haskell notation. Maybe
because of type constraints and module interfaces.

-- 
Michel
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* RE: [Caml-list] variant with tuple arg in pattern match?
@ 2001-04-10 12:17 Dave Berry
  2001-04-10 13:12 ` Marcin 'Qrczak' Kowalczyk
  2001-04-10 13:51 ` Frank Atanassow
  0 siblings, 2 replies; 42+ messages in thread
From: Dave Berry @ 2001-04-10 12:17 UTC (permalink / raw)
  To: Daniel de Rauglaudre, caml-list

You certainly can avoid currying in functional languages.  Currying is a
hack that was created to keep the lambda calculus as simple as possible.
Currying lets the lambda calculus simulate two things:

1. Multiple arguments.  Fine for the calculus, but in any language with
tuples or records we can just write f(x,y), like everybody else.

2. Partial application.  Again, fine for the calculus, but for languages
this fixes the decision of which arguments can be partially applied when
the function is defined, instead of where it is used.  If we define
functions with tuple arguments, we can introduce an explicit syntax for
partial application, e.g. f(_,y).

The explicit syntax is particularly useful for ML, because of the value
polymorphism rule.  In pure functional languages (and SML'90), you can
write:
	let flatten = fold \:: []
In ML, this gives an error (at least at top level), and you have to
eta-expand the definition:
	let sum l = fold \:: [] l
With explicit syntax for partial application, you would write:
	let sum = fold (\::, [], _)

Daniel points out that you will always be able to return a function from
a function.  But currying is a partly syntactic hack; it relies on
function application being notated by juxtaposition.  Without this hack,
you have to write:
	let f = g (x, y)
	f (z)
instead of:
	g x y z
In cases where a function is explicitly returning another (as opposed to
just simulating multiple arguments), I think the explicit binding
describes what is happening more clearly.

Incidentally, using juxtaposition to denote application makes it harder
for the parser to detect some errors.  This makes it more likely that
the user will see a type error where a simpler parse error would have
been more appropriate.  An earlier writer in this thread has already
pointed out that if some arguments are mistakenly omitted in a curried
application, this isn't reported until the point of use (and there might
not even be any uses, if the function is only called for its side
effects).


-----Original Message-----
From: Daniel de Rauglaudre [mailto:daniel.de_rauglaudre@inria.fr]
Sent: Monday, April 09, 2001 8:34
To: caml-list@inria.fr
Subject: Re: [Caml-list] variant with tuple arg in pattern match?


Hi,

On Mon, Apr 09, 2001 at 08:23:40AM +0200, Mattias Waldau wrote:

> If so, I don't think that curried syntax is something good.

I agree with your arguments, but... but you cannot avoid currification
in functional languages.

Ok, all your functions take non curried parameters, but how do you write
a function which returns a function? If it is:

   let f x = fun y -> blahblah

ok, you can write it:

   let f (x, y) = blahblah

But, how do you transform it if it is:

   let f x = blahblahblah...; blah blah blah; fun y -> blah blah

Currification is inside functional languages, you cannot decide to
ignore it.

And in OCaml, currified functions are more efficient (mmm... Xavier,
tell us if I am wrong). Besides, if you don't apply all arguments, you
get typing errors (in most cases), anyway.

-- 
Daniel de RAUGLAUDRE
daniel.de_rauglaudre@inria.fr
http://cristal.inria.fr/~ddr/
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives:
http://caml.inria.fr
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 11:47                     ` reig
@ 2001-04-10 12:10                       ` reig
  2001-04-10 12:35                         ` Michel Mauny
  2001-04-10 12:49                         ` Marcin 'Qrczak' Kowalczyk
  0 siblings, 2 replies; 42+ messages in thread
From: reig @ 2001-04-10 12:10 UTC (permalink / raw)
  To: caml-list; +Cc: Michel.Mauny

> Michel Mauny wrote:
> 
> > Sure. With CamlP4's revised syntax, you would write this as
> > 
> >    type t 'a =3D
> >      I of int
> >    | B of bool
> >    | N of (t 'a) and (t 'a)      (* parens probably unnecessary *)
> >    | Uncurried of int * int
> > 
> Like in haskell, if it *looks* curried, it *is* curried.
> 
> data T a = Curried (T a) (T a) 
>          | Function (T a -> T a)
> 

In fact, the syntax for the type definition could be like in haskell:
use juxtaposition.

type 'a t = Curried  : ('a t) ('a t)
	  | Function : 'a t -> 'a t

After all, we already use juxtaposition for curried function
definitions:

let f x y = ...
fun x y -> ...

Fermin Reig
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 11:32                   ` Michel Mauny
@ 2001-04-10 11:47                     ` reig
  2001-04-10 12:10                       ` reig
  0 siblings, 1 reply; 42+ messages in thread
From: reig @ 2001-04-10 11:47 UTC (permalink / raw)
  To: Michel.Mauny; +Cc: caml-list

Michel Mauny wrote:

> Sure. With CamlP4's revised syntax, you would write this as
> 
>    type t 'a =3D
>      I of int
>    | B of bool
>    | N of (t 'a) and (t 'a)      (* parens probably unnecessary *)
>    | Uncurried of int * int
> 
> > Moreover, the last part (-> 'a t) is the same for all constructors and
> > can be omitted like you do in haskell (so that Xavier is happier :)
> >=20
> >    type 'a t =3D
> >      Int : int
> >    | Bool : bool
> >    | Node : 'a t -> 'a t
> >    | Uncurried : int * int
> 
> I'm afraid the Node case is ambiguous, here.
> 
> Is the type of Node   'a t -> 'a t  -> 'a t
> or is it             ('a t -> 'a t) -> 'a t ?
> 
> In other words, you can't know wether Node carries functions, or is
> curried.

Like in haskell, if it *looks* curried, it *is* curried.

data T a = Curried (T a) (T a) 
        | Function (T a -> T a)

Main> :i T
-- type constructor
data T a
 
-- constructors:
Curried :: T a -> T a -> T a
Function :: (T a -> T a) -> T a
 
Even in ocaml's current syntax, you need parens for functions in datatypes:

# type t = F of int -> int;;
Syntax error
# type t = F of (int -> int);;
type t = F of (int -> int)

Maybe other syntax of disambiguating this case are better, I'm
proposing the one I know, which seems quite regular.

Fermin Reig


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10 10:44                 ` reig
@ 2001-04-10 11:32                   ` Michel Mauny
  2001-04-10 11:47                     ` reig
  0 siblings, 1 reply; 42+ messages in thread
From: Michel Mauny @ 2001-04-10 11:32 UTC (permalink / raw)
  To: reig; +Cc: caml-list

reig@dcs.gla.ac.uk wrote/écrivait (Apr 10 2001, 11:44AM +0100):

> This is how you do it in haskell:
> 
> data T a = I Int
> 	 | B Bool
> 	 | N (T a) (T a) 
> 	 | Uncurried (Int,Int)

Sure. With CamlP4's revised syntax, you would write this as

   type t 'a =
     I of int
   | B of bool
   | N of (t 'a) and (t 'a)      (* parens probably unnecessary *)
   | Uncurried of int * int

> Moreover, the last part (-> 'a t) is the same for all constructors and
> can be omitted like you do in haskell (so that Xavier is happier :)
> 
>    type 'a t =
>      Int : int
>    | Bool : bool
>    | Node : 'a t -> 'a t
>    | Uncurried : int * int

I'm afraid the Node case is ambiguous, here.

Is the type of Node   'a t -> 'a t  -> 'a t
or is it             ('a t -> 'a t) -> 'a t ?

In other words, you can't know wether Node carries functions, or is
curried.

-- Michel
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10  8:23               ` Michel Mauny
  2001-04-10  9:14                 ` Xavier Leroy
@ 2001-04-10 10:44                 ` reig
  2001-04-10 11:32                   ` Michel Mauny
  1 sibling, 1 reply; 42+ messages in thread
From: reig @ 2001-04-10 10:44 UTC (permalink / raw)
  To: caml-list; +Cc: Michel.Mauny

Michel Mauny wrote:

> Well, as far as I understand, there is an interaction with
> pattern-matching. Consider the following example:
> 
>   type 'a t =
>     Int : int -> int t
>   | Bool : bool -> bool t
>   | Node : 'a t -> 'a t -> 'a t
> 
> This definition implies that data constructors Int and Bool cannot
> appear in the same tree (no way to be at the same time an int t, and a
> bool t, unless being an 'a t, which cannot occur at all).
> [...]

This is how you do it in haskell:

data T a = I Int
	 | B Bool
	 | N (T a) (T a) 
	 | Uncurried (Int,Int)

hugs (a haskell interpreter) reports this:

Main> :i T
-- type constructor
data T a
 
-- constructors:
I :: Int -> T a
B :: Bool -> T a
N :: T a -> T a -> T a
Uncurried :: (Int,Int) -> T a

Of course, you can have trees with bools and ints:

Main> N (I 1) (B True)
N (I 1) (B True) :: T a

Notice that I has type Int -> T a, not Int -> T Int

The equivalent in ocaml, using Pierre's new syntax, would be:

   type 'a t =
     Int : int -> 'a t
   | Bool : bool -> 'a t
   | Node : 'a t -> 'a t -> 'a t
   | Uncurried : int * int -> 'a t

Moreover, the last part (-> 'a t) is the same for all constructors and
can be omitted like you do in haskell (so that Xavier is happier :)

   type 'a t =
     Int : int
   | Bool : bool
   | Node : 'a t -> 'a t
   | Uncurried : int * int

[I assume there would be no type checking problems for ocaml, but I
don't know for sure]

One other thing changes too: data constructors can be partially
applied in haskell. Ex:

Main> :t N (I 1)
N (I 1) :: T a -> T a

Main> map I [1,2,3]
[I 1,I 2,I 3] :: [T a]

[Don't need to eta expand (\x -> I x)]

Personally, I quite like this feature of haskell compared to ML.

Fermin Reig
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10  9:14                 ` Xavier Leroy
@ 2001-04-10 10:09                   ` Michel Mauny
  0 siblings, 0 replies; 42+ messages in thread
From: Michel Mauny @ 2001-04-10 10:09 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: caml-list

Xavier Leroy wrote/écrivait (Apr 10 2001, 11:14AM +0200):

> The Coq proof assistant doesn't agree with you here.

Well, Coq agrees with both of us on the fact that typing in OCaml and in Coq
are jobs of pretty different nature :-)

In my previous message, I was of course assuming an ML typing
philosophy.

-- Michel
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-10  8:23               ` Michel Mauny
@ 2001-04-10  9:14                 ` Xavier Leroy
  2001-04-10 10:09                   ` Michel Mauny
  2001-04-10 10:44                 ` reig
  1 sibling, 1 reply; 42+ messages in thread
From: Xavier Leroy @ 2001-04-10  9:14 UTC (permalink / raw)
  To: Michel Mauny; +Cc: caml-list

> Well, as far as I understand, there is an interaction with
> pattern-matching. Consider the following example:
> 
>   type 'a t =
>     Int : int -> int t
>   | Bool : bool -> bool t
>   | Node : 'a t -> 'a t -> 'a t
> 
> This definition implies that data constructors Int and Bool cannot
> appear in the same tree (no way to be at the same time an int t, and a
> bool t, unless being an 'a t, which cannot occur at all).
> 
> Consider now the following traversal function scheme:
> 
>   let rec traverse t = match t with
>     Int n -> ...   (* case 1 *)
>   | Bool b -> ...  (* case 2 *)
>   | Node t1 t2 -> ...
> 
> It's a total function, but untypable.

The Coq proof assistant doesn't agree with you here.  (Note to the
readers: I'm bringing Coq in the discussion because the notation
suggested by Pierre is the one Coq uses for its inductive definitions,
which generalize ML datatype definitions.)

Inductive t : Set -> Set :=
  Int : nat -> (t nat)
| Bool : bool -> (t bool)
| Node : (A: Set) (t A) -> (t A) -> (t A).

Definition traverse :=
  [A:Set][x: (t A)]
    Cases x of
      (Int _) => O
    | (Bool _) => (S O)
    | (Node _ _ _) => (S (S O))
    end.

Coq gives "traverse" the type (A:Set)(t A)->nat, i.e. 'a t -> int
in ML syntax.  How Coq does this is a bit of a mystery to me, but
clearly it doesn't unify the types of the l.h.s. of the
pattern-matching as we are used to do in ML...

Coming back to Pierre's suggestion, I don't see the point in switching
to the Coq syntax for declaring datatypes.  For one thing, it is
considerably more verbose: one has to repeat "-> (params) t" at the
end of each constructor declaration.  For another thing, it allows
more non-regular definitions (like Alain Frisch noted) which we don't
quite know how to handle, and are useless in practice (in my opinion).
Lastly, why change something that works?

(For Coq, the situation is different because inductive definitions can
define not only data structures, but also logical predicates, and in
the latter case the non-regular definitions are very useful, e.g. to
express inference rules.)

- Xavier Leroy
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-09 15:57           ` Pierre Weis
@ 2001-04-10  9:07             ` Sven LUTHER
  0 siblings, 0 replies; 42+ messages in thread
From: Sven LUTHER @ 2001-04-10  9:07 UTC (permalink / raw)
  To: Pierre Weis; +Cc: Brian Rogoff, caml-list

On Mon, Apr 09, 2001 at 05:57:00PM +0200, Pierre Weis wrote:
> [...]
> > > I suggest to explicitely annotate the constructor definitions as in:
> > > 
> > > type t =
> > > | C : int -> int -> t
> > 
> > Now that's an interesting idea! 
> > 
> > > This notation is explicit, intuitive, and allows refined type checking
> > > in some cases (for instance
> > > type 'a t = C : int -> bool -> (int * bool) t).
> > > 
> > > Last but not least, this suggestion is a pure extension of the actual
> > > syntax, compatible with the current notations. (We can still allow the
> > > form ``C of ty'' as a short hand for C of ty -> t).
> > 
> > You meant C : ty -> t of course.
> 
> Oups. Thank you for the correction.
> 
> > Getting back to the original problem
> > and confusing cases, would you still want the shorthands for the cases, 
> > say 
> > 
> > type t = C : int -> int -> t <=> type t = C of int * int ?
> > type t = C : int * int -> t  <=> type t = C of (int * int)
> > 
> > to be fixed so that the confusions don't arise anymore, or would you just 
> > want to deprecate the earlier notations?
> >
> > -- Brian
> 
> I suggest to support those equivalences while deprecating the earlier
> notations (after a while, so that the transition would be
> smooth). This would be easy if Caml users vote for the new notation (I
> mean if they intensively use the new notation in their programs). I
> think the new notation is so clean and easy that we would adopt it
> without discussion as soon as it is available in the language.

And it would permit us to do :

type t = A of int -> int

err that is 

type t = A : int -> int

instead of having to add parentheses around it ?

# type t = A of int -> int ;;
Syntax error
# type t = A of (int -> int) ;;
type t = A of (int -> int)

Friendly,

Sven Luther
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-09 16:07             ` Pierre Weis
@ 2001-04-10  8:23               ` Michel Mauny
  2001-04-10  9:14                 ` Xavier Leroy
  2001-04-10 10:44                 ` reig
  0 siblings, 2 replies; 42+ messages in thread
From: Michel Mauny @ 2001-04-10  8:23 UTC (permalink / raw)
  To: caml-list

On Sun, 8 Apr 2001, Pierre Weis wrote:
> I suggest to explicitely annotate the constructor definitions as in:
> 
> type t =
> | C : int -> int -> t
> This notation is explicit, intuitive, and allows refined type checking 
> in some cases (for instance
> type 'a t = C : int -> bool -> (int * bool) t).
 
Alain Frish then asked:

> How does this interact with pattern matching ?

Pierre Weis replied:

> As usual. There would be no interaction with the pattern matching
> facility of Objective Caml.

Well, as far as I understand, there is an interaction with
pattern-matching. Consider the following example:

  type 'a t =
    Int : int -> int t
  | Bool : bool -> bool t
  | Node : 'a t -> 'a t -> 'a t

This definition implies that data constructors Int and Bool cannot
appear in the same tree (no way to be at the same time an int t, and a
bool t, unless being an 'a t, which cannot occur at all).

Consider now the following traversal function scheme:

  let rec traverse t = match t with
    Int n -> ...   (* case 1 *)
  | Bool b -> ...  (* case 2 *)
  | Node t1 t2 -> ...

It's a total function, but untypable. If you want to make it typable
(and still semantically total), you'd have to suppress either case 1
or case 2. But now, how the compiler will see that the function is
indeed total?

This is yet another case where the pattern-matching compiler needs to
use a non-trivial knowledge from the typechecker. This is indeed
understandable, since values of type t are either int t or bool t,
that is [int | bool] t, which is pretty close to a feature of
variants.

-- Michel
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 19:45       ` Pierre Weis
                           ` (2 preceding siblings ...)
  2001-04-09  8:20         ` Christian RINDERKNECHT
@ 2001-04-10  2:54         ` Patrick M Doane
  2001-04-10 19:04           ` John Max Skaller
  3 siblings, 1 reply; 42+ messages in thread
From: Patrick M Doane @ 2001-04-10  2:54 UTC (permalink / raw)
  To: Pierre Weis; +Cc: caml-list

On Sun, 8 Apr 2001, Pierre Weis wrote:

> I would suggest the other way round: as we already did for functions,
> we should prefer the curried syntax for constructors.
> 
> I suggest to explicitely annotate the constructor definitions as in:
> 
> type t =
> | C : int -> int -> t

I really like this!  You mentioned in later e-mails that this would leave
pattern matching unaffected. I assume it should also be possible to
consider the constructor as a higher-order function usable in any
location that a variable is currently allowed.

I think it is good to have these syntax discussions from time to time. 
Obviously it should not be the main focus of attention, but syntax really
matters for the first impressions a user has with a new programming
language. 

Patrick

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-09  0:22           ` Alain Frisch
@ 2001-04-09 16:07             ` Pierre Weis
  2001-04-10  8:23               ` Michel Mauny
  0 siblings, 1 reply; 42+ messages in thread
From: Pierre Weis @ 2001-04-09 16:07 UTC (permalink / raw)
  To: Alain Frisch; +Cc: caml-list

> On Sun, 8 Apr 2001, Pierre Weis wrote:
> > I suggest to explicitely annotate the constructor definitions as in:
> > 
> > type t =
> > | C : int -> int -> t
> > This notation is explicit, intuitive, and allows refined type checking
> > in some cases (for instance
> > type 'a t = C : int -> bool -> (int * bool) t).
> 
> How does this interact with pattern matching ?

As usual. There would be no minteraction with the pattern matching
facility of Objective Caml.

[...]
> For instance, with the declaration:
>   type 'a t = A : int t | B : 'a -> 'a t
> do you issue a warning for:
>   function B x -> x
> ?

Yes, as usual: the constructor A is not covered by this matching.

> -- 
>   Alain Frisch

One more, there is no interaction with the pattern matching algorithm,
and as Daniel said, the syntax would just prevent you from trying to
misuse the arguments of a constructor.

Hope this helps,

Pierre Weis

INRIA, Projet Cristal, Pierre.Weis@inria.fr, http://pauillac.inria.fr/~weis/


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 23:57         ` Brian Rogoff
  2001-04-09  0:22           ` Alain Frisch
  2001-04-09  6:23           ` Mattias Waldau
@ 2001-04-09 15:57           ` Pierre Weis
  2001-04-10  9:07             ` Sven LUTHER
  2 siblings, 1 reply; 42+ messages in thread
From: Pierre Weis @ 2001-04-09 15:57 UTC (permalink / raw)
  To: Brian Rogoff; +Cc: Pierre.Weis, caml-list

[...]
> > I suggest to explicitely annotate the constructor definitions as in:
> > 
> > type t =
> > | C : int -> int -> t
> 
> Now that's an interesting idea! 
> 
> > This notation is explicit, intuitive, and allows refined type checking
> > in some cases (for instance
> > type 'a t = C : int -> bool -> (int * bool) t).
> > 
> > Last but not least, this suggestion is a pure extension of the actual
> > syntax, compatible with the current notations. (We can still allow the
> > form ``C of ty'' as a short hand for C of ty -> t).
> 
> You meant C : ty -> t of course.

Oups. Thank you for the correction.

> Getting back to the original problem
> and confusing cases, would you still want the shorthands for the cases, 
> say 
> 
> type t = C : int -> int -> t <=> type t = C of int * int ?
> type t = C : int * int -> t  <=> type t = C of (int * int)
> 
> to be fixed so that the confusions don't arise anymore, or would you just 
> want to deprecate the earlier notations?
>
> -- Brian

I suggest to support those equivalences while deprecating the earlier
notations (after a while, so that the transition would be
smooth). This would be easy if Caml users vote for the new notation (I
mean if they intensively use the new notation in their programs). I
think the new notation is so clean and easy that we would adopt it
without discussion as soon as it is available in the language.

Cheers,

Pierre Weis

INRIA, Projet Cristal, Pierre.Weis@inria.fr, http://pauillac.inria.fr/~weis/


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 19:45       ` Pierre Weis
  2001-04-08 20:37         ` Charles Martin
  2001-04-08 23:57         ` Brian Rogoff
@ 2001-04-09  8:20         ` Christian RINDERKNECHT
  2001-04-10  2:54         ` Patrick M Doane
  3 siblings, 0 replies; 42+ messages in thread
From: Christian RINDERKNECHT @ 2001-04-09  8:20 UTC (permalink / raw)
  To: caml-list

On Sun, Apr 08, 2001 at 09:45:52PM +0200, Pierre Weis wrote:
> 
> I would suggest [...] as we already did for functions,
> we should prefer the curried syntax for constructors.

I am not used to support a new feature by a posting, but this one seems
to me an important improvement: it is elegant and conservative, and
will be used all the time, without misunderstanding...

Regards,

-- 

Christian

-----------------------------------------------------------------------
Christian Rinderknecht                     Phone +33 (0)1 60 76 44 43
Institut National des Télécommunications   Fax   +33 (0)1 60 76 47 11
Département Logiciels Réseaux (LOR)        WWW
9, Rue Charles Fourier, F-91011 Évry Cedex
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-09  6:23           ` Mattias Waldau
@ 2001-04-09  7:34             ` Daniel de Rauglaudre
  0 siblings, 0 replies; 42+ messages in thread
From: Daniel de Rauglaudre @ 2001-04-09  7:34 UTC (permalink / raw)
  To: caml-list

Hi,

On Mon, Apr 09, 2001 at 08:23:40AM +0200, Mattias Waldau wrote:

> If so, I don't think that curried syntax is something good.

I agree with your arguments, but... but you cannot avoid currification
in functional languages.

Ok, all your functions take non curried parameters, but how do you write
a function which returns a function? If it is:

   let f x = fun y -> blahblah

ok, you can write it:

   let f (x, y) = blahblah

But, how do you transform it if it is:

   let f x = blahblahblah...; blah blah blah; fun y -> blah blah

Currification is inside functional languages, you cannot decide to
ignore it.

And in OCaml, currified functions are more efficient (mmm... Xavier,
tell us if I am wrong). Besides, if you don't apply all arguments, you
get typing errors (in most cases), anyway.

-- 
Daniel de RAUGLAUDRE
daniel.de_rauglaudre@inria.fr
http://cristal.inria.fr/~ddr/
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* RE: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 23:57         ` Brian Rogoff
  2001-04-09  0:22           ` Alain Frisch
@ 2001-04-09  6:23           ` Mattias Waldau
  2001-04-09  7:34             ` Daniel de Rauglaudre
  2001-04-09 15:57           ` Pierre Weis
  2 siblings, 1 reply; 42+ messages in thread
From: Mattias Waldau @ 2001-04-09  6:23 UTC (permalink / raw)
  To: Brian Rogoff, Pierre Weis; +Cc: caml-list

> I would suggest the other way round: as we already did for functions,
> we should prefer the curried syntax for constructors.

What do you really mean by "curried syntax", do you mean that you can
"add" one argument at a time to a function call?

If so, I don't think that curried syntax is something good. I don't
understand
why "curried" calls couldn't be annotated.

If I for example add an argument to a function and forget to update
all callers, I won't get an error where the call is done, but where the
result of the call is used. I won't errors at the correct location.

Since 99% of my calls are non-curried, Ocaml points me to the incorrect
location in 99% of the cases.

Why can't curried calls be annotated? This would improve error-detection!

And of course, I don't want this misfeature to spread anymore.

/mattias


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 23:57         ` Brian Rogoff
@ 2001-04-09  0:22           ` Alain Frisch
  2001-04-09 16:07             ` Pierre Weis
  2001-04-09  6:23           ` Mattias Waldau
  2001-04-09 15:57           ` Pierre Weis
  2 siblings, 1 reply; 42+ messages in thread
From: Alain Frisch @ 2001-04-09  0:22 UTC (permalink / raw)
  To: Pierre Weis, Caml list

On Sun, 8 Apr 2001, Pierre Weis wrote:
> I suggest to explicitely annotate the constructor definitions as in:
> 
> type t =
> | C : int -> int -> t
> This notation is explicit, intuitive, and allows refined type checking
> in some cases (for instance
> type 'a t = C : int -> bool -> (int * bool) t).

How does this interact with pattern matching ?  If constructor types
are not uniform, it seems that it is no longer possible to 
say whether a simple (without guards) pattern matching is exhaustive or
not.

For instance, with the declaration:
  type 'a t = A : int t | B : 'a -> 'a t
do you issue a warning for:
  function B x -> x
?


-- 
  Alain Frisch

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 19:45       ` Pierre Weis
  2001-04-08 20:37         ` Charles Martin
@ 2001-04-08 23:57         ` Brian Rogoff
  2001-04-09  0:22           ` Alain Frisch
                             ` (2 more replies)
  2001-04-09  8:20         ` Christian RINDERKNECHT
  2001-04-10  2:54         ` Patrick M Doane
  3 siblings, 3 replies; 42+ messages in thread
From: Brian Rogoff @ 2001-04-08 23:57 UTC (permalink / raw)
  To: Pierre Weis; +Cc: caml-list

On Sun, 8 Apr 2001, Pierre Weis wrote:
> > On 06-Apr-2001, Xavier Leroy <Xavier.Leroy@inria.fr> wrote:
> > > 
> > > Frankly, I think there is no point in maintaining the illusion that
> > > datatype constructors are either nullary (constant) or unary.  The
> > > only efficient implementation model is N-ary constructors, so let's
> > > reflect this in the language.
> > 
> > Sounds good to me.  Now, for consistency, shouldn't you do the same
> > for function arguments? ;-)
> 
> I would suggest the other way round: as we already did for functions,
> we should prefer the curried syntax for constructors.

Good, I was starting to get worried. Someone earlier was complaining about 
Caml's curriedness vs SML's tupledness. I've been porting a bunch of code 
from SML to Caml lately, and of course this issue comes up constantly. 
There is probably a strong issue of familiarity involved, but I actually 
much prefer the Caml way.

> I suggest to explicitely annotate the constructor definitions as in:
> 
> type t =
> | C : int -> int -> t

Now that's an interesting idea! 

> This notation is explicit, intuitive, and allows refined type checking
> in some cases (for instance
> type 'a t = C : int -> bool -> (int * bool) t).
> 
> Last but not least, this suggestion is a pure extension of the actual
> syntax, compatible with the current notations. (We can still allow the
> form ``C of ty'' as a short hand for C of ty -> t).

You meant C : ty -> t of course. Getting back to the original problem
and confusing cases, would you still want the shorthands for the cases, 
say 

type t = C : int -> int -> t <=> type t = C of int * int ?
type t = C : int * int -> t  <=> type t = C of (int * int)

to be fixed so that the confusions don't arise anymore, or would you just 
want to deprecate the earlier notations?

-- Brian


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-08 19:45       ` Pierre Weis
@ 2001-04-08 20:37         ` Charles Martin
  2001-04-08 23:57         ` Brian Rogoff
                           ` (2 subsequent siblings)
  3 siblings, 0 replies; 42+ messages in thread
From: Charles Martin @ 2001-04-08 20:37 UTC (permalink / raw)
  To: caml-list


> > Sounds good to me.  Now, for consistency, shouldn't you do the same
> > for function arguments? ;-)
>
>I would suggest the other way round: as we already did for functions,
>we should prefer the curried syntax for constructors.

Yes, yes, yes please!


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-07  7:42     ` Fergus Henderson
@ 2001-04-08 19:45       ` Pierre Weis
  2001-04-08 20:37         ` Charles Martin
                           ` (3 more replies)
  0 siblings, 4 replies; 42+ messages in thread
From: Pierre Weis @ 2001-04-08 19:45 UTC (permalink / raw)
  To: Fergus Henderson; +Cc: Xavier.Leroy, patrick, checker, caml-list

> On 06-Apr-2001, Xavier Leroy <Xavier.Leroy@inria.fr> wrote:
> > 
> > Frankly, I think there is no point in maintaining the illusion that
> > datatype constructors are either nullary (constant) or unary.  The
> > only efficient implementation model is N-ary constructors, so let's
> > reflect this in the language.
> 
> Sounds good to me.  Now, for consistency, shouldn't you do the same
> for function arguments? ;-)
> 
> -- 
> Fergus Henderson <fjh@cs.mu.oz.au>  |  "I have always known that the pursuit
>                                     |  of excellence is a lethal habit"
> WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.
> -------------------
> To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr

I would suggest the other way round: as we already did for functions,
we should prefer the curried syntax for constructors.

I suggest to explicitely annotate the constructor definitions as in:

type t =
| C : int -> int -> t

This notation is explicit, intuitive, and allows refined type checking
in some cases (for instance
type 'a t = C : int -> bool -> (int * bool) t).

Last but not least, this suggestion is a pure extension of the actual
syntax, compatible with the current notations. (We can still allow the
form ``C of ty'' as a short hand for C of ty -> t).

Hope this helps,

Pierre Weis

INRIA, Projet Cristal, Pierre.Weis@inria.fr, http://pauillac.inria.fr/~weis/


-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-06 13:52   ` Xavier Leroy
  2001-04-07  1:42     ` Patrick M Doane
@ 2001-04-07  7:42     ` Fergus Henderson
  2001-04-08 19:45       ` Pierre Weis
  1 sibling, 1 reply; 42+ messages in thread
From: Fergus Henderson @ 2001-04-07  7:42 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: Patrick M Doane, Chris Hecker, caml-list

On 06-Apr-2001, Xavier Leroy <Xavier.Leroy@inria.fr> wrote:
> 
> Frankly, I think there is no point in maintaining the illusion that
> datatype constructors are either nullary (constant) or unary.  The
> only efficient implementation model is N-ary constructors, so let's
> reflect this in the language.

Sounds good to me.  Now, for consistency, shouldn't you do the same
for function arguments? ;-)

-- 
Fergus Henderson <fjh@cs.mu.oz.au>  |  "I have always known that the pursuit
                                    |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-07  1:42     ` Patrick M Doane
@ 2001-04-07  6:44       ` Daniel de Rauglaudre
  0 siblings, 0 replies; 42+ messages in thread
From: Daniel de Rauglaudre @ 2001-04-07  6:44 UTC (permalink / raw)
  To: caml-list

Hi,

On Fri, Apr 06, 2001 at 09:42:38PM -0400, Patrick M Doane wrote:

> What are the current thoughts about adopting the revised syntax as the
> "standard one"? How many programmers use that syntax?

Discussions about syntax generally degenerate into quarrels because it
is often a question of taste and find a consensus is extremely hard.
Adopting it as "standard one" is then not possible. And there is too
much code written in OCaml by all users.

I wrote this "revised" syntax but I don't think that many people use
it. I have no idea of the number, but probably very few. Except me, I
just know two persons, one of them already not agreeing one of my
choices. I agree to improve this syntax, to change things (I mean in
the Camlp4 distribution), but only if there are more than 3 persons
interested.

Well, everybody can make his own syntax, e.g. starting from the file
treating the normal syntax (etc/pa_o.ml) or the file of the revised
syntax (meta/pa_r.ml). This revised syntax, even dating from several
years, is just an experiment. I would have liked that people
experiment other possible syntaxes, but it seems that it is not a
subject interesting many people.

Less than genealogy, in any case...

-- 
Daniel de RAUGLAUDRE
daniel.de_rauglaudre@inria.fr
http://cristal.inria.fr/~ddr/
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-06 13:52   ` Xavier Leroy
@ 2001-04-07  1:42     ` Patrick M Doane
  2001-04-07  6:44       ` Daniel de Rauglaudre
  2001-04-07  7:42     ` Fergus Henderson
  1 sibling, 1 reply; 42+ messages in thread
From: Patrick M Doane @ 2001-04-07  1:42 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: Chris Hecker, caml-list

Very good points regarding compilation.  As I think about it more, I agree
that you are right about making N-ary constructors exposed at the
syntactic level.  I especially like the syntax modifications that are part
of the revised syntax, but times certainly change:  when I first looked at
that syntax long ago, I didn't understand why the difference was there in
the first place. 

What are the current thoughts about adopting the revised syntax as the
"standard one"? How many programmers use that syntax?

Patrick

On Fri, 6 Apr 2001, Xavier Leroy wrote:

> [ Difference between "type foo = Foo of int * int" and
>   "type foo = Foo of (int * int)" ]
> 
> > I would certainly like it if Caml could:
> > 
> >   1) Treat this entirely as an optimization issue and not make a syntactic
> > distinction.
> 
> This is extremely hard to do in the presence of modules and abstract
> type.  The problem is that the structure
> 
>       struct
>         type foo = Foo of int * int
>         type arg = int * int
>         ...
>       end
> 
> would then match
> 
>       sig
>         type arg
>         type foo = Foo of arg
>         ...
>       end
> 
> and users of the module would believe that "Foo" is a constructor with
> one argument (that happens to be a pair), which does not match the
> representation used in the rest of the structure ("Foo" as a
> constructor with two arguments).
> 
> Type-based compilation strategies such as TAL and FLINT can deal with
> this issue, but at considerable cost in complexity of the compiler and
> execution speed.
> 
> Frankly, I think there is no point in maintaining the illusion that
> datatype constructors are either nullary (constant) or unary.  The
> only efficient implementation model is N-ary constructors, so let's
> reflect this in the language.
> 
> >   2) Be able to make reasonable choices about which representation would
> > be more appropriate.
> 
> 99% of the time, the current representation choice (N-ary constructor
> if the constructor is declared with a N-tuple type) is adequate.
> 
> I agree that in an ideal world the syntax of the declaration should
> make this more explicit, e.g. the CamlP4 way ("Foo of int and int"
> vs. "Foo of int * int").  The current "syntactic overloading" of "*"
> in constructor declarations is sometimes misleading, but did make the
> conversion from Caml V3.1 code convenient a long, long time ago...
> 
> - Xavier Leroy
> 

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 19:18 ` Patrick M Doane
  2001-04-04 19:36   ` Chris Hecker
@ 2001-04-06 13:52   ` Xavier Leroy
  2001-04-07  1:42     ` Patrick M Doane
  2001-04-07  7:42     ` Fergus Henderson
  1 sibling, 2 replies; 42+ messages in thread
From: Xavier Leroy @ 2001-04-06 13:52 UTC (permalink / raw)
  To: Patrick M Doane; +Cc: Chris Hecker, caml-list

[ Difference between "type foo = Foo of int * int" and
  "type foo = Foo of (int * int)" ]

> I would certainly like it if Caml could:
> 
>   1) Treat this entirely as an optimization issue and not make a syntactic
> distinction.

This is extremely hard to do in the presence of modules and abstract
type.  The problem is that the structure

      struct
        type foo = Foo of int * int
        type arg = int * int
        ...
      end

would then match

      sig
        type arg
        type foo = Foo of arg
        ...
      end

and users of the module would believe that "Foo" is a constructor with
one argument (that happens to be a pair), which does not match the
representation used in the rest of the structure ("Foo" as a
constructor with two arguments).

Type-based compilation strategies such as TAL and FLINT can deal with
this issue, but at considerable cost in complexity of the compiler and
execution speed.

Frankly, I think there is no point in maintaining the illusion that
datatype constructors are either nullary (constant) or unary.  The
only efficient implementation model is N-ary constructors, so let's
reflect this in the language.

>   2) Be able to make reasonable choices about which representation would
> be more appropriate.

99% of the time, the current representation choice (N-ary constructor
if the constructor is declared with a N-tuple type) is adequate.

I agree that in an ideal world the syntax of the declaration should
make this more explicit, e.g. the CamlP4 way ("Foo of int and int"
vs. "Foo of int * int").  The current "syntactic overloading" of "*"
in constructor declarations is sometimes misleading, but did make the
conversion from Caml V3.1 code convenient a long, long time ago...

- Xavier Leroy
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 19:49     ` Daniel de Rauglaudre
@ 2001-04-05  8:19       ` Christian RINDERKNECHT
  0 siblings, 0 replies; 42+ messages in thread
From: Christian RINDERKNECHT @ 2001-04-05  8:19 UTC (permalink / raw)
  To: caml-list

Dear Caml aficionados,

On Wed, Apr 04, 2001 at 09:49:18PM +0200, Daniel de Rauglaudre wrote:
>
> [...] by Camlp4, I propose to represent constructors with several
> parameters with currification syntax. You can write:
> 
>      type t1 = [ Foo of int and int ]    to specify two parameters
>      type t2 = [ Bar of (int * int) ]    to specify one parameter, a tuple

I think this syntax (and the associated patterns) is much better
indeed than the current one, but, anyway, different syntactic
constructs are worth if there is a different operational semantics,
for instance if it is then allowed to apply partially a contructor,
like in a previous version of Caml Light. I understand that efficiency
is an important issue but it should remain as _syntactically_
transparent as possible...

Best regards,

-- 

Christian

-----------------------------------------------------------------------
Christian Rinderknecht                     Phone +33 (0)1 60 76 44 43
Institut National des Télécommunications   Fax   +33 (0)1 60 76 47 11
Département Logiciels Réseaux (LOR)        WWW
9, Rue Charles Fourier, F-91011 Évry Cedex
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 19:36   ` Chris Hecker
  2001-04-04 19:49     ` Daniel de Rauglaudre
@ 2001-04-04 19:49     ` Patrick M Doane
  1 sibling, 0 replies; 42+ messages in thread
From: Patrick M Doane @ 2001-04-04 19:49 UTC (permalink / raw)
  To: Chris Hecker; +Cc: caml-list

Hi Chris,

This only becomes an issue when the data being associated with a
constructor would need to be boxed.  Since an int doesn't require any
boxing, the type 'foo = Foo of int' will work exactly as expected.

Boxing/unboxing optimizations can be very subtle. The most important
example I can think of is computation with complex numbers.  Is it better
for the the representation to be as a pair of floats in one structure or
as two separate floats?  Different parts of a program may do better with
one representation instead of the other.

As far as I understand, the compiler could choose a representation for
variants and insert the necessary transformation code to hide the issue
from the programmer entirely.  I haven't thought about the issue much so 
there could be a real problem that I'm not seeing. From what I remember,
SML does not make this kind of syntactic distinction.

Patrick

On Wed, 4 Apr 2001, Chris Hecker wrote:

> 
> >I would certainly like it if Caml could:
> >  1) Treat this entirely as an optimization issue and not make a syntactic
> >distinction.
> 
> I agree.  Is there a reason why it's done this way?  I guess you need to
> be able to bind another name to the tuple independently, and for that to
> work you need it to be another block on the heap.  Maybe it's not
> possible in general to do the right thing. 
> 
> But wait, why isn't this a problem even with normal non-tupled values?
> 
> In other worlds, how does type foo = Foo of int work when I take a
> reference to the int?  It has to know I'm refering to the int to GC
> correctly.  Why is the tuple version any different? 
> 
> I'm confused.
> 
> Chris
> 
> 

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 19:36   ` Chris Hecker
@ 2001-04-04 19:49     ` Daniel de Rauglaudre
  2001-04-05  8:19       ` Christian RINDERKNECHT
  2001-04-04 19:49     ` Patrick M Doane
  1 sibling, 1 reply; 42+ messages in thread
From: Daniel de Rauglaudre @ 2001-04-04 19:49 UTC (permalink / raw)
  To: caml-list

Hi,

My opinion is that the confusion comes from the syntax. In my revised syntax
by Camlp4, I propose to represent constructors with several parameters with
currification syntax. You can write:

     type t1 = [ Foo of int and int ]    to specify two parameters
     type t2 = [ Bar of (int * int) ]    to specify one parameter, a tuple

And you (must) write:
    Foo 3 5
    Bar (3, 5)

The case:
    Foo 3
answers:
    The constructor Foo expects 2 argument(s),
    but is here applied to 1 argument(s)
which is normal.

Idem for the case:
   match x with [ Foo y -> y ]

To get the couple, you have to write:
   match x with [ Foo y z -> (y, z) ]

This is logical. With this syntax, no possible confusion. You would
even not have asked the question.

It is not a question of semantics, but a question of *syntax*.

-- 
Daniel de RAUGLAUDRE
daniel.de_rauglaudre@inria.fr
http://cristal.inria.fr/~ddr/
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 19:18 ` Patrick M Doane
@ 2001-04-04 19:36   ` Chris Hecker
  2001-04-04 19:49     ` Daniel de Rauglaudre
  2001-04-04 19:49     ` Patrick M Doane
  2001-04-06 13:52   ` Xavier Leroy
  1 sibling, 2 replies; 42+ messages in thread
From: Chris Hecker @ 2001-04-04 19:36 UTC (permalink / raw)
  To: Patrick M Doane; +Cc: caml-list


>I would certainly like it if Caml could:
>  1) Treat this entirely as an optimization issue and not make a syntactic
>distinction.

I agree.  Is there a reason why it's done this way?  I guess you need to be able to bind another name to the tuple independently, and for that to work you need it to be another block on the heap.  Maybe it's not possible in general to do the right thing.  

But wait, why isn't this a problem even with normal non-tupled values?

In other worlds, how does type foo = Foo of int work when I take a reference to the int?  It has to know I'm refering to the int to GC correctly.  Why is the tuple version any different?

I'm confused.

Chris

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 11:04 Chris Hecker
  2001-04-04 18:47 ` Alain Frisch
@ 2001-04-04 19:18 ` Patrick M Doane
  2001-04-04 19:36   ` Chris Hecker
  2001-04-06 13:52   ` Xavier Leroy
  1 sibling, 2 replies; 42+ messages in thread
From: Patrick M Doane @ 2001-04-04 19:18 UTC (permalink / raw)
  To: Chris Hecker; +Cc: caml-list

Hi Chris,

You'll need to change your type declaration from

  type foo = Foo of int * int

to

  type foo = Foo of (int * int)

or

  type bar = int * int
  type foo = Foo of bar

Caml performs some optimizations on the representation of tuples to place
the arguments for the constructor as well as constructor name into one
word of memory.  This can be a big win, both in memory usage and in access
time because one pointer access is removed.

It makes this distinction syntactically in the type declarations.  In the
first case, the memory layout for values of type foo would be: 

   [ tag word | int1 | int2 ]

where the second case would be

   [ tag word |  pointer ]  ->  [ tag word | int1 | int2 ]

I would certainly like it if Caml could:

  1) Treat this entirely as an optimization issue and not make a syntactic
distinction.

  2) Be able to make reasonable choices about which representation would
be more appropriate.

I doubt that it would do as well as the programmer could and it certainly
would take a bit of effort without a real clear improvement.

On the other hand, left with the syntactic distincation, a possible
improvement would be to make a distinction between

  type foo = Foo of bar

and 

  type foo = Foo of (bar)

so that "equational reasoning" could hold with regard to type
declarations. On several occasions, I have been tempted not to create
another type declaration because of this representation issue.

Hope this helps

Patrick

On Wed, 4 Apr 2001, Chris Hecker wrote:

> 
> I can't find anything about this in the docs, faq, or list archives.
> 
> I expected ii to be bound to the int * int tuple (1,2) in this pattern match:
> 
> # type foo = Foo of int * int;;
> type foo = Foo of int * int
> #   match Foo (1,2) with Foo ii -> ii ;;
> Characters 23-29:
> The constructor Foo expects 2 argument(s),
> but is here applied to 1 argument(s)
> 
> 
> This works:
> 
> # match Foo (1,2) with Foo _ -> () ;;
> - : unit = ()
> 
> But I can't get an "as" clause to work, either:
> 
> # match Foo (1,2) with Foo ((_,_) as ii) -> ii ;;
> Characters 21-38:
> The constructor Foo expects 2 argument(s),
> but is here applied to 1 argument(s)
> 
> But, even if the "as" worked, it's messy compared to the top method.
>  
> Chris
> 
> -------------------
> To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr
> 

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* Re: [Caml-list] variant with tuple arg in pattern match?
  2001-04-04 11:04 Chris Hecker
@ 2001-04-04 18:47 ` Alain Frisch
  2001-04-04 19:18 ` Patrick M Doane
  1 sibling, 0 replies; 42+ messages in thread
From: Alain Frisch @ 2001-04-04 18:47 UTC (permalink / raw)
  To: Chris Hecker; +Cc: caml-list

Hello,

On Wed, 4 Apr 2001, Chris Hecker wrote:

> I expected ii to be bound to the int * int tuple (1,2) in this pattern match:
> 
> # type foo = Foo of int * int;;
> type foo = Foo of int * int

You define Foo to be a constructor with two arguments ...

(the star here is not the same as the one for tuple types)

> #   match Foo (1,2) with Foo ii -> ii ;;

and you use it as an unary constructor. Hence the error:

> Characters 23-29:
> The constructor Foo expects 2 argument(s),
> but is here applied to 1 argument(s)

The solution is to declare:

type foo = Foo of (int * int)

The drawback is that the internal representation of the value Foo (1,2)
uses two heap allocated blocks (one for the constructor, one for the
tuple). A flat representation, as is the case with your declaration, may
be more efficient, but then you have to explicitely reconstruct the tuple:

match Foo (1,2) with Foo (a,b) -> (a,b);;


The issue probably deserves a few words in the FAQ or in the manual.


Hope this helps.

-- 
Alain Frisch
-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

* [Caml-list] variant with tuple arg in pattern match?
@ 2001-04-04 11:04 Chris Hecker
  2001-04-04 18:47 ` Alain Frisch
  2001-04-04 19:18 ` Patrick M Doane
  0 siblings, 2 replies; 42+ messages in thread
From: Chris Hecker @ 2001-04-04 11:04 UTC (permalink / raw)
  To: caml-list


I can't find anything about this in the docs, faq, or list archives.

I expected ii to be bound to the int * int tuple (1,2) in this pattern match:

# type foo = Foo of int * int;;
type foo = Foo of int * int
#   match Foo (1,2) with Foo ii -> ii ;;
Characters 23-29:
The constructor Foo expects 2 argument(s),
but is here applied to 1 argument(s)


This works:

# match Foo (1,2) with Foo _ -> () ;;
- : unit = ()

But I can't get an "as" clause to work, either:

# match Foo (1,2) with Foo ((_,_) as ii) -> ii ;;
Characters 21-38:
The constructor Foo expects 2 argument(s),
but is here applied to 1 argument(s)

But, even if the "as" worked, it's messy compared to the top method.
 
Chris

-------------------
To unsubscribe, mail caml-list-request@inria.fr.  Archives: http://caml.inria.fr


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

end of thread, other threads:[~2001-04-17 17:33 UTC | newest]

Thread overview: 42+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2001-04-08  0:22 [Caml-list] variant with tuple arg in pattern match? jgm
  -- strict thread matches above, loose matches on Subject: below --
2001-04-10 17:33 Dave Berry
2001-04-10 22:34 ` John Prevost
2001-04-10 17:25 Dave Berry
2001-04-10 23:16 ` Marcin 'Qrczak' Kowalczyk
2001-04-10 12:17 Dave Berry
2001-04-10 13:12 ` Marcin 'Qrczak' Kowalczyk
2001-04-10 21:26   ` Bruce Hoult
2001-04-10 22:34     ` John Prevost
2001-04-10 13:51 ` Frank Atanassow
2001-04-04 11:04 Chris Hecker
2001-04-04 18:47 ` Alain Frisch
2001-04-04 19:18 ` Patrick M Doane
2001-04-04 19:36   ` Chris Hecker
2001-04-04 19:49     ` Daniel de Rauglaudre
2001-04-05  8:19       ` Christian RINDERKNECHT
2001-04-04 19:49     ` Patrick M Doane
2001-04-06 13:52   ` Xavier Leroy
2001-04-07  1:42     ` Patrick M Doane
2001-04-07  6:44       ` Daniel de Rauglaudre
2001-04-07  7:42     ` Fergus Henderson
2001-04-08 19:45       ` Pierre Weis
2001-04-08 20:37         ` Charles Martin
2001-04-08 23:57         ` Brian Rogoff
2001-04-09  0:22           ` Alain Frisch
2001-04-09 16:07             ` Pierre Weis
2001-04-10  8:23               ` Michel Mauny
2001-04-10  9:14                 ` Xavier Leroy
2001-04-10 10:09                   ` Michel Mauny
2001-04-10 10:44                 ` reig
2001-04-10 11:32                   ` Michel Mauny
2001-04-10 11:47                     ` reig
2001-04-10 12:10                       ` reig
2001-04-10 12:35                         ` Michel Mauny
2001-04-10 12:49                         ` Marcin 'Qrczak' Kowalczyk
2001-04-09  6:23           ` Mattias Waldau
2001-04-09  7:34             ` Daniel de Rauglaudre
2001-04-09 15:57           ` Pierre Weis
2001-04-10  9:07             ` Sven LUTHER
2001-04-09  8:20         ` Christian RINDERKNECHT
2001-04-10  2:54         ` Patrick M Doane
2001-04-10 19:04           ` John Max Skaller

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).