git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3996 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Daniel de Rauglaudre 2001-11-07 12:42:25 +00:00
parent 27a1084a09
commit 7d23cf6672
8 changed files with 53 additions and 14 deletions

View File

@ -1,6 +1,9 @@
Camlp4 Version 3.04
-------------------
- [07 Nov 01] Added the ability to use $ as token: was impossible so far,
because of AST quotation uses it for its antiquotation. The fix is just
a little (invisible) change in Plexer.
- [05 Nov 01] Added option -tc (types comment) when using pr_o or pr_r
try to print comments inside sum and record types like they are in
the source (not by default, because may work incorrectly).

View File

@ -18,7 +18,10 @@ open Pcaml;
Pcaml.no_constructors_arity.val := True;
do {
let odfa = Plexer.dollar_for_antiquotation.val in
Plexer.dollar_for_antiquotation.val := False;
Grammar.Unsafe.reinit_gram gram (Plexer.make ());
Plexer.dollar_for_antiquotation.val := odfa;
Grammar.Unsafe.clear_entry interf;
Grammar.Unsafe.clear_entry implem;
Grammar.Unsafe.clear_entry top_phrase;
@ -90,7 +93,7 @@ value is_operator =
["asr"; "land"; "lor"; "lsl"; "lsr"; "lxor"; "mod"; "or"];
List.iter (fun x -> Hashtbl.add ct x True)
['!'; '&'; '*'; '+'; '-'; '/'; ':'; '<'; '='; '>'; '@'; '^'; '|'; '~';
'?'; '%'; '.'];
'?'; '%'; '.'; '$'];
fun x ->
try Hashtbl.find ht x with
[ Not_found -> try Hashtbl.find ct x.[0] with _ -> False ]
@ -154,7 +157,7 @@ value infixop0 =
(parser
[: `("", x)
when
not (List.mem x excl) && String.length x >= 2 &&
not (List.mem x excl) && String.length x >= 1 &&
List.mem x.[0] list && symbolchar x 1 :] ->
x)
;

View File

@ -113,7 +113,7 @@ value rec skip_spaces =
value error_on_unknown_keywords = ref False;
value err loc msg = raise_with_loc loc (Token.Error msg);
value next_token_fun find_kwd =
value next_token_fun dfa find_kwd =
let keyword_or_error loc s =
try (("", find_kwd s), loc) with
[ Not_found ->
@ -262,9 +262,14 @@ value next_token_fun find_kwd =
("ANTIQUOT", k ^ ":" ^ locate_or_antiquot_rest bp 0 s)
| [: `'\\'; `c; s :] ->
("ANTIQUOT", ":" ^ locate_or_antiquot_rest bp (store len c) s)
| [: `c; s :] ->
| [: s :] ->
if dfa then
match s with parser
[ [: `c :] ->
("ANTIQUOT", ":" ^ locate_or_antiquot_rest bp (store len c) s)
| [: :] ep -> err (bp, ep) "antiquotation not terminated" ]
else
("", get_buff (ident2 (store 0 '$') s)) ]
and maybe_locate bp len =
parser
[ [: `'$' :] -> ("ANTIQUOT", ":" ^ get_buff len)
@ -366,9 +371,12 @@ value next_token_fun find_kwd =
err (Stream.count cstrm, Stream.count cstrm + 1) str ]
;
value dollar_for_antiquotation = ref True;
value func kwd_table =
let find = Hashtbl.find kwd_table in
Token.lexer_func_of_parser (next_token_fun find)
let dfa = dollar_for_antiquotation.val in
Token.lexer_func_of_parser (next_token_fun dfa find)
;
value rec check_keyword_stream =

View File

@ -37,3 +37,8 @@ value make : unit -> Token.lexer;
The lexer do not use global (mutable) variables: instantiations
of [Plexer.make ()] do not perturb each other. *)
value dollar_for_antiquotation : ref bool;
(* When True (default), the next call to [Plexer.make ()] returns a
lexer where the dollar sign is used for antiquotations. If False,
the dollar sign can be used as token. *)

View File

@ -38,7 +38,10 @@ Pcaml.add_option "-help_seq" (Arg.Unit help_sequences)
" Print explanations about new sequences and exit.";
do {
let odfa = Plexer.dollar_for_antiquotation.val in
Plexer.dollar_for_antiquotation.val := False;
Grammar.Unsafe.reinit_gram gram (Plexer.make ());
Plexer.dollar_for_antiquotation.val := odfa;
Grammar.Unsafe.clear_entry interf;
Grammar.Unsafe.clear_entry implem;
Grammar.Unsafe.clear_entry top_phrase;

View File

@ -116,7 +116,7 @@ let rec skip_spaces (strm__ : _ Stream.t) =
let error_on_unknown_keywords = ref false;;
let err loc msg = raise_with_loc loc (Token.Error msg);;
let next_token_fun find_kwd =
let next_token_fun dfa find_kwd =
let keyword_or_error loc s =
try ("", find_kwd s), loc with
Not_found ->
@ -377,12 +377,18 @@ let next_token_fun find_kwd =
"ANTIQUOT", ":" ^ locate_or_antiquot_rest bp (store len c) strm__
| _ -> raise (Stream.Error "")
end
| Some c ->
| _ ->
let s = strm__ in
if dfa then
let (strm__ : _ Stream.t) = s in
match Stream.peek strm__ with
Some c ->
Stream.junk strm__;
"ANTIQUOT", ":" ^ locate_or_antiquot_rest bp (store len c) strm__
"ANTIQUOT", ":" ^ locate_or_antiquot_rest bp (store len c) s
| _ ->
let ep = Stream.count strm__ in
err (bp, ep) "antiquotation not terminated"
else "", get_buff (ident2 (store 0 '$') s)
and maybe_locate bp len (strm__ : _ Stream.t) =
match Stream.peek strm__ with
Some '$' -> Stream.junk strm__; "ANTIQUOT", ":" ^ get_buff len
@ -559,9 +565,12 @@ let next_token_fun find_kwd =
Stream.Error str -> err (Stream.count cstrm, Stream.count cstrm + 1) str
;;
let dollar_for_antiquotation = ref true;;
let func kwd_table =
let find = Hashtbl.find kwd_table in
Token.lexer_func_of_parser (next_token_fun find)
let dfa = !dollar_for_antiquotation in
Token.lexer_func_of_parser (next_token_fun dfa find)
;;
let rec check_keyword_stream (strm__ : _ Stream.t) =

View File

@ -37,3 +37,8 @@ val make : unit -> Token.lexer;;
The lexer do not use global (mutable) variables: instantiations
of [Plexer.make ()] do not perturb each other. *)
val dollar_for_antiquotation : bool ref;;
(* When True (default), the next call to [Plexer.make ()] returns a
lexer where the dollar sign is used for antiquotations. If False,
the dollar sign can be used as token. *)

View File

@ -35,7 +35,10 @@ To avoid compilation warning use the new syntax.
Pcaml.add_option "-help_seq" (Arg.Unit help_sequences)
" Print explanations about new sequences and exit.";;
let odfa = !(Plexer.dollar_for_antiquotation) in
Plexer.dollar_for_antiquotation := false;
Grammar.Unsafe.reinit_gram gram (Plexer.make ());
Plexer.dollar_for_antiquotation := odfa;
Grammar.Unsafe.clear_entry interf;
Grammar.Unsafe.clear_entry implem;
Grammar.Unsafe.clear_entry top_phrase;