Registration API for ppx rewriters.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13269 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2013-01-23 09:15:41 +00:00
parent ba00d09386
commit 0c856310f2
2 changed files with 56 additions and 6 deletions

View File

@ -488,6 +488,11 @@ class mapper =
method location l = l
end
class type main_entry_points =
object
method implementation: string -> structure -> string * structure
method interface: string -> signature -> string * signature
end
let apply ~source ~target mapper =
let ic = open_in_bin source in
@ -510,11 +515,12 @@ let apply ~source ~target mapper =
output_value oc ast;
close_out oc
let main mapper =
let run_main mapper =
try
let n = Array.length Sys.argv in
let a = Sys.argv in
let n = Array.length a in
if n > 2 then
apply ~source:Sys.argv.(n - 2) ~target:Sys.argv.(n - 1) mapper
apply ~source:a.(n - 2) ~target:a.(n - 1) (mapper (Array.to_list (Array.sub a 1 (n - 3))))
else begin
Printf.eprintf "Usage: %s [extra_args] <infile> <outfile>" Sys.executable_name;
exit 1
@ -523,3 +529,14 @@ let main mapper =
prerr_endline (Printexc.to_string exn);
exit 2
let main mapper = run_main (fun _ -> mapper)
let standalone_mode = ref true
let registered_mappers = ref []
let register name f =
if !standalone_mode then
run_main f
else
registered_mappers := (name, (f :> string list -> mapper)) :: !registered_mappers

View File

@ -47,12 +47,45 @@ class mapper:
method with_constraint: with_constraint -> with_constraint
end
val apply: source:string -> target:string -> #mapper -> unit
class type main_entry_points =
object
method implementation: string -> structure -> string * structure
method interface: string -> signature -> string * signature
end
val apply: source:string -> target:string -> #main_entry_points -> unit
(** Apply a mapper to a dumped parsetree found in the [source] file
and put the result in the [target] file. *)
val main: #mapper -> unit
(** Entry point to call to implement a -ppx rewriter from a mapper object. *)
val main: #main_entry_points -> unit
(** Entry point to call to implement a standalone -ppx rewriter
from a mapper object. *)
(** {2 Registration API} *)
val standalone_mode: bool ref
val registered_mappers: (string * (string list -> mapper)) list ref
(** Get all registered mappers (order is reversed w.r.t. registration
time. *)
val register: string -> (string list -> #mapper) -> unit
(**
If [standalone_mode] is true, the mapper is run immediatly
and the arguments are taken from the process command line.
This is to support a scenario where a mapper is linked
as a stand-alone executable.
If [standalone_mode] is false, the mapper is registered
to a global table, accessible with [get_registered]. This
is to support -ppx drivers, which combine several mappers
in a single process. Typically, a driver starts
by setting [standalone_mode] to false, then lets ppx rewriters
(linked statically or dynamically) register themselves,
and then run all or some of them. It is also possible
to have -ppx drivers apply rewriters to only specific parts
of an AST.
*)
(** {2 Helpers to build Parsetree fragments} *)