module Ast = CicNotationPt
module Env = CicNotationEnv
-exception Parse_error of Token.flocation * string
+exception Parse_error of string
exception Level_not_found of int
let level1_pattern_grammar =
f ()
with
| Stdpp.Exc_located (floc, Stream.Error msg) ->
- raise (Parse_error (floc, msg))
+ raise (HExtlib.Localized (floc, Parse_error msg))
| Stdpp.Exc_located (floc, exn) ->
- raise (Parse_error (floc, (Printexc.to_string exn)))
+ raise (HExtlib.Localized (floc, (Parse_error (Printexc.to_string exn))))
let parse_level1_pattern lexbuf =
exc_located_wrapper
* http://helm.cs.unibo.it/
*)
-exception Parse_error of Token.flocation * string
+exception Parse_error of string
exception Level_not_found of int
(** {2 Parsing functions} *)
type sort_kind = [ `Prop | `Set | `Type of CicUniv.universe | `CProp ]
type fold_kind = [ `Left | `Right ]
-type location = Lexing.position * Lexing.position
-(* cut and past from CicAst.loc_of_floc *)
-let loc_of_floc = function
- | { Lexing.pos_cnum = loc_begin }, { Lexing.pos_cnum = loc_end } ->
- (loc_begin, loc_end)
+type location = Token.flocation
let fail floc msg =
- let (x, y) = loc_of_floc floc in
+ let (x, y) = HExtlib.loc_of_floc floc in
failwith (Printf.sprintf "Error at characters %d - %d: %s" x y msg)
type href = UriManager.uri
| IDENT "fold"; kind = reduction_kind; t = tactic_term; p = pattern_spec ->
let (pt,_,_) = p in
if pt <> None then
- raise (CicNotationParser.Parse_error
- (loc, "the pattern cannot specify the term to replace, only its"
- ^ " paths in the hypotheses and in the conclusion"))
+ raise (HExtlib.Localized (loc, CicNotationParser.Parse_error
+ ("the pattern cannot specify the term to replace, only its"
+ ^ " paths in the hypotheses and in the conclusion")))
else
GrafiteAst.Fold (loc, kind, t, p)
| IDENT "fourier" ->
let (pt,_,_) = p in
if pt <> None then
raise
- (CicNotationParser.Parse_error
- (loc,"the pattern cannot specify the term to rewrite, only its paths in the hypotheses and in the conclusion"))
+ (HExtlib.Localized (loc,
+ (CicNotationParser.Parse_error
+ "the pattern cannot specify the term to rewrite, only its paths in the hypotheses and in the conclusion")))
else
GrafiteAst.Rewrite (loc, d, t, p)
| IDENT "right" ->
then
GrafiteAst.Ident_alias (id, uri)
else
- raise (CicNotationParser.Parse_error (loc,sprintf "Not a valid uri: %s" uri))
+ raise
+ (HExtlib.Localized (loc, CicNotationParser.Parse_error (sprintf "Not a valid uri: %s" uri)))
else
- raise (CicNotationParser.Parse_error (loc,
- sprintf "Not a valid identifier: %s" id))
+ raise (HExtlib.Localized (loc, CicNotationParser.Parse_error (
+ sprintf "Not a valid identifier: %s" id)))
| IDENT "symbol"; symbol = QSTRING;
instance = OPT [ LPAREN; IDENT "instance"; n = int; RPAREN -> n ];
SYMBOL "="; dsc = QSTRING ->
| IDENT "metadata"; [ IDENT "dependency" | IDENT "baseuri" ] ; URI ->
(** metadata commands lives only in .moo, where they are in marshalled
* form *)
- raise (CicNotationParser.Parse_error (loc, "metadata not allowed here"))
+ raise (HExtlib.Localized (loc,CicNotationParser.Parse_error "metadata not allowed here"))
| IDENT "dump" -> GrafiteAst.Dump loc
| IDENT "render"; u = URI ->
with
| Stdpp.Exc_located (_, End_of_file) -> raise End_of_file
| Stdpp.Exc_located (floc, Stream.Error msg) ->
- raise (CicNotationParser.Parse_error (floc, msg))
+ raise (HExtlib.Localized (floc,CicNotationParser.Parse_error msg))
| Stdpp.Exc_located (floc, exn) ->
- raise (CicNotationParser.Parse_error (floc, (Printexc.to_string exn)))
+ raise
+ (HExtlib.Localized (floc,CicNotationParser.Parse_error (Printexc.to_string exn)))
let parse_statement lexbuf =
exc_located_wrapper
try
let statement = GrafiteParser.parse_statement istream in
let floc = extract_loc statement in
- let (_, y) = P.loc_of_floc floc in
+ let (_, y) = HExtlib.loc_of_floc floc in
char_count := y + !char_count;
match statement with
(* | G.Executable (_, G.Macro (_, G.Check (_,
| _ -> prerr_endline "Unsupported statement"
with
| End_of_file -> raise End_of_file
- | CicNotationParser.Parse_error (floc, msg) ->
- let (x, y) = P.loc_of_floc floc in
+ | HExtlib.Localized (floc,CicNotationParser.Parse_error msg) ->
+ let (x, y) = HExtlib.loc_of_floc floc in
(* let before = String.sub line 0 x in
let error = String.sub line x (y - x) in
let after = String.sub line y (String.length line - y) in
PACKAGE = extlib
-REQUIRES = unix
+REQUIRES = unix camlp4.gramlib
PREDICATES =
INTERFACE_FILES = \
at_end ();
res
+(** {2 Localized exceptions } *)
+
+exception Localized of Token.flocation * exn
+
+let loc_of_floc = function
+ | { Lexing.pos_cnum = loc_begin }, { Lexing.pos_cnum = loc_end } ->
+ (loc_begin, loc_end)
+
+let raise_localized_exception ~offset floc exn =
+ let (x, y) = loc_of_floc floc in
+ let x = offset + x in
+ let y = offset + y in
+ let flocb,floce = floc in
+ let floc =
+ { flocb with Lexing.pos_cnum = x }, { floce with Lexing.pos_cnum = y }
+ in
+ raise (Localized (floc, exn))
val profile : ?enable:bool -> string -> profiler
val set_profiling_printings : (unit -> bool) -> unit
+(** {2 Localized exceptions } *)
+
+exception Localized of Token.flocation * exn
+
+val loc_of_floc: Token.flocation -> int * int
+
+val raise_localized_exception: offset:int -> Token.flocation -> exn -> 'a