Mailing list for all users of the OCaml language and system.
 help / color / mirror / Atom feed
* Camlp4 help
@ 2009-03-21  3:41 Andre Nathan
  2009-03-21 15:26 ` [Caml-list] " blue storm
  0 siblings, 1 reply; 7+ messages in thread
From: Andre Nathan @ 2009-03-21  3:41 UTC (permalink / raw)
  To: caml-list

Hello

I'm just beginning with camlp4 here, and I'm stuck with what I think is
a precedence issue. I have the following syntax extension:

open Camlp4.PreCast
open Syntax

let sum = Gram.Entry.mk "sum"

EXTEND Gram
  expr: LEVEL "top"
    [ [ "sum"; "do"; seq = LIST1 sum; "done" ->
        <:expr< do { $list:seq$ } >> ] ]
    ;
  sum:
    [ [ x = expr; "plus"; y = expr ->
        <:expr< $x$ + $y$ >> ] ]
    ;
END

This works fine for something like this:

sum do
  1 plus 2
done

which becomes (1 + 2).

However, it breaks on

sum do
  let a = 1 in
  let b = 2 in
  a plus b
done

because it becomes ((let a = 1 in let b = 2 in a) + b).

How can fix that (allowing "b" to be in scope for the second argument of
"plus")?

Also, sequences of operations don't parse:

sum do
  1 + 2;
  3 + 4
done

gives "Parse error: [sum] or "done" expected (in [expr])"

What am I missing here?

Thanks in advance,
Andre


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

* Re: [Caml-list] Camlp4 help
  2009-03-21  3:41 Camlp4 help Andre Nathan
@ 2009-03-21 15:26 ` blue storm
  2009-03-21 16:14   ` Andre Nathan
  0 siblings, 1 reply; 7+ messages in thread
From: blue storm @ 2009-03-21 15:26 UTC (permalink / raw)
  To: Andre Nathan; +Cc: caml-list

This is not a camlp4-specific problem : the grammar you described
apparently do not conform to what you have in mind.

According to your definition, the "sum do ... done" can only contain
"sum" forms, not an arbitrary expression. The only valid way to parse
"sum do let a = b in a plus c done" is thus "sum do (let a = b in a)
plus b done", as "sum do let a = b in (a plus b) done" has an
expression (instead of a sum) between do ... done (and a sum in expr
position, wich is also incorrect, but it can also be parsed as a
correct expression).

What is the syntax you want to be supported ?

On 3/21/09, Andre Nathan <andre@sneakymustard.com> wrote:
> Hello
>
> I'm just beginning with camlp4 here, and I'm stuck with what I think is
> a precedence issue. I have the following syntax extension:
>
> open Camlp4.PreCast
> open Syntax
>
> let sum = Gram.Entry.mk "sum"
>
> EXTEND Gram
>   expr: LEVEL "top"
>     [ [ "sum"; "do"; seq = LIST1 sum; "done" ->
>         <:expr< do { $list:seq$ } >> ] ]
>     ;
>   sum:
>     [ [ x = expr; "plus"; y = expr ->
>         <:expr< $x$ + $y$ >> ] ]
>     ;
> END
>
> This works fine for something like this:
>
> sum do
>   1 plus 2
> done
>
> which becomes (1 + 2).
>
> However, it breaks on
>
> sum do
>   let a = 1 in
>   let b = 2 in
>   a plus b
> done
>
> because it becomes ((let a = 1 in let b = 2 in a) + b).
>
> How can fix that (allowing "b" to be in scope for the second argument of
> "plus")?
>
> Also, sequences of operations don't parse:
>
> sum do
>   1 + 2;
>   3 + 4
> done
>
> gives "Parse error: [sum] or "done" expected (in [expr])"
>
> What am I missing here?
>
> Thanks in advance,
> Andre
>
> _______________________________________________
> 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] 7+ messages in thread

* Re: [Caml-list] Camlp4 help
  2009-03-21 15:26 ` [Caml-list] " blue storm
@ 2009-03-21 16:14   ` Andre Nathan
  2009-03-21 17:24     ` blue storm
  0 siblings, 1 reply; 7+ messages in thread
From: Andre Nathan @ 2009-03-21 16:14 UTC (permalink / raw)
  To: blue storm; +Cc: caml-list

Hi

On Sat, 2009-03-21 at 16:26 +0100, blue storm wrote:
> This is not a camlp4-specific problem : the grammar you described
> apparently do not conform to what you have in mind.

I think I understand, although I thought the "x = expr" rule in the sum
form definition meant that before "plus" any expression would be
allowed.

I want to allow any expression inside a "sum" block, which I think I
could do by defining it as a new rule in "expr", but I'd like "plus"
expressions to only be allowed inside a "sum" block, which I'm not sure
how to do.

