caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] Matching when
@ 2002-08-05  9:26 Nicolas Cannasse
  2002-08-05  9:41 ` Luc Maranget
                   ` (4 more replies)
  0 siblings, 5 replies; 15+ messages in thread
From: Nicolas Cannasse @ 2002-08-05  9:26 UTC (permalink / raw)
  To: OCaml

Hi !

I was thinking that the following should be possible :

match e with
| Any
| Int x when x > 0 ->
        .... (* here we don't use x *)
| ....

But the typechecker reject it because of the unbound 'x' in the "Any"
matching.
I don't know what kind of difficulty this modification require, but it would
be nice if the compiler was able to resolve such cases.

:-)
Nicolas Cannasse

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05  9:26 [Caml-list] Matching when Nicolas Cannasse
@ 2002-08-05  9:41 ` Luc Maranget
  2002-08-05 16:13   ` John Max Skaller
  2002-08-05 13:05 ` [Caml-list] Matching when Pierre Weis
                   ` (3 subsequent siblings)
  4 siblings, 1 reply; 15+ messages in thread
From: Luc Maranget @ 2002-08-05  9:41 UTC (permalink / raw)
  To: Nicolas Cannasse; +Cc: OCaml

> 
> Hi !
> 
> I was thinking that the following should be possible :
> 
> match e with
> | Any
> | Int x when x > 0 ->
>         .... (* here we don't use x *)
> | ....
> 
> But the typechecker reject it because of the unbound 'x' in the "Any"
> matching.
> I don't know what kind of difficulty this modification require, but it would
> be nice if the compiler was able to resolve such cases.
> 
> :-)
> Nicolas Cannasse
> 

Hello,

This has already been discussed.
The modifications required are important and probably not worth the
trouble.

More precisely the guard ``when expression'' is not part of patterns but rather
part of clauses.

That is your example is to to be parsed as
 Any | Int x <-- pattern                \
 when x > 0   <-- guard                 | clause
 ->                                     |
  ...         <-- right hand side       /

What you are asking is ``pattern when expression'' to be a pattern.
Then your example would be parsed as

That is your example is to to be parsed as
 Any              <-- pattern   | 
|                               | Pattern (or pat)
 Int x when x > 0 <-- pattern   |
->
  ...             <-- right hand side


Modifications are really important because this would make patterns and
expression mutually recursive, which they are not at the moment.



--Luc
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05  9:26 [Caml-list] Matching when Nicolas Cannasse
  2002-08-05  9:41 ` Luc Maranget
@ 2002-08-05 13:05 ` Pierre Weis
  2002-08-05 15:50 ` John Max Skaller
                   ` (2 subsequent siblings)
  4 siblings, 0 replies; 15+ messages in thread
From: Pierre Weis @ 2002-08-05 13:05 UTC (permalink / raw)
  To: Nicolas Cannasse; +Cc: caml-list

Hi !

