caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* buidlExpressionParser
@ 2005-07-31 13:21 Pietro Abate
  2005-07-31 23:39 ` [Caml-list] buidlExpressionParser skaller
  2005-08-12  7:07 ` Pietro Abate
  0 siblings, 2 replies; 5+ messages in thread
From: Pietro Abate @ 2005-07-31 13:21 UTC (permalink / raw)
  To: ocaml ml

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

Hi all,

I'm trying to write a generic parser similar to the buidlExpressionParser
in the haskel library (without using external libraries). I came up with
a kind of hack that uses the grammar extension mechanism (attached).

Is there a better way of doing this ?

And an other question: at the moment I'm using ( Plexer.gmake () ) as a
lexer, but I don't need it (too restrictive and doesn't lex tokens like
"[]" ).

Does anybody have an example on how to write a simple lexer that I can
use instead ?

:)
p

compile with:

ocamlfind ocamlc -c -pp "camlp4o -I . pa_extend.cmo q_MLast.cmo " -I /usr/lib/ocaml/3.08.3/camlp4 datatype.ml inputParser.ml

ocamlc /usr/lib/ocaml/3.08.3/camlp4/gramlib.cma datatype.cmo inputParser.cmo main.ml

-- 
++ 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

[-- Attachment #2: datatype.ml --]
[-- Type: text/plain, Size: 507 bytes --]


type t =
    Atom of string
  | And of t * t
  | Or of t * t
  | Not of t


let rec string_of_formula = function
    |And(f1,f2) ->
            Printf.sprintf "(%s And %s)"
            (string_of_formula f1)
            (string_of_formula f2)
    |Or(f1,f2) ->
            Printf.sprintf "(%s Or %s)"
            (string_of_formula f1)
            (string_of_formula f2)
    |Not(f) -> Printf.sprintf "(Not %s)" (string_of_formula f)
    |Atom(s) -> s
;;

let print s = print_endline (string_of_formula s)

[-- Attachment #3: inputParser.ml --]
[-- Type: text/plain, Size: 918 bytes --]

(*pp camlp4o -I . pa_extend.cmo q_MLast.cmo *)

open Genlex

let gram = Grammar.gcreate (Plexer.gmake ());;
let expr_term = Grammar.Entry.create gram "expr_term";;

let add_uconn op co =
    EXTEND
      expr_term: LEVEL "Simple"
      [[ $op$; x = expr_term -> co [x] ]];
    END
;;

let add_biconn lev op co =
    EXTEND
      expr_term: LEVEL $lev$
      [[ x = expr_term; $op$; y = expr_term -> co [x;y] ]];
    END
;;

EXTEND
GLOBAL : expr_term;
  expr_term:
    [ "One" LEFTA [ ]
    | "Two" RIGHTA [ ]
    | "Simple" NONA
      [ x = LIDENT -> Datatype.Atom x 
      | "("; p = expr_term; ")" -> p
      ]
    ];

END

let buildParser table =
    List.iter(function
    |"Simple",op,co -> add_uconn op co
    |lev,op,co -> add_biconn lev op co
    ) table;
    let loc = Token.dummy_loc in
    let _ = Grammar.Entry.print expr_term in
    fun s ->
        Grammar.Entry.parse expr_term (Stream.of_string s)
;;


[-- Attachment #4: main.ml --]
[-- Type: text/plain, Size: 302 bytes --]


open Datatype

let inputparser = InputParser.buildParser [
    ("Simple","~",(fun l -> Not(List.hd l)) );
    ("One","&",(fun l -> And(List.hd l, List.hd(List.tl l))) );
    ("One","v",(fun l -> Or(List.hd l, List.hd(List.tl l))) );
    ] ;;

let a = inputparser "a & ( c v ~ d)" in
Datatype.print a


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

* Re: [Caml-list] buidlExpressionParser
  2005-07-31 13:21 buidlExpressionParser Pietro Abate
@ 2005-07-31 23:39 ` skaller
  2005-08-01  1:45   ` Pietro Abate
  2005-08-12  7:07 ` Pietro Abate
  1 sibling, 1 reply; 5+ messages in thread
From: skaller @ 2005-07-31 23:39 UTC (permalink / raw)
  To: Pietro Abate; +Cc: ocaml ml

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

On Sun, 2005-07-31 at 23:21 +1000, Pietro Abate wrote:
> Hi all,
> 
> I'm trying to write a generic parser similar to the buidlExpressionParser
> in the haskel library (without using external libraries). I came up with
> a kind of hack that uses the grammar extension mechanism (attached).
> 
> Is there a better way of doing this ?

Do I understand right: you're leveraging the camlp4 library
code to build a general purpose LL(1) parser which will support
runtime extension?

> Does anybody have an example on how to write a simple lexer that I can
> use instead ?

Hmmm ... don't know about 'simple lexer' but I have a library
function that can translate a representation of a labelled sequence
of regexps into a tokeniser.

I would not call this system 'simple' but it is entirely combinator
based, and generates a lex style deterministic finite state automaton.

You may want an NFA based interpreter instead though.

-- 
John Skaller <skaller at users dot sourceforge dot net>


[-- Attachment #2: This is a digitally signed message part --]
[-- Type: application/pgp-signature, Size: 189 bytes --]

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

* Re: [Caml-list] buidlExpressionParser
  2005-07-31 23:39 ` [Caml-list] buidlExpressionParser skaller
@ 2005-08-01  1:45   ` Pietro Abate
  2005-08-01  8:13     ` skaller
  0 siblings, 1 reply; 5+ messages in thread
From: Pietro Abate @ 2005-08-01  1:45 UTC (permalink / raw)
  To: ocaml ml

On Mon, Aug 01, 2005 at 09:39:31AM +1000, skaller wrote:
> > Is there a better way of doing this ?
> Do I understand right: you're leveraging the camlp4 library
> code to build a general purpose LL(1) parser which will support
> runtime extension?

yep, I tought it was a kinda of creative way of using it... 

now I've to convince ocamlfind to compile it properly :) 

I'm not sure that this can be a general solution,
but for my small calculator-like example works well.

> > Does anybody have an example on how to write a simple lexer that I can
> > use instead ?
> Hmmm ... don't know about 'simple lexer' but I have a library
> function that can translate a representation of a labelled sequence
> of regexps into a tokeniser.
I'll be happy to have a look at this function...

> You may want an NFA based interpreter instead though.
I was thinking of using the Token interface in the Camlp4 library

that is, if f = Token.lexer_func_of_parser <some parser>
maybe your function can be used here ...

then the glexer would be something like:

{ Token.tok_func = f;
  Token.tok_using = (fun _ -> ());
  Token.tok_removing = (fun _ -> ());
  Token.tok_match = Token.default_match;
  Token.tok_text = Token.lexer_text }

:)
p

-- 
++ 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] 5+ messages in thread

* Re: [Caml-list] buidlExpressionParser
  2005-08-01  1:45   ` Pietro Abate
@ 2005-08-01  8:13     ` skaller
  0 siblings, 0 replies; 5+ messages in thread
From: skaller @ 2005-08-01  8:13 UTC (permalink / raw)
  To: Pietro Abate; +Cc: ocaml ml

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

On Mon, 2005-08-01 at 11:45 +1000, Pietro Abate wrote:
> On Mon, Aug 01, 2005 at 09:39:31AM +1000, skaller wrote:

> > Hmmm ... don't know about 'simple lexer' but I have a library
> > function that can translate a representation of a labelled sequence
> > of regexps into a tokeniser.
> I'll be happy to have a look at this function...

OK, I uploaded the package to 

http://felix.sf.net/reg_1.0.tgz


-- 
John Skaller <skaller at users dot sourceforge dot net>


[-- Attachment #2: This is a digitally signed message part --]
[-- Type: application/pgp-signature, Size: 189 bytes --]

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

* Re: [Caml-list] buidlExpressionParser
  2005-07-31 13:21 buidlExpressionParser Pietro Abate
  2005-07-31 23:39 ` [Caml-list] buidlExpressionParser skaller
@ 2005-08-12  7:07 ` Pietro Abate
  1 sibling, 0 replies; 5+ messages in thread
From: Pietro Abate @ 2005-08-12  7:07 UTC (permalink / raw)
  To: caml-list, ocaml ml; +Cc: Pietro Abate

Hi all,
I've fixed the problem with ocamlfind (you need to specify the "require"
in the META file) and now I'm tring to dynamically load my small parser.

In order to make it work I need also to load Pcaml. Dynlink doesn't do
this automatically form me, so I wrote this small function below, but
I'm stuck with "Fatal error: exception Dynlink.Error(0)" while tring to
load the stdlib (that contains Lexing needed by Pcaml - I suppose). What
am I doing wrong ?

---------- test.ml ---------
let load_camlp4 () =
    let version = Sys.ocaml_version in
    try
        let stdlib = "/usr/lib/ocaml/"^version^"/stdlib.cma" in
        let gramlib = "/usr/lib/ocaml/"^version^"/camlp4/gramlib.cma" in
        Printf.printf "Loading: %s ..." stdlib;
        Dynlink.loadfile (stdlib);
        print_endline "done.";
        Printf.printf "Loading: %s ..." gramlib;
        Dynlink.loadfile (gramlib);
        print_endline "done.";
    with
    | Dynlink.Error(Dynlink.Unavailable_unit(depend))
    | Dynlink.Error(
        Dynlink.Linking_error(_,Dynlink.Undefined_global(depend))
        ) -> failwith ("Cannot find "^String.lowercase(depend))
;;

let main () =
Dynlink.init();
load_camlp4 ()
;;

main ()

----------
compile with ocamlfind ocamlc -package dynlink -linkpkg test.ml

thanks,
p

On Sun, Jul 31, 2005 at 11:21:19PM +1000, Pietro Abate wrote:
> Hi all,
> 
> I'm trying to write a generic parser similar to the buidlExpressionParser
> in the haskel library (without using external libraries). I came up with
> a kind of hack that uses the grammar extension mechanism (attached).
> 
> Is there a better way of doing this ?
> 
> And an other question: at the moment I'm using ( Plexer.gmake () ) as a
> lexer, but I don't need it (too restrictive and doesn't lex tokens like
> "[]" ).
> 
> Does anybody have an example on how to write a simple lexer that I can
> use instead ?
> 
> :)
> p
> 
> compile with:
> 
> ocamlfind ocamlc -c -pp "camlp4o -I . pa_extend.cmo q_MLast.cmo " -I /usr/lib/ocaml/3.08.3/camlp4 datatype.ml inputParser.ml
> 
> ocamlc /usr/lib/ocaml/3.08.3/camlp4/gramlib.cma datatype.cmo inputParser.cmo main.ml
> 
> -- 
> ++ 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

