caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Problem with precedence declaration in .mly file
@ 2007-10-30 14:00 Angela Zhu
  2007-10-30 14:20 ` [Caml-list] " Oliver Bandel
       [not found] ` <1193753915.47273d3bb15f2@webmail.in-berlin.de>
  0 siblings, 2 replies; 11+ messages in thread
From: Angela Zhu @ 2007-10-30 14:00 UTC (permalink / raw)
  To: caml-list

[-- Attachment #1: Type: text/plain, Size: 823 bytes --]

Hi all,

I have some problem with precedence declaration in OCaml parser.
If I what to say exponential(ATOB) is prior to *(STAR) and / (DIVIDE),
  * and / are prior to +(PLUS)  and -(MINUS),
I wrote the following in the parser:


/***** Precedence Rules  *****/
...
%left PLUS MINUS
%left STAR DIVIDE
%left ATOB
...

But I still have the following problems:
(1) It appears that the parser
reads "test = 2^2 + 7;" as "test = 2^9" instead of "test = 4+7", which
would follow the conventional order of operations.

(2)It also interprets "test = (1^2)/3 + 1;" as "test = (1 ^ 2
/ (3 + 1));"

Can any one help me to see why it happens? Why the precedence rules  
doesn't work?

Thanks,
Angela
------------------------------------------
Dept. of CS, Rice U.
http://www.cs.rice.edu/~yz2/
------------------------------------------

[-- Attachment #2: Type: text/html, Size: 5311 bytes --]

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

* Re: [Caml-list] Problem with precedence declaration in .mly file
  2007-10-30 14:00 Problem with precedence declaration in .mly file Angela Zhu
@ 2007-10-30 14:20 ` Oliver Bandel
       [not found] ` <1193753915.47273d3bb15f2@webmail.in-berlin.de>
  1 sibling, 0 replies; 11+ messages in thread
From: Oliver Bandel @ 2007-10-30 14:20 UTC (permalink / raw)
  To: caml-list

Zitat von Angela Zhu <angela.zhu@cs.rice.edu>:

> Hi all,
>
> I have some problem with precedence declaration in OCaml parser.
> If I what to say exponential(ATOB) is prior to *(STAR) and / (DIVIDE),
>   * and / are prior to +(PLUS)  and -(MINUS),
> I wrote the following in the parser:
>
>
> /***** Precedence Rules  *****/
> ...
> %left PLUS MINUS
> %left STAR DIVIDE
> %left ATOB
> ...
>
> But I still have the following problems:
> (1) It appears that the parser
> reads "test = 2^2 + 7;" as "test = 2^9" instead of "test = 4+7", which
> would follow the conventional order of operations.
>
> (2)It also interprets "test = (1^2)/3 + 1;" as "test = (1 ^ 2
> / (3 + 1));"
>
> Can any one help me to see why it happens? Why the precedence rules
> doesn't work?
[...]

Precedences also can be created by sophisticated
organization of the grammar rules.

So, if your grammar rules may have a contradictory
meaning, then your parser works not as expected.

In general I would use the precedence-declarations only,
when you run into parser conflicts, if you don't use them.
When developing a grammr, I would recommend, first to start
with the grammar rules, and add precedence-/associatitivity-
declarations, at the end, if really necessary.


What is the rest of your mly-file?

A complete example would be helpful.


Ciao,
   Oliver


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

