diff options
-rw-r--r-- | camlp4/camlp4/pcaml.ml | 10 | ||||
-rw-r--r-- | camlp4/etc/pr_o.ml | 8 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/pcaml.ml | 24 | ||||
-rw-r--r-- | camlp4/ocaml_src/meta/q_MLast.ml | 10 |
4 files changed, 29 insertions, 23 deletions
diff --git a/camlp4/camlp4/pcaml.ml b/camlp4/camlp4/pcaml.ml index cb4ba5e9b..411d565b5 100644 --- a/camlp4/camlp4/pcaml.ml +++ b/camlp4/camlp4/pcaml.ml @@ -254,14 +254,14 @@ value print_format str = value print_exn = fun [ Out_of_memory -> Format.print_string "Out of memory\n" - | Match_failure (file, first_char, last_char) -> + | Match_failure (file, line, char) -> do { Format.print_string "Pattern matching failed, file "; Format.print_string file; - Format.print_string ", chars "; - Format.print_int first_char; - Format.print_char '-'; - Format.print_int last_char + Format.print_string ", line "; + Format.print_int line; + Format.print_string ", char "; + Format.print_int char } | Stream.Error str -> print_format ("Parse error: " ^ str) | Stream.Failure -> Format.print_string "Parse failure" diff --git a/camlp4/etc/pr_o.ml b/camlp4/etc/pr_o.ml index c777edd87..1e203b982 100644 --- a/camlp4/etc/pr_o.ml +++ b/camlp4/etc/pr_o.ml @@ -334,10 +334,16 @@ pr_expr_fun_args.val := | ge -> ([], ge) ]; value raise_match_failure (bp, ep) k = + let (line, char, _) = + if Pcaml.input_file.val <> "-" then + Stdpp.line_of_loc Pcaml.input_file.val (bp, ep) + else + (1, bp, ep) + in HOVbox [: `S LR "raise"; `S LO "("; `S LR "Match_failure"; `S LO "("; `S LR ("\"" ^ Pcaml.input_file.val ^ "\""); `S RO ","; - `S LR (string_of_int bp); `S RO ","; `S LR (string_of_int ep); + `S LR (string_of_int line); `S RO ","; `S LR (string_of_int char); `S RO ")"; `S RO ")"; k :] ; diff --git a/camlp4/ocaml_src/camlp4/pcaml.ml b/camlp4/ocaml_src/camlp4/pcaml.ml index 8b3676412..6368aa720 100644 --- a/camlp4/ocaml_src/camlp4/pcaml.ml +++ b/camlp4/ocaml_src/camlp4/pcaml.ml @@ -19,7 +19,7 @@ let gram = {Token.tok_func = (fun _ -> failwith "no loaded parsing module"); Token.tok_using = (fun _ -> ()); Token.tok_removing = (fun _ -> ()); Token.tok_match = - (fun _ -> raise (Match_failure ("pcaml.ml", 1506, 1512))); + (fun _ -> raise (Match_failure ("pcaml.ml", 21, 23))); Token.tok_text = fun _ -> ""} ;; @@ -252,13 +252,13 @@ let print_format str = let print_exn = function Out_of_memory -> Format.print_string "Out of memory\n" - | Match_failure (file, first_char, last_char) -> + | Match_failure (file, line, char) -> Format.print_string "Pattern matching failed, file "; Format.print_string file; - Format.print_string ", chars "; - Format.print_int first_char; - Format.print_char '-'; - Format.print_int last_char + Format.print_string ", line "; + Format.print_int line; + Format.print_string ", char "; + Format.print_int char | Stream.Error str -> print_format ("Parse error: " ^ str) | Stream.Failure -> Format.print_string "Parse failure" | Token.Error str -> @@ -338,27 +338,27 @@ and kont = pretty Stream.t ;; let pr_str_item = - {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 12089, 12095))); + {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 349, 30))); pr_levels = []} ;; let pr_sig_item = - {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 12144, 12150))); + {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 350, 30))); pr_levels = []} ;; let pr_expr = - {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 12195, 12201))); + {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 351, 26))); pr_levels = []} ;; let pr_patt = - {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 12246, 12252))); + {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 352, 26))); pr_levels = []} ;; let pr_ctyp = - {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 12297, 12303))); + {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 353, 26))); pr_levels = []} ;; let pr_class_str_item = - {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 12358, 12364))); + {pr_fun = (fun _ -> raise (Match_failure ("pcaml.ml", 354, 36))); pr_levels = []} ;; let pr_expr_fun_args = ref Extfun.empty;; diff --git a/camlp4/ocaml_src/meta/q_MLast.ml b/camlp4/ocaml_src/meta/q_MLast.ml index 82f1966f1..590235609 100644 --- a/camlp4/ocaml_src/meta/q_MLast.ml +++ b/camlp4/ocaml_src/meta/q_MLast.ml @@ -590,7 +590,7 @@ Grammar.extend Qast.Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 10073, 10089)) + _ -> raise (Match_failure ("q_MLast.ml", 288, 19)) in Qast.Node ("StExc", [Qast.Loc; c; tl; b]) : 'str_item)); @@ -826,7 +826,7 @@ Grammar.extend Qast.Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 12344, 12360)) + _ -> raise (Match_failure ("q_MLast.ml", 340, 19)) in Qast.Node ("SgExc", [Qast.Loc; c; tl]) : 'sig_item)); @@ -2663,7 +2663,7 @@ Grammar.extend Qast.Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 33221, 33237)) + _ -> raise (Match_failure ("q_MLast.ml", 882, 19)) in Qast.Node ("CrVal", [Qast.Loc; lab; mf; e]) : 'class_str_item)); @@ -3058,7 +3058,7 @@ Grammar.extend Qast.Tuple [xx1; xx2] -> xx1, xx2 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 38172, 38188)) + _ -> raise (Match_failure ("q_MLast.ml", 996, 19)) in Qast.Node ("TyObj", [Qast.Loc; ml; v]) : 'ctyp)); @@ -3093,7 +3093,7 @@ Grammar.extend Qast.Tuple [xx1; xx2] -> xx1, xx2 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 38519, 38535)) + _ -> raise (Match_failure ("q_MLast.ml", 1007, 19)) in Qast.Tuple [Qast.Cons (f, ml); v] : 'meth_list))]]; |