> 
> type t =
>     Atom of string
>   | And of t * t
>   | Or of t * t
>   | Not of t
> 
> 
> let rec string_of_formula = function
>     |And(f1,f2) ->
>             Printf.sprintf "(%s And %s)"
>             (string_of_formula f1)
>             (string_of_formula f2)
>     |Or(f1,f2) ->
>             Printf.sprintf "(%s Or %s)"
>             (string_of_formula f1)
>             (string_of_formula f2)
>     |Not(f) -> Printf.sprintf "(Not %s)" (string_of_formula f)
>     |Atom(s) -> s
> ;;
> 
> let print s = print_endline (string_of_formula s)

> (*pp camlp4o -I . pa_extend.cmo q_MLast.cmo *)
> 
> open Genlex
> 
> let gram = Grammar.gcreate (Plexer.gmake ());;
> let expr_term = Grammar.Entry.create gram "expr_term";;
> 
> let add_uconn op co =
>     EXTEND
>       expr_term: LEVEL "Simple"
>       [[ $op$; x = expr_term -> co [x] ]];
>     END
> ;;
> 
> let add_biconn lev op co =
>     EXTEND
>       expr_term: LEVEL $lev$
>       [[ x = expr_term; $op$; y = expr_term -> co [x;y] ]];
>     END
> ;;
> 
> EXTEND
> GLOBAL : expr_term;
>   expr_term:
>     [ "One" LEFTA [ ]
>     | "Two" RIGHTA [ ]
>     | "Simple" NONA
>       [ x = LIDENT -> Datatype.Atom x 
>       | "("; p = expr_term; ")" -> p
>       ]
>     ];
> 
> END
> 
> let buildParser table =
>     List.iter(function
>     |"Simple",op,co -> add_uconn op co
>     |lev,op,co -> add_biconn lev op co
>     ) table;
>     let loc = Token.dummy_loc in
>     let _ = Grammar.Entry.print expr_term in
>     fun s ->
>         Grammar.Entry.parse expr_term (Stream.of_string s)
> ;;
> 

> 
> open Datatype
> 
> let inputparser = InputParser.buildParser [
>     ("Simple","~",(fun l -> Not(List.hd l)) );
>     ("One","&",(fun l -> And(List.hd l, List.hd(List.tl l))) );
>     ("One","v",(fun l -> Or(List.hd l, List.hd(List.tl l))) );
>     ] ;;
> 
> let a = inputparser "a & ( c v ~ d)" in
> Datatype.print a
> 

> _______________________________________________
> 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


-- 
++ 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] 5+ messages in thread

end of thread, other threads:[~2005-08-12  7:08 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2005-07-31 13:21 buidlExpressionParser Pietro Abate
2005-07-31 23:39 ` [Caml-list] buidlExpressionParser skaller
2005-08-01  1:45   ` Pietro Abate
2005-08-01  8:13     ` skaller
2005-08-12  7:07 ` Pietro Abate

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