Thanks,
Andre

> 
> According to your definition, the "sum do ... done" can only contain
> "sum" forms, not an arbitrary expression. The only valid way to parse
> "sum do let a = b in a plus c done" is thus "sum do (let a = b in a)
> plus b done", as "sum do let a = b in (a plus b) done" has an
> expression (instead of a sum) between do ... done (and a sum in expr
> position, wich is also incorrect, but it can also be parsed as a
> correct expression).
> 
> What is the syntax you want to be supported ?
> 
> On 3/21/09, Andre Nathan <andre@sneakymustard.com> wrote:
> > Hello
> >
> > I'm just beginning with camlp4 here, and I'm stuck with what I think is
> > a precedence issue. I have the following syntax extension:
> >
> > open Camlp4.PreCast
> > open Syntax
> >
> > let sum = Gram.Entry.mk "sum"
> >
> > EXTEND Gram
> >   expr: LEVEL "top"
> >     [ [ "sum"; "do"; seq = LIST1 sum; "done" ->
> >         <:expr< do { $list:seq$ } >> ] ]
> >     ;
> >   sum:
> >     [ [ x = expr; "plus"; y = expr ->
> >         <:expr< $x$ + $y$ >> ] ]
> >     ;
> > END
> >
> > This works fine for something like this:
> >
> > sum do
> >   1 plus 2
> > done
> >
> > which becomes (1 + 2).
> >
> > However, it breaks on
> >
> > sum do
> >   let a = 1 in
> >   let b = 2 in
> >   a plus b
> > done
> >
> > because it becomes ((let a = 1 in let b = 2 in a) + b).
> >
> > How can fix that (allowing "b" to be in scope for the second argument of
> > "plus")?
> >
> > Also, sequences of operations don't parse:
> >
> > sum do
> >   1 + 2;
> >   3 + 4
> > done
> >
> > gives "Parse error: [sum] or "done" expected (in [expr])"
> >
> > What am I missing here?
> >
> > Thanks in advance,
> > Andre
> >
> > _______________________________________________
> > 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


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

* Re: [Caml-list] Camlp4 help
  2009-03-21 16:14   ` Andre Nathan
@ 2009-03-21 17:24     ` blue storm
  2009-03-21 17:26       ` blue storm
  0 siblings, 1 reply; 7+ messages in thread
From: blue storm @ 2009-03-21 17:24 UTC (permalink / raw)
  To: Andre Nathan; +Cc: caml-list

On 3/21/09, Andre Nathan <andre@sneakymustard.com> wrote:
> I think I understand, although I thought the "x = expr" rule in the sum
> form definition meant that before "plus" any expression would be
> allowed.

What you wanted is   let a = b in (a plus b). The expression is not
before plus, plus is inside the expression. Your rule means that
inside plus, the left member can be an expression (eg. (let a = b in
a) plus b).

> I want to allow any expression inside a "sum" block, which I think I
> could do by defining it as a new rule in "expr", but I'd like "plus"
> expressions to only be allowed inside a "sum" block, which I'm not sure
> how to do.

I see (but there may be a better choice) two solutions :
- create a new structure expression_inside_sum wich is a complete copy
of "expr" with sums added. This is ugly and redundant.
- use a "marker" trick in two pass :
   - in your grammar you "mark" plus nodes by translating them into a
specific AST node (wich cannot be produced by any usual camlp4
construct), for example "a plus b" -> <:expr< $id:"camlp4.plus"$ a b
>>
   - then you use an Ast.map or a Camlp4Filter to explore the
resulting AST, translating the marked nodes (the ones with
"camlp4.plus" as identifiers) into different things depending on
wether you're inside a sum-block or not (or possibly raising an error
outside a sum-block).

If you want an example, I used a similar trick in my "pa_holes"
extension : "\1"-like identifiers are allowed only inside a (\ ... )
block; at first they're allowed everywhere (the "ident" rule is
changed), then they're transformed into a valid camlp4 construction
inside the (\ ... ) blocks ("expr" rule), and finally the AST is
explored and any remaining \n raise an error (Remove_holes filter).

This solution is also ugly, but has little redudancy.


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

* Re: [Caml-list] Camlp4 help
  2009-03-21 17:24     ` blue storm
