Library
Module
Module type
Parameter
Class
Class type
Public API of ppx_deriving
executable.
type deriver = {
name : string;
core_type : (Parsetree.core_type -> Parsetree.expression) option;
type_decl_str : options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_declaration list ->
Parsetree.structure;
type_ext_str : options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_extension ->
Parsetree.structure;
module_type_decl_str : options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.module_type_declaration ->
Parsetree.structure;
type_decl_sig : options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_declaration list ->
Parsetree.signature;
type_ext_sig : options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_extension ->
Parsetree.signature;
module_type_decl_sig : options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.module_type_declaration ->
Parsetree.signature;
}
A type of deriving plugins.
A structure or signature deriving function accepts a list of ~options
, a ~path
of modules for the type declaration currently being processed (with []
for toplevel phrases), and a type declaration item (type t = .. and t' = ..
), and returns a list of items to be appended after the type declaration item in structure and signature. It is invoked by [\@\@deriving]
annotations.
A type deriving function accepts a type and returns a corresponding derived expression. It is invoked by [%derive.foo:]
and [%foo:]
annotations. If this function is missing, the corresponding [%foo:]
annotation is ignored.
The structure and signature deriving functions are invoked in the order in which they appear in the source code.
val register : deriver -> unit
register deriver
registers deriver
according to its name
field.
val add_register_hook : (deriver -> unit) -> unit
add_register_hook hook
adds hook
to be executed whenever a new deriver is registered.
val derivers : unit -> deriver list
derivers ()
returns all currently registered derivers.
val create :
string ->
?core_type:(Parsetree.core_type -> Parsetree.expression) ->
?type_ext_str:
(options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_extension ->
Parsetree.structure) ->
?type_ext_sig:
(options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_extension ->
Parsetree.signature) ->
?type_decl_str:
(options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_declaration list ->
Parsetree.structure) ->
?type_decl_sig:
(options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.type_declaration list ->
Parsetree.signature) ->
?module_type_decl_str:
(options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.module_type_declaration ->
Parsetree.structure) ->
?module_type_decl_sig:
(options:(string * Parsetree.expression) list ->
path:string list ->
Parsetree.module_type_declaration ->
Parsetree.signature) ->
unit ->
deriver
Creating deriver
structure.
val lookup : string -> deriver option
lookup name
looks up a deriver called name
.
val raise_errorf :
?sub:Location.error list ->
?loc:Location.t ->
('a, unit, string, 'b) Stdlib.format4 ->
'a
Error handling
Ast_helper.Const
is not defined in OCaml <4.03.
string_of_core_type typ
unparses typ
, omitting any attributes.
val string_of_constant_opt : constant -> string option
string_of_constant_opt c
returns Some s
if the constant c
is a string s
, None
otherwise.
string_of_expression_opt e
returns Some s
if the expression e
is a string constant s
, None
otherwise.
module Arg : sig ... end
Arg
contains convenience functions that extract constants from AST fragments, to be used when parsing options or [\@attributes]
attached to types, fields or constructors.
val create_quoter : unit -> quoter
quoter ()
creates an empty quoter.
val quote : quoter:quoter -> Parsetree.expression -> Parsetree.expression
quote quoter expr
records a pure expression expr
within quoter
and returns an expression which has the same value as expr
in the context that sanitize
provides.
val sanitize :
?module_:Longident.t ->
?quoter:quoter ->
Parsetree.expression ->
Parsetree.expression
sanitize module_ quoter expr
wraps expr
in a way that ensures that the contents of module_
and Pervasives
, as well as the identifiers in expressions returned by quote
are in scope, and returns the wrapped expression. module_
defaults to Ppx_deriving_runtime
if it's not provided
val with_quoter :
(quoter -> 'a -> Parsetree.expression) ->
'a ->
Parsetree.expression
with_quoter fn
≡ fun fn a -> let quoter = create_quoter () in sanitize ~quoter (fn quoter a)
expand_path name
returns name
with the path
module path prepended, e.g. expand_path ["Foo";"M"] "t"
= "Foo.M.t"
and expand_path [] "t"
= "t"
path_of_type_decl ~path type_
returns path
if type_
does not have a manifest or the manifest is not a constructor, and the module path of manifest otherwise.
path_of_type_decl
is useful when determining the canonical path location of fields and constructors; e.g. for type bar = M.foo = A | B
, it will return ["M"]
.
val mangle_type_decl :
?fixpoint:string ->
[ `Prefix of string | `Suffix of string | `PrefixSuffix of string * string ] ->
Parsetree.type_declaration ->
string
mangle_type_decl ~fixpoint affix type_
derives a function name from type_
name by doing nothing if type_
is named fixpoint
("t"
by default), or appending and/or prepending affix
via an underscore.
val mangle_lid :
?fixpoint:string ->
[ `Prefix of string | `Suffix of string | `PrefixSuffix of string * string ] ->
Longident.t ->
Longident.t
mangle_lid ~fixpoint affix lid
does the same as mangle_type_decl
, but for the last component of lid
.
attr ~deriver name attrs
searches for an attribute [\@deriving.deriver.attr]
in attrs
if any attribute with name starting with \@deriving.deriver
exists, or [\@deriver.attr]
if any attribute with name starting with \@deriver
exists, or [\@attr]
otherwise.
attr_warning expr
builds the attribute \@ocaml.warning expr
val free_vars_in_core_type : Parsetree.core_type -> tyvar list
free_vars_in_core_type typ
returns unique free variables in typ
in lexical order.
remove_pervasives ~deriver typ
removes the leading "Pervasives." module name in longidents. Type expressions marked with [\@nobuiltin]
are ignored.
The name of the deriving plugin should be passed as deriver
; it is used in error messages.
fresh_var bound
returns a fresh variable name not present in bound
. The name is selected in alphabetical succession.
val fold_left_type_decl :
('a -> tyvar -> 'a) ->
'a ->
Parsetree.type_declaration ->
'a
fold_left_type_decl fn accum type_
performs a left fold over all type variable (i.e. not wildcard) parameters in type_
.
val fold_right_type_decl :
(tyvar -> 'a -> 'a) ->
Parsetree.type_declaration ->
'a ->
'a
fold_right_type_decl fn accum type_
performs a right fold over all type variable (i.e. not wildcard) parameters in type_
.
val fold_left_type_ext :
('a -> tyvar -> 'a) ->
'a ->
Parsetree.type_extension ->
'a
fold_left_type_ext fn accum type_
performs a left fold over all type variable (i.e. not wildcard) parameters in type_
.
val fold_right_type_ext :
(tyvar -> 'a -> 'a) ->
Parsetree.type_extension ->
'a ->
'a
fold_right_type_ext fn accum type_
performs a right fold over all type variable (i.e. not wildcard) parameters in type_
.
val poly_fun_of_type_decl :
Parsetree.type_declaration ->
Parsetree.expression ->
Parsetree.expression
poly_fun_of_type_decl type_ expr
wraps expr
into fun poly_N -> ...
for every type parameter 'N
present in type_
. For example, if type_
refers to type ('a, 'b) map
, expr
will be wrapped into fun poly_a poly_b -> [%e expr]
.
_
parameters are ignored.
Same as poly_fun_of_type_decl
but for type extension.
val poly_apply_of_type_decl :
Parsetree.type_declaration ->
Parsetree.expression ->
Parsetree.expression
poly_apply_of_type_decl type_ expr
wraps expr
into expr poly_N
for every type parameter 'N
present in type_
. For example, if type_
refers to type ('a, 'b) map
, expr
will be wrapped into [%e expr] poly_a poly_b
.
_
parameters are ignored.
val poly_apply_of_type_ext :
Parsetree.type_extension ->
Parsetree.expression ->
Parsetree.expression
Same as poly_apply_of_type_decl
but for type extension.
val poly_arrow_of_type_decl :
(Parsetree.core_type -> Parsetree.core_type) ->
Parsetree.type_declaration ->
Parsetree.core_type ->
Parsetree.core_type
poly_arrow_of_type_decl fn type_ typ
wraps typ
in an arrow with fn [%type: 'N]
as argument for every type parameter 'N
present in type_
. For example, if type_
refers to type ('a, 'b) map
and fn
is fun var -> [%type: [%t var] -> string]
, typ
will be wrapped into ('a -> string) -> ('b -> string) -> [%t typ]
.
_
parameters are ignored.
val poly_arrow_of_type_ext :
(Parsetree.core_type -> Parsetree.core_type) ->
Parsetree.type_extension ->
Parsetree.core_type ->
Parsetree.core_type
Same as poly_arrow_of_type_decl
but for type extension.
core_type_of_type_decl type_
constructs type ('a, 'b, ...) t
for type declaration type ('a, 'b, ...) t = ...
.
Same as core_type_of_type_decl
but for type extension.
val instantiate :
string list ->
Parsetree.type_declaration ->
Parsetree.core_type * string list * string list
instantiate bound type_
returns typ, vars, bound'
where typ
is a type instantiated from type declaration type_
, vars
≡ free_vars_in_core_type typ
and bound'
≡ bound @ vars
.
val fold_exprs :
?unit:Parsetree.expression ->
(Parsetree.expression -> Parsetree.expression -> Parsetree.expression) ->
Parsetree.expression list ->
Parsetree.expression
fold_exprs ~unit fn exprs
folds exprs
using head of exprs
as initial accumulator value, or unit
if exprs = []
.
See also seq_reduce
and binop_reduce
.
val seq_reduce :
?sep:Parsetree.expression ->
Parsetree.expression ->
Parsetree.expression ->
Parsetree.expression
When sep
is present: seq_reduce
≡ fun x a b -> [%expr [%e a]; [%e x]; [%e b]]
. When sep
is missing: seq_reduce
≡ fun a b -> [%expr [%e a]; [%e b]]
.
val binop_reduce :
Parsetree.expression ->
Parsetree.expression ->
Parsetree.expression ->
Parsetree.expression
binop_reduce
≡ fun x a b -> [%expr [%e x] [%e a] [%e b]]
.
strong_type_of_type ty
transform a type ty to freevars . ty
, giving a strong polymorphic type
The mapper for the currently loaded deriving plugins. It is useful for recursively processing expression-valued attributes.