2013-01-16 08:10:29 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* OCaml *)
|
|
|
|
(* *)
|
|
|
|
(* Alain Frisch, LexiFi *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2012 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(** Helpers to write Parsetree rewriters *)
|
|
|
|
|
|
|
|
open Parsetree
|
|
|
|
|
|
|
|
(** {2 A generic mapper class} *)
|
|
|
|
|
|
|
|
class mapper:
|
|
|
|
object
|
2013-04-19 00:40:57 -07:00
|
|
|
method case: case -> case
|
|
|
|
method cases: case list -> case list
|
2013-01-16 08:10:29 -08:00
|
|
|
method class_declaration: class_declaration -> class_declaration
|
|
|
|
method class_description: class_description -> class_description
|
|
|
|
method class_expr: class_expr -> class_expr
|
|
|
|
method class_field: class_field -> class_field
|
|
|
|
method class_signature: class_signature -> class_signature
|
|
|
|
method class_structure: class_structure -> class_structure
|
|
|
|
method class_type: class_type -> class_type
|
|
|
|
method class_type_declaration: class_type_declaration -> class_type_declaration
|
|
|
|
method class_type_field: class_type_field -> class_type_field
|
|
|
|
method expr: expression -> expression
|
|
|
|
method implementation: string -> structure -> string * structure
|
|
|
|
method interface: string -> signature -> string * signature
|
|
|
|
method location: Location.t -> Location.t
|
2013-03-05 08:50:05 -08:00
|
|
|
method module_binding: module_binding -> module_binding
|
2013-03-04 09:39:07 -08:00
|
|
|
method module_declaration: module_declaration -> module_declaration
|
2013-01-16 08:10:29 -08:00
|
|
|
method module_expr: module_expr -> module_expr
|
|
|
|
method module_type: module_type -> module_type
|
2013-03-06 04:14:02 -08:00
|
|
|
method module_type_declaration: module_type_declaration -> module_type_declaration
|
2013-01-16 08:10:29 -08:00
|
|
|
method pat: pattern -> pattern
|
|
|
|
method signature: signature -> signature
|
2013-03-01 04:44:04 -08:00
|
|
|
method signature_item: signature_item -> signature_item
|
2013-01-16 08:10:29 -08:00
|
|
|
method structure: structure -> structure
|
2013-03-01 04:44:04 -08:00
|
|
|
method structure_item: structure_item -> structure_item
|
2013-01-16 08:10:29 -08:00
|
|
|
method typ: core_type -> core_type
|
|
|
|
method type_declaration: type_declaration -> type_declaration
|
|
|
|
method type_kind: type_kind -> type_kind
|
|
|
|
method value_description: value_description -> value_description
|
|
|
|
method with_constraint: with_constraint -> with_constraint
|
2013-03-01 04:44:04 -08:00
|
|
|
method attribute: attribute -> attribute
|
2013-03-08 06:59:45 -08:00
|
|
|
method attributes: attribute list -> attribute list
|
2013-03-01 04:44:04 -08:00
|
|
|
method extension: extension -> extension
|
2013-03-06 05:51:18 -08:00
|
|
|
method constructor_declaration: constructor_declaration -> constructor_declaration
|
|
|
|
method label_declaration: label_declaration -> label_declaration
|
2013-06-03 08:14:19 -07:00
|
|
|
method value_binding: value_binding -> value_binding
|
2013-07-22 07:58:15 -07:00
|
|
|
method payload: payload -> payload
|
2013-01-16 08:10:29 -08:00
|
|
|
end
|
|
|
|
|
2013-01-23 01:15:41 -08:00
|
|
|
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
|
2013-01-16 08:10:29 -08:00
|
|
|
(** Apply a mapper to a dumped parsetree found in the [source] file
|
|
|
|
and put the result in the [target] file. *)
|
|
|
|
|
2013-01-23 01:15:41 -08:00
|
|
|
val main: #main_entry_points -> unit
|
|
|
|
(** Entry point to call to implement a standalone -ppx rewriter
|
|
|
|
from a mapper object. *)
|
|
|
|
|
2013-01-23 02:15:45 -08:00
|
|
|
val run_main: (string list -> #main_entry_points) -> unit
|
|
|
|
(** Same as [main], but with extra arguments from the command line. *)
|
|
|
|
|
2013-01-23 01:15:41 -08:00
|
|
|
(** {2 Registration API} *)
|
|
|
|
|
2013-01-23 02:15:45 -08:00
|
|
|
val register_function: (string -> (string list -> mapper) -> unit) ref
|
2013-01-23 01:15:41 -08:00
|
|
|
|
|
|
|
val register: string -> (string list -> #mapper) -> unit
|
|
|
|
|
2013-01-23 02:15:45 -08:00
|
|
|
(** Apply the [register_function]. The default behavior is to run
|
2013-02-07 22:04:36 -08:00
|
|
|
the mapper immediately, taking arguments from the process
|
2013-01-23 02:15:45 -08:00
|
|
|
command line. This is to support a scenario where a mapper is
|
|
|
|
linked as a stand-alone executable.
|
|
|
|
|
|
|
|
It is possible to overwrite the [register_function] to define
|
|
|
|
"-ppx drivers", which combine several mappers in a single
|
|
|
|
process. Typically, a driver starts by defining
|
|
|
|
[register_function] to a custom implementation, 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. *)
|
2013-09-03 01:59:23 -07:00
|
|
|
|
|
|
|
(** {2 Convenience functions to write mappers} *)
|
|
|
|
|
|
|
|
val map_opt: ('a -> 'b) -> 'a option -> 'b option
|