On Mar 8, 2009, at 3:55 PM, Matthieu Wipliez wrote:

Well I just duplicated Static to Static1 (and added Camlp4.Struct.Grammar where necessary) and replaced:
 module Structure = Camlp4.Struct.Grammar.Structure.Make Lexer;
by:

Something like this you mean? I must be doing something wrong as I never see my printout from 'using'.

        Thanks, Joel

--- Static1.ml ---

open Camlp4;
open Struct;
open Grammar;

value uncurry f (x,y) = f x y;
value flip f x y = f y x;

module Make (Lexer : Sig.Lexer)
: Sig.Grammar.Static with module Loc = Lexer.Loc
                        and module Token = Lexer.Token
= struct
  module Structure = struct
    include Camlp4.Struct.Grammar.Structure.Make Lexer;

    value using { gkeywords = table; gfilter = filter } kwd =
let _ = print_endline ("using: storing " ^ String.lowercase kwd) in
      let kwd = String.lowercase kwd in
      let r = try Hashtbl.find table kwd with
        [ Not_found ->
          let r = ref 0 in do { Hashtbl.add table kwd r; r } ]
in do { Token.Filter.keyword_added filter kwd (r.val = 0); incr r };
  end;
  module Delete = Delete.Make Structure;
  module Insert = Insert.Make Structure;
  module Fold = Fold.Make Structure;
  include Structure;

  value gram =
    let gkeywords = Hashtbl.create 301 in
    {
      gkeywords = gkeywords;
      gfilter = Token.Filter.mk (Hashtbl.mem gkeywords);
      glexer = Lexer.mk ();
      warning_verbose = ref True; (* FIXME *)
      error_verbose = Camlp4_config.verbose
    };

  module Entry = struct
    module E = Entry.Make Structure;
    type t 'a = E.t 'a;
    value mk = E.mk gram;
    value of_parser name strm = E.of_parser gram name strm;
    value setup_parser = E.setup_parser;
    value name = E.name;
    value print = E.print;
    value clear = E.clear;
    value dump = E.dump;
    value obj x = x;
  end;

  value get_filter () = gram.gfilter;

  value lex loc cs = gram.glexer loc cs;

  value lex_string loc str = lex loc (Stream.of_string str);

  value filter ts = Token.Filter.filter gram.gfilter ts;

value parse_tokens_after_filter entry ts = Entry.E.parse_tokens_after_filter entry ts;

value parse_tokens_before_filter entry ts = parse_tokens_after_filter entry (filter ts);

value parse entry loc cs = parse_tokens_before_filter entry (lex loc cs);

value parse_string entry loc str = parse_tokens_before_filter entry (lex_string loc str);

  value delete_rule = Delete.delete_rule;

  value srules e rl =
Stree (List.fold_left (flip (uncurry (Insert.insert_tree e))) DeadEnd rl);
  value sfold0 = Fold.sfold0;
  value sfold1 = Fold.sfold1;
  value sfold0sep = Fold.sfold0sep;
  (* value sfold1sep = Fold.sfold1sep; *)

  value extend = Insert.extend;

end;

---
http://tinyco.de
Mac, C++, OCaml



_______________________________________________
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

Reply via email to