* Re: [Caml-list] Problem with precedence declaration in .mly file
       [not found] ` <1193753915.47273d3bb15f2@webmail.in-berlin.de>
@ 2007-10-31  4:11   ` Angela Zhu
  2007-10-31  4:26   ` Angela Zhu
  1 sibling, 0 replies; 11+ messages in thread
From: Angela Zhu @ 2007-10-31  4:11 UTC (permalink / raw)
  To: caml-list

[-- Attachment #1: Type: text/plain, Size: 3169 bytes --]


On Oct 30, 2007, at 9:18 AM, Oliver Bandel wrote:

> Zitat von Angela Zhu <angela.zhu@cs.rice.edu>:
>
>> Hi all,
>>
>> I have some problem with precedence declaration in OCaml parser.
>> If I what to say exponential(ATOB) is prior to *(STAR) and /  
>> (DIVIDE),
>>   * and / are prior to +(PLUS)  and -(MINUS),
>> I wrote the following in the parser:
>>
>>
>> /***** Precedence Rules  *****/
>> ...
>> %left PLUS MINUS
>> %left STAR DIVIDE
>> %left ATOB
>> ...
>>
>> But I still have the following problems:
>> (1) It appears that the parser
>> reads "test = 2^2 + 7;" as "test = 2^9" instead of "test = 4+7",  
>> which
>> would follow the conventional order of operations.
>>
>> (2)It also interprets "test = (1^2)/3 + 1;" as "test = (1 ^ 2
>> / (3 + 1));"
>>
>> Can any one help me to see why it happens? Why the precedence rules
>> doesn't work?
> [...]
>
> Precedences also can be created by sophisticated
> organization of the grammar rules.
But I want to avoid this.
>
> So, if your grammar rules may have a contradictory
> meaning, then your parser works not as expected.
>
> In general I would use the precedence-declarations only,
> when you run into parser conflicts, if you don't use them.
> When developing a grammr, I would recommend, first to start
> with the grammar rules, and add precedence-/associatitivity-
> declarations, at the end, if really necessary.
>
>
> What is the rest of your mly-file?
>
> A complete example would be helpful.
Here is part of my .mly file:
Beside the precedence issue, everything works fine.

  %{

open Past
open Parsing
open ParseError

let pi = 4.0 *. atan 1.0;;

let get_range n = {
   pos_start = Parsing.rhs_start_pos n;
   pos_end = Parsing.rhs_end_pos n;
}

let unclosed opening_name opening_num closing_name closing_num =
   raise(Error(Unclosed(get_range opening_num, opening_name,
                        get_range closing_num, closing_name)))
%}

/* List of all tokens the lexer can output */

...

%token PLUS
%token STAR
%token MINUS
%token DIVIDE
%token AND	
%token OR
...

%token ATOB  /* A^B: exponential */
...


/***** Precedence Rules  *****/
%left PLUS MINUS
%left STAR DIVIDE
%left ATOB
%nonassoc prec_unary_minus


%start prog

%type <Past.pprog> prog

%%

/* Rules for parsing. The parsing rules should generally be in a */
/* one-to-one correspondence with the BNF */
/* type prog = Prog of consDeclare list * varDeclare list *  
inpDeclare list * sysDeclare list */




prog:

exp:
    LPAREN exp RPAREN          { $2 }
  | LPAREN exp error           { unclosed "(" 1 ")" 3 }

  | exp PLUS exp					{ Add($1, $3) }
  | MINUS exp  					{ Sub(Value(VFloat(0.0)), $2) }
  | exp MINUS exp             	{ Sub($1, $3) }
  | exp DIVIDE exp				{ Divide($1, $3) }
  | exp STAR exp              	{ Mult($1, $3) }
  | exp ATOB exp              	{ Atob($1, $3) }


  | value PLUS exp				{ Add(Value($1), $3) }
  | value MINUS exp             	{ Sub(Value($1), $3) }
  | value DIVIDE exp				{ Divide(Value($1), $3) }
  | value STAR exp              	{ Mult(Value($1), $3) }
  | value ATOB exp              	{ Atob(Value($1), $3) }


...

  | IDENT						{ Id($1) }
  | value						{ Value($1) }


;


...





[-- Attachment #2: Type: text/html, Size: 44813 bytes --]

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

* Re: [Caml-list] Problem with precedence declaration in .mly file
       [not found] ` <1193753915.47273d3bb15f2@webmail.in-berlin.de>
  2007-10-31  4:11   ` Angela Zhu
@ 2007-10-31  4:26   ` Angela Zhu
  2007-10-31  5:52     ` skaller
  2007-10-31 11:52     ` Peter Ilberg
  1 sibling, 2 replies; 11+ messages in thread
From: Angela Zhu @ 2007-10-31  4:26 UTC (permalink / raw)
  To: caml-list

