summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--camlp4/CHANGES5
-rw-r--r--camlp4/camlp4/ast2pt.ml3
-rw-r--r--camlp4/etc/pa_o.ml2
-rw-r--r--camlp4/lib/plexer.ml31
-rw-r--r--camlp4/ocaml_src/camlp4/ast2pt.ml2
-rw-r--r--camlp4/ocaml_src/lib/plexer.ml33
6 files changed, 60 insertions, 16 deletions
diff --git a/camlp4/CHANGES b/camlp4/CHANGES
index b7990cb7b..b720547c2 100644
--- a/camlp4/CHANGES
+++ b/camlp4/CHANGES
@@ -1,6 +1,11 @@
Camlp4 Version 3.03
-------------------
+- [05 Oct 01] Fixed bug in normal syntax: when defining a constructor
+ named "True" of "False" (capitalized, i.e. not like the booleans), it
+ did not work.
+- [04 Oct 01] Fixed some revised and quotation syntaxes in objects classes
+ and types (cleaner),
- [02 Oct 01] In revised syntax, the warning for using old syntax for
sequences is now by default. To remove it, the option -no-warn-seq
of camlp4r has been added. Option -warn-seq has been removed.
diff --git a/camlp4/camlp4/ast2pt.ml b/camlp4/camlp4/ast2pt.ml
index 086aa1d59..1f1368487 100644
--- a/camlp4/camlp4/ast2pt.ml
+++ b/camlp4/camlp4/ast2pt.ml
@@ -59,7 +59,8 @@ value conv_con =
let t = Hashtbl.create 73 in
do {
List.iter (fun (s, s') -> Hashtbl.add t s s')
- [("True", "true"); ("False", "false")];
+ [("True", "true"); ("False", "false");
+ (" True", "True"); (" False", "False")];
fun s -> try Hashtbl.find t s with [ Not_found -> s ]
}
;
diff --git a/camlp4/etc/pa_o.ml b/camlp4/etc/pa_o.ml
index 993d2f2ef..b618a1b5b 100644
--- a/camlp4/etc/pa_o.ml
+++ b/camlp4/etc/pa_o.ml
@@ -592,6 +592,8 @@ EXTEND
| s = FLOAT -> <:expr< $flo:s$ >>
| s = STRING -> <:expr< $str:s$ >>
| c = CHAR -> <:expr< $chr:c$ >>
+ | UIDENT "True" -> <:expr< $uid:" True"$ >>
+ | UIDENT "False" -> <:expr< $uid:" False"$ >>
| i = expr_ident -> i
| s = "false" -> <:expr< False >>
| s = "true" -> <:expr< True >>
diff --git a/camlp4/lib/plexer.ml b/camlp4/lib/plexer.ml
index a1b330fd5..f8d609cf4 100644
--- a/camlp4/lib/plexer.ml
+++ b/camlp4/lib/plexer.ml
@@ -436,6 +436,16 @@ value check_keyword s =
try check_keyword_stream (Stream.of_string s) with _ -> False
;
+value error_no_respect_rules p_con p_prm =
+ raise
+ (Token.Error
+ ("the token " ^
+ (if p_con = "" then "\"" ^ p_prm ^ "\""
+ else if p_prm = "" then p_con
+ else p_con ^ " \"" ^ p_prm ^ "\"") ^
+ " does not respect Plexer rules"))
+;
+
value using_token kwd_table (p_con, p_prm) =
match p_con with
[ "" ->
@@ -445,13 +455,20 @@ value using_token kwd_table (p_con, p_prm) =
with
[ Not_found ->
if check_keyword p_prm then Hashtbl.add kwd_table p_prm p_prm
- else
- raise
- (Token.Error
- ("\
-the token \"" ^ p_prm ^
- "\" does not respect Plexer rules")) ]
- | "LIDENT" | "UIDENT" | "TILDEIDENT" | "TILDEIDENTCOLON" | "QUESTIONIDENT" |
+ else error_no_respect_rules p_con p_prm ]
+ | "LIDENT" ->
+ if p_prm = "" then ()
+ else
+ match p_prm.[0] with
+ [ 'A'..'Z' -> error_no_respect_rules p_con p_prm
+ | _ -> () ]
+ | "UIDENT" ->
+ if p_prm = "" then ()
+ else
+ match p_prm.[0] with
+ [ 'a'..'z' -> error_no_respect_rules p_con p_prm
+ | _ -> () ]
+ | "TILDEIDENT" | "TILDEIDENTCOLON" | "QUESTIONIDENT" |
"QUESTIONIDENTCOLON" | "INT" | "FLOAT" | "CHAR" | "STRING" | "QUOTATION" |
"ANTIQUOT" | "LOCATE" | "EOI" ->
()
diff --git a/camlp4/ocaml_src/camlp4/ast2pt.ml b/camlp4/ocaml_src/camlp4/ast2pt.ml
index d0b82ade2..5064d4ed0 100644
--- a/camlp4/ocaml_src/camlp4/ast2pt.ml
+++ b/camlp4/ocaml_src/camlp4/ast2pt.ml
@@ -58,7 +58,7 @@ let ldot l s = Ldot (l, s);;
let conv_con =
let t = Hashtbl.create 73 in
List.iter (fun (s, s') -> Hashtbl.add t s s')
- ["True", "true"; "False", "false"];
+ ["True", "true"; "False", "false"; " True", "True"; " False", "False"];
fun s ->
try Hashtbl.find t s with
Not_found -> s
diff --git a/camlp4/ocaml_src/lib/plexer.ml b/camlp4/ocaml_src/lib/plexer.ml
index a7e6b281f..4298be5a5 100644
--- a/camlp4/ocaml_src/lib/plexer.ml
+++ b/camlp4/ocaml_src/lib/plexer.ml
@@ -655,20 +655,39 @@ let check_keyword s =
_ -> false
;;
+let error_no_respect_rules p_con p_prm =
+ raise
+ (Token.Error
+ ("the token " ^
+ (if p_con = "" then "\"" ^ p_prm ^ "\""
+ else if p_prm = "" then p_con
+ else p_con ^ " \"" ^ p_prm ^ "\"") ^
+ " does not respect Plexer rules"))
+;;
+
let using_token kwd_table (p_con, p_prm) =
match p_con with
"" ->
begin try let _ = Hashtbl.find kwd_table p_prm in () with
Not_found ->
if check_keyword p_prm then Hashtbl.add kwd_table p_prm p_prm
- else
- raise
- (Token.Error
- ("\
-the token \"" ^ p_prm ^
- "\" does not respect Plexer rules"))
+ else error_no_respect_rules p_con p_prm
end
- | "LIDENT" | "UIDENT" | "TILDEIDENT" | "TILDEIDENTCOLON" | "QUESTIONIDENT" |
+ | "LIDENT" ->
+ if p_prm = "" then ()
+ else
+ begin match p_prm.[0] with
+ 'A'..'Z' -> error_no_respect_rules p_con p_prm
+ | _ -> ()
+ end
+ | "UIDENT" ->
+ if p_prm = "" then ()
+ else
+ begin match p_prm.[0] with
+ 'a'..'z' -> error_no_respect_rules p_con p_prm
+ | _ -> ()
+ end
+ | "TILDEIDENT" | "TILDEIDENTCOLON" | "QUESTIONIDENT" |
"QUESTIONIDENTCOLON" | "INT" | "FLOAT" | "CHAR" | "STRING" | "QUOTATION" |
"ANTIQUOT" | "LOCATE" | "EOI" ->
()