diff options
-rw-r--r-- | driver/pparse.ml | 10 | ||||
-rw-r--r-- | driver/pparse.mli | 10 |
2 files changed, 13 insertions, 7 deletions
diff --git a/driver/pparse.ml b/driver/pparse.ml index 79adb7a78..4b2553f27 100644 --- a/driver/pparse.ml +++ b/driver/pparse.ml @@ -96,7 +96,7 @@ let rewrite magic ast ppxs = (List.fold_left (apply_rewriter magic) (write_ast magic ast) (List.rev ppxs)) -let apply_rewriters_str ~restore ~tool_name ast = +let apply_rewriters_str ?(restore = true) ~tool_name ast = match !Clflags.all_ppx with | [] -> ast | ppxs -> @@ -104,7 +104,7 @@ let apply_rewriters_str ~restore ~tool_name ast = let ast = rewrite Config.ast_impl_magic_number ast ppxs in Ast_mapper.drop_ppx_context_str ~restore ast -let apply_rewriters_sig ~restore ~tool_name ast = +let apply_rewriters_sig ?(restore = true) ~tool_name ast = match !Clflags.all_ppx with | [] -> ast | ppxs -> @@ -112,11 +112,11 @@ let apply_rewriters_sig ~restore ~tool_name ast = let ast = rewrite Config.ast_intf_magic_number ast ppxs in Ast_mapper.drop_ppx_context_sig ~restore ast -let apply_rewriters ~restore ~tool_name magic ast = +let apply_rewriters ?restore ~tool_name magic ast = if magic = Config.ast_impl_magic_number then - Obj.magic (apply_rewriters_str ~restore ~tool_name (Obj.magic ast)) + Obj.magic (apply_rewriters_str ?restore ~tool_name (Obj.magic ast)) else if magic = Config.ast_intf_magic_number then - Obj.magic (apply_rewriters_sig ~restore ~tool_name (Obj.magic ast)) + Obj.magic (apply_rewriters_sig ?restore ~tool_name (Obj.magic ast)) else assert false diff --git a/driver/pparse.mli b/driver/pparse.mli index 7972e6c04..bcff4e781 100644 --- a/driver/pparse.mli +++ b/driver/pparse.mli @@ -21,8 +21,14 @@ exception Error of error val preprocess : string -> string val remove_preprocessed : string -> unit val file : formatter -> tool_name:string -> string -> (Lexing.lexbuf -> 'a) -> string -> 'a -val apply_rewriters: restore:bool -> tool_name:string -> string -> 'a -> 'a -val apply_rewriters_str: restore:bool -> tool_name:string -> Parsetree.structure -> Parsetree.structure +val apply_rewriters: ?restore:bool -> tool_name:string -> string -> 'a -> 'a + (** If [restore = true] (the default), cookies set by external rewriters will be + kept for later calls. *) + +val apply_rewriters_str: ?restore:bool -> tool_name:string -> Parsetree.structure -> Parsetree.structure +val apply_rewriters_sig: ?restore:bool -> tool_name:string -> Parsetree.signature -> Parsetree.signature + + val report_error : formatter -> error -> unit |