[-- Attachment #1: Type: text/plain, Size: 2363 bytes --]


On Oct 30, 2007, at 9:18 AM, Oliver Bandel wrote:
Zitat von Angela Zhu <angela.zhu@cs.rice.edu>:

Hi all,

I have some problem with precedence declaration in OCaml parser.
If I what to say exponential(ATOB) is prior to *(STAR) and / (DIVIDE),
   * and / are prior to +(PLUS)  and -(MINUS),
I wrote the following in the parser:


/***** Precedence Rules  *****/
...
%left PLUS MINUS
%left STAR DIVIDE
%left ATOB
...

But I still have the following problems:
(1) It appears that the parser
reads "test = 2^2 + 7;" as "test = 2^9" instead of "test = 4+7", which
would follow the conventional order of operations.

(2)It also interprets "test = (1^2)/3 + 1;" as "test = (1 ^ 2
/ (3 + 1));"

Can any one help me to see why it happens? Why the precedence rules
doesn't work?
[...]

Precedences also can be created by sophisticated
organization of the grammar rules.
But I want to avoid this.

So, if your grammar rules may have a contradictory
meaning, then your parser works not as expected.

In general I would use the precedence-declarations only,
when you run into parser conflicts, if you don't use them.
When developing a grammr, I would recommend, first to start
with the grammar rules, and add precedence-/associatitivity-
declarations, at the end, if really necessary.


What is the rest of your mly-file?

A complete example would be helpful.
Here is part of my .mly file:
Beside the precedence issue, everything works fine.

  %{

open Past
...
%}

...

%token PLUS
%token STAR
%token MINUS
%token DIVIDE
%token AND	
%token OR
...

%token ATOB  /* A^B: exponential */
...


/***** Precedence Rules  *****/
%left PLUS MINUS
%left STAR DIVIDE
%left ATOB
%nonassoc prec_unary_minus


%start prog

%type <Past.pprog> prog

%%
prog:
...
exp:
...
  | exp PLUS exp					{ Add($1, $3) }
  | MINUS exp  					{ Sub(Value(VFloat(0.0)), $2) }
  | exp MINUS exp             	{ Sub($1, $3) }
  | exp DIVIDE exp				{ Divide($1, $3) }
  | exp STAR exp              	{ Mult($1, $3) }
  | exp ATOB exp              	{ Atob($1, $3) }


  | value PLUS exp				{ Add(Value($1), $3) }
  | value MINUS exp             	{ Sub(Value($1), $3) }
  | value DIVIDE exp				{ Divide(Value($1), $3) }
  | value STAR exp              	{ Mult(Value($1), $3) }
  | value ATOB exp              	{ Atob(Value($1), $3) }


...

  | IDENT						{ Id($1) }
  | value						{ Value($1) }


;


...