@ 2009-03-21 17:26       ` blue storm
  0 siblings, 0 replies; 7+ messages in thread
From: blue storm @ 2009-03-21 17:26 UTC (permalink / raw)
  To: Andre Nathan; +Cc: caml-list

Oops, missing code : http://bluestorm.info/camlp4/pa_holes.ml.html


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

* Camlp4 help
@ 2009-04-13  0:05 Andre Nathan
  0 siblings, 0 replies; 7+ messages in thread
From: Andre Nathan @ 2009-04-13  0:05 UTC (permalink / raw)
  To: caml-list

Hello

I'm adding support for property testing in OSpec. Currently you can
write a specification like

  forall (list_of int) (fun l -> (List.rev (List.rev l)) should = l)

and it's also possible to add a constraint as in

  forall (list_of int) ~given:(fun l -> List.length l > 0)
         (fun l -> l should match x::xs)

This automatically generates lists of random sizes containing random
elements, and runs the specified property for each of them. I've been
trying to turn this into a syntax extension that would look like

  forall (list_of int) l . (List.rev (List.rev l)) should = l

or

  forall (list_of int) l . List.length l > 0 => l should match x::xs

The best I could to to make this work was forcing parenthesis around the
expression that comes after the dot, with the following rule:

  "forall"; "("; gen = expr; ")"; var = ipatt; "."; OPT "(";
  e1 = expr; OPT ")"; impl = OPT "=>"; e2 = OPT expr ->

With that I can write the two specifications above as

  forall (list_of int) l . ((List.rev (List.rev l)) should = l)

and

  forall (list_of int) l . (List.length l > 0) => l should match x::xs

which is not that bad, but not exactly what I wanted... 

If I simplify the rule above to

  "forall"; "("; gen = expr; ")"; var = ipatt; ".";
  e1 = expr; impl = OPT "=>"; e2 = OPT expr ->

then everything after the dot is bound to e1, even when there's a "=>". 

Is there some other matcher in camlp4 other than "expr" that I could use
for that? If not, is there another way to parse this correctly without
the extra parenthesis?

Thanks in advance,
Andre


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

* camlp4 help
@ 2005-07-15  8:39 Pietro Abate
  0 siblings, 0 replies; 7+ messages in thread
From: Pietro Abate @ 2005-07-15  8:39 UTC (permalink / raw)
  To: ocaml ml

Hi all,
I'm having problems (once again) with camlp4...

I'd like to parse and produce a bit of ocaml code out of the
following description :

---------------------
CONNECTIVES
    "_&_",AssocLeft,And ;
    "_v_",AssocLeft,Or
END

TABLEAU

    RULE "And"
    { A & B }
    ----------
      A ; B
    END

END
---------------

The first time around I used quotes around the "{A & B}" and parsed the
expression with a adhoc parser outside camlp4 (and it's all good and
working).  Now I want to remove the quotes tut-cur and do everything
using the pre-processor (quotes make my code quote un-readable).  I've
started writing this code below, but I don't know how to proceed...

The main problem is of course that I've to parse an expression (in rule),
with a generic parser built on the top of the connectives that I've just
declared. Is there a way to tell campl4 : pass everything in between 
RULE and END to a function my_parser ?

I was looking for inspiration in M. Jambon excellent tutorial, but 
without much luck... 

thanks,
p

-----------------------(not tested)
let rule = Grammar.Entry.create Pcaml.gram "rule";;
let connective = Grammar.Entry.create Pcaml.gram "connective";;

type assoc = |AssocLeft |AssocRight |AssocNone ;;

let conntable = Hashtbl.create 15;;

EXTEND
  Pcaml.str_item: [
    "CONNECTIVES"; clist = LIST1 connective SEP ";"; "END" ->
      List.iter Hashtbl.add conntable clist;
      <:str_item< value version = "connectives declared" >>
    |"TABLEAU"; LIST1 rule; "END" ->
        <:str_item< value version = "tableau declared" >>
  ];

  connective: [
    s = STRING; ","; a = UIDENT; ","; r = UIDENT -> (s,a,r)
  ];

  (* how can I write a quotation outside the EXTEND syntax ? *)
  (* how does this quotation looks like ? *)
  (* Quotation.add my_parser ??? *)
  rule: [
    "RULE"; r = my_parser ??? "END" -> do_something r
  ];
  
END
------------------------

-- 
++ Blog: http://blog.rsise.anu.edu.au/?q=pietro
++ 
++ "All great truths begin as blasphemies." -George Bernard Shaw
++ Please avoid sending me Word or PowerPoint attachments.
   See http://www.fsf.org/philosophy/no-word-attachments.html


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

end of thread, other threads:[~2009-04-13  0:00 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-03-21  3:41 Camlp4 help Andre Nathan
2009-03-21 15:26 ` [Caml-list] " blue storm
2009-03-21 16:14   ` Andre Nathan
2009-03-21 17:24     ` blue storm
2009-03-21 17:26       ` blue storm
  -- strict thread matches above, loose matches on Subject: below --
2009-04-13  0:05 Andre Nathan
2005-07-15  8:39 camlp4 help Pietro Abate

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