git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4423 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Daniel de Rauglaudre 2002-02-16 19:06:56 +00:00
parent 0054bf8a75
commit 4991390992
3 changed files with 4 additions and 21 deletions

View File

@ -23,7 +23,7 @@ camlp4$D.fast.opt: pa_$D_fast.cmx
cd ../camlp4; $(MAKE) optp4 CAMLP4OPT=../compile/camlp4$D.fast.opt CAMLP4M="../compile/pa_$D_fast.cmx ../meta/pr_dump.cmx"
pa_$D_fast.ml: comp_head.ml $D_fast.ml comp_trail.ml
cat $(SRC) | sed -e "s/Plexer.make ()/P.lexer/" -e "/EXTEND/,/END/d" -e "/Grammar.Entry.of_parser/d" -e "/Grammar.Entry.create/d" | cat comp_head.ml - $D_fast.ml comp_trail.ml > pa_$D_fast.ml
cat $(SRC) | sed -e "s/Plexer.gmake ()/P.lexer/" -e "/EXTEND/,/END/d" -e "/Grammar.Entry.of_parser/d" -e "/Grammar.Entry.gcreate/d" | cat comp_head.ml - $D_fast.ml comp_trail.ml > pa_$D_fast.ml
$D_fast.ml: compile.cmo $(SRC)
OTOP=$(OTOP) EXE=$(EXE) ./compile.sh $(COMP_OPT) $(SRC) > $D_fast.ml

View File

@ -62,7 +62,7 @@ let _ = do { Printf.eprintf "recovered or_zero at loc (%d, %d)\n" loc1 loc2; flu
(if prev_symb = "" then "" else " after " ^ prev_symb) ^
" (in [" ^ entry ^ "])"
;
value lexer = Plexer.make ();
value lexer = Plexer.gmake ();
end
;

View File

@ -21,7 +21,7 @@ value rec name_of_symbol entry =
[ Snterm e -> "[" ^ e.ename ^ "]"
| Snterml e l -> "[" ^ e.ename ^ " level " ^ l ^ "]"
| Sself | Snext -> "[" ^ entry.ename ^ "]"
| Stoken tok -> entry.egram.glexer.Token.text tok
| Stoken tok -> entry.egram.glexer.Token.tok_text tok
| _ -> "???" ]
;
@ -363,11 +363,6 @@ value rec continue_parser_of_levels entry clevn levs =
let pel = continue_parser_of_levels entry (succ clevn) levs in
match lev.lsuffix with
[ DeadEnd ->
(*
let ncont = entry.ename ^ "_" ^ string_of_int clevn ^ "_cont" in
let e = <:expr< fun bp a__ strm__ -> a__ >> in
let pel = if levs = [] then [] else pel in
*)
[None :: pel]
| tree ->
let alevn =
@ -515,18 +510,6 @@ value all_entries_in_graph list entry =
value entries = ref [];
(*
[Grammar.Entry.obj Pcaml.interf;
Grammar.Entry.obj Pcaml.implem;
Grammar.Entry.obj Pcaml.top_phrase;
Grammar.Entry.obj Pcaml.use_file;
Grammar.Entry.obj Pcaml.str_item;
Grammar.Entry.obj Pcaml.sig_item;
Grammar.Entry.obj Pcaml.ctyp;
Grammar.Entry.obj Pcaml.expr;
Grammar.Entry.obj Pcaml.patt]
*)
value rec list_mem_right_assoc x =
fun
[ [] -> False
@ -561,7 +544,7 @@ value compile () =
let si2 =
let list = List.sort compare keywords.val in
<:str_item<
List.iter (fun kw -> P.lexer.Token.using ("", kw))
List.iter (fun kw -> P.lexer.Token.tok_using ("", kw))
$expr_list list$
>>
in