[-- Attachment #2: Type: text/html, Size: 35083 bytes --]

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

* Re: [Caml-list] Problem with precedence declaration in .mly file
  2007-10-31  4:26   ` Angela Zhu
@ 2007-10-31  5:52     ` skaller
       [not found]       ` <BE3BA36D-7E69-426F-B558-26CBCF9D78F6@cs.rice.edu>
  2007-10-31 11:52     ` Peter Ilberg
  1 sibling, 1 reply; 11+ messages in thread
From: skaller @ 2007-10-31  5:52 UTC (permalink / raw)
  To: Angela Zhu; +Cc: caml-list


On Tue, 2007-10-30 at 23:26 -0500, Angela Zhu wrote:

> /***** Precedence Rules  *****/
> ...
> %left PLUS MINUS
> %left STAR DIVIDE
> %left ATOB

> Can any one help me to see why it happens? Why the precedence rules
> doesn't work?

> Precedences also can be created by sophisticated
> organization of the grammar rules.
> But I want to avoid this.

DO NOT USE THEM. The rules are hard to explain and very badly
designed, in other words, they're a hack. Ocaml provides
them for compatibility with older yacc like tools.

Write your grammar properly instead, in pseudo code:

	term = factor | term + factor
	factor = atom | factor * atom
	atom = INTEGER | ( term )


gives the precedence of * over + and left associativity,
without using incomprehensible precedence rules. 


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


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

* Re: Re:  Re: [Caml-list] Problem with precedence declaration in .mly  file
       [not found]         ` <1193814307.8355.68.camel@rosella.wigram>
@ 2007-10-31  7:16           ` Angela Zhu
  0 siblings, 0 replies; 11+ messages in thread
From: Angela Zhu @ 2007-10-31  7:16 UTC (permalink / raw)
  To: skaller; +Cc: caml-list

Thanks a lot for your detailed explanation.
The problem is that now the AST for my language is getting really big.
I am not sure how much work it will take.

Best regards,
Angela
------------------------------------------
Dept. of CS, Rice Unitersity
http://www.cs.rice.edu/~yz2/
------------------------------------------



On Oct 31, 2007, at 2:05 AM, skaller wrote:

>
> On Wed, 2007-10-31 at 01:02 -0500, Angela Zhu wrote:
>>>
>>>
>>> DO NOT USE THEM. The rules are hard to explain and very badly
>>> designed, in other words, they're a hack. Ocaml provides
>>> them for compatibility with older yacc like tools.
>>>
>>> Write your grammar properly instead, in pseudo code:
>>>
>>> 	term = factor | term + factor
>>> 	factor = atom | factor * atom
>>> 	atom = INTEGER | ( term )
>>
>> ... Then I need to change my whole AST.....
>> :(
>
> Yes, that's possible. The 'simple' AST isn't efficient,
> that is, where you have a variant
>
> 	type term = Term_Factor of factor | Term_plus of term * factor
>
> because of the first case. However this isn't necessary if you just
> use something like
>
> 	type expr = Integer of int | Apply of string * expr list
>
> then you can just do:
>
> 	term:
> 	| factor { $1 }
> 	| term + factor { Apply  ("+",[$1;$3]) }
>
> and similarly for the other productions. The typing here
> is weaker than you may want, for example you can get
> nonsense like
>
> 	Apply ["*",Integer 1]
>
> so you might try a safer encoding, eg using
>
> 	| Integer of int
> 	| Unary of string * expr
> 	| Binary of string * expr * expr
> 	
>
> The point is, this AST is still less structured than one
> which exactly reflects the syntax tree -- but that is the
> point of an 'Abstract' syntax tree (AST).
>
> Exactly how much work you do in the parser is a difficult
> design choice.
>
>
> -- 
> John Skaller <skaller at users dot sf dot net>
> Felix, successor to C++: http://felix.sf.net
>


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

* Re: [Caml-list] Problem with precedence declaration in .mly file
  2007-10-31  4:26   ` Angela Zhu
  2007-10-31  5:52     ` skaller
@ 2007-10-31 11:52     ` Peter Ilberg
  2007-10-31 13:51       ` Angela Zhu
  1 sibling, 1 reply; 11+ messages in thread
From: Peter Ilberg @ 2007-10-31 11:52 UTC (permalink / raw)
  To: Angela Zhu; +Cc: caml-list


I have no experience with ocamlyacc, but looking at your grammar below, it 
seems that you don't need the 'value PLUS exp' etc rules. All these cases 
should be covered already by the 'exp PLUS exp' rules at the beginning and 
the 'value' rule at the end.

Try removing the 'value PLUS exp' rules. Maybe ocamlyacc gets confused 
if it has two sets of productions that it has to disambiguate with 
precedence rules.

--- Peter

On Tue, 30 Oct 2007, Angela Zhu wrote:
> exp:
> ...
> | exp PLUS exp					{ Add($1, $3) }
> | MINUS exp  					{ Sub(Value(VFloat(0.0)), $2) 
> }
> | exp MINUS exp             	{ Sub($1, $3) }
> | exp DIVIDE exp				{ Divide($1, $3) }
> | exp STAR exp              	{ Mult($1, $3) }
> | exp ATOB exp              	{ Atob($1, $3) }

*** do you really need these productions?
> | value PLUS exp				{ Add(Value($1), $3) }
> | value MINUS exp             	{ Sub(Value($1), $3) }
> | value DIVIDE exp				{ Divide(Value($1), $3) }
> | value STAR exp              	{ Mult(Value($1), $3) }
> | value ATOB exp              	{ Atob(Value($1), $3) }
***

> ...
>
> | IDENT						{ Id($1) }
> | value						{ Value($1) }
>
>
> ;


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

* Re: [Caml-list] Problem with precedence declaration in .mly file
  2007-10-31 11:52     ` Peter Ilberg
@ 2007-10-31 13:51       ` Angela Zhu
  2007-10-31 14:14         ` Thomas Gazagnaire
  0 siblings, 1 reply; 11+ messages in thread
From: Angela Zhu @ 2007-10-31 13:51 UTC (permalink / raw)
  To: Peter Ilberg; +Cc: caml-list


On Oct 31, 2007, at 6:52 AM, Peter Ilberg wrote:

>
> I have no experience with ocamlyacc, but looking at your grammar  
> below, it seems that you don't need the 'value PLUS exp' etc rules.  
> All these cases should be covered already by the 'exp PLUS exp'  
> rules at the beginning and the 'value' rule at the end.
>
> Try removing the 'value PLUS exp' rules. Maybe ocamlyacc gets  
> confused if it has two sets of productions that it has to  
> disambiguate with precedence rules.

I removed 'value PLUS exp' rules.
The precedence is still not correct, what is more, 1+ t (with t  
declared) gives a syntax error.

Thanks,
Angela



>
> --- Peter


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

* Re: [Caml-list] Problem with precedence declaration in .mly file
  2007-10-31 13:51       ` Angela Zhu
@ 2007-10-31 14:14         ` Thomas Gazagnaire
  2007-10-31 14:40           ` Angela Zhu
  0 siblings, 1 reply; 11+ messages in thread
From: Thomas Gazagnaire @ 2007-10-31 14:14 UTC (permalink / raw)
  To: caml-list

The following code works perfectly for me. Maybe you introduce some 
undesired precedence rules in your grammar rules.


----

%token <int> INT
%token PLUS MINUS DIVIDE STAR ATOB END

%start main
%type <int> main

%left PLUS MINUS
%left STAR DIVIDE
%left ATOB

%%


main:
| expr END { $1 }

expr:
| INT { $1 }
| expr PLUS expr { $1 + $3 }
| expr MINUS expr { $1 - $3 }
| expr DIVIDE expr { $1 / $3 }
| expr STAR expr { $1 * $3 }
| expr ATOB expr { int_of_float ( (float_of_int $1) ** (float_of_int $3) ) }
;

---

And then "2^2+7\n" gives me "11"

Cheers,
Thomas

Angela Zhu a écrit :
> 
> On Oct 31, 2007, at 6:52 AM, Peter Ilberg wrote:
> 
>>
>> I have no experience with ocamlyacc, but looking at your grammar 
>> below, it seems that you don't need the 'value PLUS exp' etc rules. 
>> All these cases should be covered already by the 'exp PLUS exp' rules 
>> at the beginning and the 'value' rule at the end.
>>
>> Try removing the 'value PLUS exp' rules. Maybe ocamlyacc gets confused 
>> if it has two sets of productions that it has to disambiguate with 
>> precedence rules.
> 
> I removed 'value PLUS exp' rules.
> The precedence is still not correct, what is more, 1+ t (with t 
> declared) gives a syntax error.
> 
> Thanks,
> Angela
> 
> 
> 
>>
>> --- Peter
> 
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs


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

* Re: [Caml-list] Problem with precedence declaration in .mly file
  2007-10-31 14:14         ` Thomas Gazagnaire
@ 2007-10-31 14:40           ` Angela Zhu
       [not found]             ` <472894EC.8040902@irisa.fr>
  0 siblings, 1 reply; 11+ messages in thread
From: Angela Zhu @ 2007-10-31 14:40 UTC (permalink / raw)
  To: Thomas Gazagnaire; +Cc: caml-list

[-- Attachment #1: Type: text/plain, Size: 2288 bytes --]

But here are  all the precedence rules I have:

/***** Precedence Rules  *****/
%left GT LT
%left PLUS MINUS
%left STAR DIVIDE
%left ATOB
%nonassoc prec_unary_minus


-Angela


On Oct 31, 2007, at 9:14 AM, Thomas Gazagnaire wrote:

> The following code works perfectly for me. Maybe you introduce some  
> undesired precedence rules in your grammar rules.
>
>
> ----
>
> %token <int> INT
> %token PLUS MINUS DIVIDE STAR ATOB END
>
> %start main
> %type <int> main
>
> %left PLUS MINUS
> %left STAR DIVIDE
> %left ATOB
>
> %%
>
>
> main:
> | expr END { $1 }
>
> expr:
> | INT { $1 }
> | expr PLUS expr { $1 + $3 }
> | expr MINUS expr { $1 - $3 }
> | expr DIVIDE expr { $1 / $3 }
> | expr STAR expr { $1 * $3 }
> | expr ATOB expr { int_of_float ( (float_of_int $1) **  
> (float_of_int $3) ) }
> ;
>
> ---
>
> And then "2^2+7\n" gives me "11"
>
> Cheers,
> Thomas
>
> Angela Zhu a écrit :
>> On Oct 31, 2007, at 6:52 AM, Peter Ilberg wrote:
>>>
>>> I have no experience with ocamlyacc, but looking at your grammar  
>>> below, it seems that you don't need the 'value PLUS exp' etc  
>>> rules. All these cases should be covered already by the 'exp PLUS  
>>> exp' rules at the beginning and the 'value' rule at the end.
>>>
>>> Try removing the 'value PLUS exp' rules. Maybe ocamlyacc gets  
>>> confused if it has two sets of productions that it has to  
>>> disambiguate with precedence rules.
>> I removed 'value PLUS exp' rules.
>> The precedence is still not correct, what is more, 1+ t (with t  
>> declared) gives a syntax error.
>> Thanks,
>> Angela
>>>
>>> --- Peter
>> _______________________________________________
>> Caml-list mailing list. Subscription management:
>> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
>> Archives: http://caml.inria.fr
>> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
>> Bug reports: http://caml.inria.fr/bin/caml-bugs
>
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>


[-- Attachment #2: Type: text/html, Size: 11070 bytes --]

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

* Re: [Caml-list] Problem with precedence declaration in .mly file
       [not found]                 ` <47289C47.8020609@irisa.fr>
@ 2007-10-31 15:34                   ` Angela Zhu
  0 siblings, 0 replies; 11+ messages in thread
From: Angela Zhu @ 2007-10-31 15:34 UTC (permalink / raw)
  To: Thomas Gazagnaire; +Cc: caml-list

[-- Attachment #1: Type: text/plain, Size: 554 bytes --]

Thanks Thomas!
And thanks for all the help I got!
The problem is solved at this point.

Regards,
Angela
------------------------------------------
Dept. of CS, Rice Unitersity
http://www.cs.rice.edu/~yz2/
------------------------------------------


On Oct 31, 2007, at 10:16 AM, Thomas Gazagnaire wrote:

> Well, I think you have a problem in your grammar rules. Your are  
> defining the same PLUS, MINUS, STAR and DIVIDE rules in multiple  
> places in your code. Try to define them once, only in the "exp"  
> rule. Them, remove in the "exp" rule :


[-- Attachment #2: Type: text/html, Size: 1412 bytes --]

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

end of thread, other threads:[~2007-10-31 15:34 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-10-30 14:00 Problem with precedence declaration in .mly file Angela Zhu
2007-10-30 14:20 ` [Caml-list] " Oliver Bandel
     [not found] ` <1193753915.47273d3bb15f2@webmail.in-berlin.de>
2007-10-31  4:11   ` Angela Zhu
2007-10-31  4:26   ` Angela Zhu
2007-10-31  5:52     ` skaller
     [not found]       ` <BE3BA36D-7E69-426F-B558-26CBCF9D78F6@cs.rice.edu>
     [not found]         ` <1193814307.8355.68.camel@rosella.wigram>
2007-10-31  7:16           ` Re: " Angela Zhu
2007-10-31 11:52     ` Peter Ilberg
2007-10-31 13:51       ` Angela Zhu
2007-10-31 14:14         ` Thomas Gazagnaire
2007-10-31 14:40           ` Angela Zhu
     [not found]             ` <472894EC.8040902@irisa.fr>
     [not found]               ` <F5672A31-E4C0-488B-B594-F75E3DA262D8@cs.rice.edu>
     [not found]                 ` <47289C47.8020609@irisa.fr>
2007-10-31 15:34                   ` Angela Zhu

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