> I was thinking that the following should be possible :
> 
> match e with
> | Any
> | Int x when x > 0 ->
>         .... (* here we don't use x *)
> | ....
> 
> But the typechecker reject it because of the unbound 'x' in the "Any"
> matching.
> I don't know what kind of difficulty this modification require, but it would
> be nice if the compiler was able to resolve such cases.

I would require to analyze the set of free variables of expression
parts of match clauses to restrict the checks on variables of patterns
to this set of variables. In this case, the set of (typed) variables of
all the patterns of an ``or'' pattern should have the same intersection
with the set of free variables of the corresponding expression of the
clause, and this would solve your problem in a simple and elegant way.

This is simple and does not involve any modification of the semantics
of the language or of the pattern matching algorithm.

Regards,

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
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05  9:26 [Caml-list] Matching when Nicolas Cannasse
  2002-08-05  9:41 ` Luc Maranget
  2002-08-05 13:05 ` [Caml-list] Matching when Pierre Weis
@ 2002-08-05 15:50 ` John Max Skaller
  2002-08-05 16:02 ` Remi VANICAT
  2002-08-05 18:25 ` Oleg
  4 siblings, 0 replies; 15+ messages in thread
From: John Max Skaller @ 2002-08-05 15:50 UTC (permalink / raw)
  To: Nicolas Cannasse; +Cc: OCaml

Nicolas Cannasse wrote:

>Hi !
>
>I was thinking that the following should be possible :
>
>match e with
>| Any
>| Int x when x > 0 ->
>        .... (* here we don't use x *)
>| ....
>
>But the typechecker reject it because of the unbound 'x' in the "Any"
>matching.
>
Hmm. to rewrite it so it works:

    | Int _ when (match e with Int x -> x > 0 | _ -> assert false) -> ...

:-)


-- 
John Max Skaller, mailto:skaller@ozemail.com.au
snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
voice:61-2-9660-0850




-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05  9:26 [Caml-list] Matching when Nicolas Cannasse
                   ` (2 preceding siblings ...)
  2002-08-05 15:50 ` John Max Skaller
@ 2002-08-05 16:02 ` Remi VANICAT
  2002-08-05 16:23   ` John Max Skaller
  2002-08-05 18:25 ` Oleg
  4 siblings, 1 reply; 15+ messages in thread
From: Remi VANICAT @ 2002-08-05 16:02 UTC (permalink / raw)
  To: caml-list

"Nicolas Cannasse" <warplayer@free.fr> writes:

> Hi !
>
> I was thinking that the following should be possible :
>
> match e with
> | Any
> | Int x when x > 0 ->
>         .... (* here we don't use x *)
> | ....

well, I won't say it's beautiful, but this work :

match (e, 10) with
  | (Any, t)
  | (Int t, _) when t > 0 -> 
               ....
  | ....

-- 
Rémi Vanicat
vanicat@labri.u-bordeaux.fr
http://dept-info.labri.u-bordeaux.fr/~vanicat
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05  9:41 ` Luc Maranget
@ 2002-08-05 16:13   ` John Max Skaller
  2002-08-05 19:29     ` Luc Maranget
  0 siblings, 1 reply; 15+ messages in thread
From: John Max Skaller @ 2002-08-05 16:13 UTC (permalink / raw)
  To: Luc Maranget; +Cc: Nicolas Cannasse, OCaml

Luc Maranget wrote:

>>What you are asking is ``pattern when expression'' to be a pattern.
>>Then your example would be parsed as
>>
>>That is your example is to to be parsed as
>> Any              <-- pattern   | 
>>|                               | Pattern (or pat)
>> Int x when x > 0 <-- pattern   |
>>->
>>  ...             <-- right hand side
>>
>>
>>Modifications are really important because this would make patterns and
>>expression mutually recursive, which they are not at the moment.
>>
The follwing code works in Felix [it prints "YES"]

#include <std.flx>

match (2,1) with
| ( (?x when x>=1), (?y when y >=1)) when x >=2 => { print "YES"; endl; }
| _ => { print "NO"; endl; }
endmatch;

wherein 'when' expressions are part of patterns, and as you can see,
can be nested within a pattern -- making the grammar for patterns
and expressions mutually recursive.

I'm curious as to what problems you perceive with
the mutual recursion.

-- 
John Max Skaller, mailto:skaller@ozemail.com.au
snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
voice:61-2-9660-0850




-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05 16:02 ` Remi VANICAT
@ 2002-08-05 16:23   ` John Max Skaller
  0 siblings, 0 replies; 15+ messages in thread
From: John Max Skaller @ 2002-08-05 16:23 UTC (permalink / raw)
  To: Remi VANICAT; +Cc: caml-list

Remi VANICAT wrote:

>"Nicolas Cannasse" <warplayer@free.fr> writes:
>
>>Hi !
>>
>>I was thinking that the following should be possible :
>>
>>match e with
>>| Any
>>| Int x when x > 0 ->
>>        .... (* here we don't use x *)
>>| ....
>>
>
>well, I won't say it's beautiful, but this work :
>
>match (e, 10) with
>  | (Any, t)
>  | (Int t, _) when t > 0 -> 
>               ....
>  | ....
>
Heh! This wins first prize for ugliest ocaml hack I have ever seen :-))

-- 
John Max Skaller, mailto:skaller@ozemail.com.au
snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
voice:61-2-9660-0850




-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05  9:26 [Caml-list] Matching when Nicolas Cannasse
                   ` (3 preceding siblings ...)
  2002-08-05 16:02 ` Remi VANICAT
@ 2002-08-05 18:25 ` Oleg
  2002-08-06  6:37   ` Florian Hars
  4 siblings, 1 reply; 15+ messages in thread
From: Oleg @ 2002-08-05 18:25 UTC (permalink / raw)
  To: OCaml

On Monday 05 August 2002 05:26 am, Nicolas Cannasse wrote:
> match e with
>
> | Any
> | Int x when x > 0 ->
>
>         .... (* here we don't use x *)
>
> | ....

What is "Any" ?  I looked in the keywords, values and types indexes of the 
O'Caml manual, and I did not find the answer.

Thanks
Oleg
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05 16:13   ` John Max Skaller
@ 2002-08-05 19:29     ` Luc Maranget
  2002-08-05 20:16       ` [Caml-list] Sharing Files between OCaml and C Michael Tucker
  0 siblings, 1 reply; 15+ messages in thread
From: Luc Maranget @ 2002-08-05 19:29 UTC (permalink / raw)
  To: John Max Skaller; +Cc: Luc Maranget, Nicolas Cannasse, OCaml

> 
> #include <std.flx>
> 
> match (2,1) with
> | ( (?x when x>=1), (?y when y >=1)) when x >=2 => { print "YES"; endl; }
> | _ => { print "NO"; endl; }
> endmatch;
> 
> wherein 'when' expressions are part of patterns, and as you can see,
> can be nested within a pattern -- making the grammar for patterns
> and expressions mutually recursive.
> 
> I'm curious as to what problems you perceive with
> the mutual recursion.
> 
> -- 
> John Max Skaller, mailto:skaller@ozemail.com.au
> snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
> voice:61-2-9660-0850
> 
> 
> 
> 

Nothing special, it is just an important change for a questionable
benefit....

Changing that would change many things in the front end, in
particular, the type-checker.

May be easy, may not be...



--Luc
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* [Caml-list] Sharing Files between OCaml and C
  2002-08-05 19:29     ` Luc Maranget
@ 2002-08-05 20:16       ` Michael Tucker
  2002-08-06 13:04         ` Olivier Andrieu
  0 siblings, 1 reply; 15+ messages in thread
From: Michael Tucker @ 2002-08-05 20:16 UTC (permalink / raw)
  To: OCaml

Hi,

  I would like to share access to a file between a C function and an OCaml
function in an application put together with CamlIDL. If I have a C
function with prototype:

int manip_file(FILE* f, int x);

  Is there any support in CamlIDL for passing a file that was opened in
OCaml. I checked the archives, and found a message that described pulling
out the integer file descriptor, and passing that to fdopen on the C side,
but that was it -- the same message asked about better support from
CamlIDL (this was winter 2000), but I couldn't find a response. Has this
changed over the past year and a half, or is that the best method?

Thanks,
Mike


-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Matching when
  2002-08-05 18:25 ` Oleg
@ 2002-08-06  6:37   ` Florian Hars
  0 siblings, 0 replies; 15+ messages in thread
From: Florian Hars @ 2002-08-06  6:37 UTC (permalink / raw)
  To: Oleg; +Cc: OCaml

Oleg wrote:
> What is "Any" ?  I looked in the keywords, values and types indexes of the 
> O'Caml manual, and I did not find the answer.

It is a cconstr-name:

   cconstr-name ::=  capitalized-ident
                  |  false
                  |  true
                  |  [ ]
                  |  ( )


It's probably part of some

   type t = Any | Int of int | Float of float | ...

Yours, Florian.
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Sharing Files between OCaml and C
  2002-08-05 20:16       ` [Caml-list] Sharing Files between OCaml and C Michael Tucker
@ 2002-08-06 13:04         ` Olivier Andrieu
  2002-08-06 14:01           ` Bruno.Verlyck
  0 siblings, 1 reply; 15+ messages in thread
From: Olivier Andrieu @ 2002-08-06 13:04 UTC (permalink / raw)
  To: Michael Tucker; +Cc: caml-list

 Michael Tucker [Monday 5 August 2002] :
 >
 > Hi,
 > 
 >   I would like to share access to a file between a C function and an
 > OCaml function in an application put together with CamlIDL. If I
 > have a C function with prototype:
 > 
 > int manip_file(FILE* f, int x);
 > 
 >   Is there any support in CamlIDL for passing a file that was opened in
 > OCaml. I checked the archives, and found a message that described
 > pulling out the integer file descriptor, and passing that to fdopen
 > on the C side, but that was it -- the same message asked about
 > better support from CamlIDL (this was winter 2000), but I couldn't
 > find a response. Has this changed over the past year and a half, or
 > is that the best method?

Yes, I think that's still the best method :
- get the descriptor with Unix.descr_of_in_channel or
  Unix.descr_of_out_channel 
- fdopen it on the C side
You might also want to call dup() on the fd so that your FILE* stream
is still working if the original caml channel is closed.

But maybe CamlIDL has improved, I don't know.

-- 
   Olivier
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Sharing Files between OCaml and C
  2002-08-06 13:04         ` Olivier Andrieu
@ 2002-08-06 14:01           ` Bruno.Verlyck
  2002-08-06 18:50             ` Lex Stein
  0 siblings, 1 reply; 15+ messages in thread
From: Bruno.Verlyck @ 2002-08-06 14:01 UTC (permalink / raw)
  To: andrieu; +Cc: mtucker, caml-list

   From: Olivier Andrieu <andrieu@ijm.jussieu.fr>
   Date: Tue, 6 Aug 2002 15:04:11 +0200

   Michael Tucker [Monday 5 August 2002] :
   > I would like to share access to a file between a C function and an OCaml
   > function in an application put together with CamlIDL.  If I have a C
   > function with prototype:
   >  int manip_file(FILE* f, int x);
   > Is there any support in CamlIDL for passing a file that was opened in
   > OCaml.  I checked the archives, and found a message that described pulling
   > out the integer file descriptor, and passing that to fdopen on the C side,
   > but that was it -- the same message asked about better support from CamlIDL
   > (this was winter 2000), but I couldn't find a response.  Has this changed
   > over the past year and a half, or is that the best method?
   Yes, I think that's still the best method:
   - get the descriptor with Unix.descr_of_in_channel or
     Unix.descr_of_out_channel
   - fdopen it on the C side
   You might also want to call dup() on the fd so that your FILE* stream is still
   working if the original caml channel is closed.
But of course you now have two concurrent buffering mechanisms, so flushing when
switching the writing side (C vs Caml) for out_channels is mandatory, and
seeking cautiously when switching the reading side (for in_channels) too.

Bruno.
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Sharing Files between OCaml and C
  2002-08-06 14:01           ` Bruno.Verlyck
@ 2002-08-06 18:50             ` Lex Stein
  2002-08-07 11:40               ` Bruno.Verlyck
  0 siblings, 1 reply; 15+ messages in thread
From: Lex Stein @ 2002-08-06 18:50 UTC (permalink / raw)
  To: Bruno.Verlyck; +Cc: andrieu, mtucker, caml-list


On POSIX compliant systems, Dup() does not, in fact, create a new vnode
for a file. It merely creates a new file descriptor table entry (in the
process's in-kernel descriptor table) that points to exactly the same
vnode. The two descriptors share the same buffered blocks in the global
buffer cache.

So if the C and Caml sides are sharing the same vnode, through dup'ed
descriptors, it should be sufficient to flush once on either the Caml
or C side.

If however, the two references to the file are independently created
using open, then the two descriptor table entries will point to
*distinct* vnodes with independent buffering and duplicate flushing
will be necessary (although one would have to be very careful not
to overwrite changes made to the same block by the other side-- a
motivator for using dup rather than open).

Lex

On Tue, 6 Aug 2002 Bruno.Verlyck@inria.fr wrote:

>    Yes, I think that's still the best method:
>    - get the descriptor with Unix.descr_of_in_channel or
>      Unix.descr_of_out_channel
>    - fdopen it on the C side
>    You might also want to call dup() on the fd so that your FILE* stream is still
>    working if the original caml channel is closed.
> But of course you now have two concurrent buffering mechanisms, so flushing when
> switching the writing side (C vs Caml) for out_channels is mandatory, and
> seeking cautiously when switching the reading side (for in_channels) too.
>
> Bruno.
> -------------------
> To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
> Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
>

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] Sharing Files between OCaml and C
  2002-08-06 18:50             ` Lex Stein
@ 2002-08-07 11:40               ` Bruno.Verlyck
  0 siblings, 0 replies; 15+ messages in thread
From: Bruno.Verlyck @ 2002-08-07 11:40 UTC (permalink / raw)
  To: stein; +Cc: andrieu, mtucker, caml-list

   Date: Tue, 6 Aug 2002 14:50:44 -0400 (EDT)
   From: Lex Stein <stein@eecs.harvard.edu>

   On POSIX compliant systems, dup() does not, in fact, create a new
   vnode for a file.  It merely creates a new file descriptor table
   entry (in the process's in-kernel descriptor table) that points to
   exactly the same vnode.  The two descriptors share the same
   buffered blocks in the global buffer cache.
The problem I was alluding to is a local (inside the Caml process)
buffering one: the Caml runtime doesn't use C stdio, and has its own
buffering scheme.  As the original poster told us about FILE * and
channels, I assumed he would mix I/O on channels and FILE * pointing
to the same file.  Then he has to be cautious.

Bruno.
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

end of thread, other threads:[~2002-08-07 11:40 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2002-08-05  9:26 [Caml-list] Matching when Nicolas Cannasse
2002-08-05  9:41 ` Luc Maranget
2002-08-05 16:13   ` John Max Skaller
2002-08-05 19:29     ` Luc Maranget
2002-08-05 20:16       ` [Caml-list] Sharing Files between OCaml and C Michael Tucker
2002-08-06 13:04         ` Olivier Andrieu
2002-08-06 14:01           ` Bruno.Verlyck
2002-08-06 18:50             ` Lex Stein
2002-08-07 11:40               ` Bruno.Verlyck
2002-08-05 13:05 ` [Caml-list] Matching when Pierre Weis
2002-08-05 15:50 ` John Max Skaller
2002-08-05 16:02 ` Remi VANICAT
2002-08-05 16:23   ` John Max Skaller
2002-08-05 18:25 ` Oleg
2002-08-06  6:37   ` Florian Hars

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).