Up

Module Default

Helpers taking a ~loc argument. This module is meant to be opened or aliased.

Signature

include module type of Ast_builder_generated.M
val case : lhs:Parsetree.pattern -> guard:Parsetree.expression option -> rhs:Parsetree.expression -> Parsetree.case
val pcl_constr : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.core_type list -> Parsetree.class_expr
val pcl_structure : loc:Location.t -> Parsetree.class_structure -> Parsetree.class_expr
val pcl_fun : loc:Location.t -> Asttypes.label -> Parsetree.expression option -> Parsetree.pattern -> Parsetree.class_expr -> Parsetree.class_expr
val pcl_apply : loc:Location.t -> Parsetree.class_expr -> (Asttypes.label * Parsetree.expression) list -> Parsetree.class_expr
val pcl_let : loc:Location.t -> Asttypes.rec_flag -> Parsetree.value_binding list -> Parsetree.class_expr -> Parsetree.class_expr
val pcl_constraint : loc:Location.t -> Parsetree.class_expr -> Parsetree.class_type -> Parsetree.class_expr
val pcl_extension : loc:Location.t -> Parsetree.extension -> Parsetree.class_expr
val pcf_inherit : loc:Location.t -> Asttypes.override_flag -> Parsetree.class_expr -> string option -> Parsetree.class_field
val pcf_val : loc:Location.t -> string Asttypes.loc * Asttypes.mutable_flag * Parsetree.class_field_kind -> Parsetree.class_field
val pcf_method : loc:Location.t -> string Asttypes.loc * Asttypes.private_flag * Parsetree.class_field_kind -> Parsetree.class_field
val pcf_constraint : loc:Location.t -> Parsetree.core_type * Parsetree.core_type -> Parsetree.class_field
val pcf_initializer : loc:Location.t -> Parsetree.expression -> Parsetree.class_field
val pcf_attribute : loc:Location.t -> Parsetree.attribute -> Parsetree.class_field
val pcf_extension : loc:Location.t -> Parsetree.extension -> Parsetree.class_field
val class_infos : loc:Location.t -> virt:Asttypes.virtual_flag -> params:(Parsetree.core_type * Asttypes.variance) list -> name:string Asttypes.loc -> expr:'a -> 'a Parsetree.class_infos
val class_signature : self:Parsetree.core_type -> fields:Parsetree.class_type_field list -> Parsetree.class_signature
val class_structure : self:Parsetree.pattern -> fields:Parsetree.class_field list -> Parsetree.class_structure
val pcty_constr : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.core_type list -> Parsetree.class_type
val pcty_signature : loc:Location.t -> Parsetree.class_signature -> Parsetree.class_type
val pcty_arrow : loc:Location.t -> Asttypes.label -> Parsetree.core_type -> Parsetree.class_type -> Parsetree.class_type
val pcty_extension : loc:Location.t -> Parsetree.extension -> Parsetree.class_type
val pctf_inherit : loc:Location.t -> Parsetree.class_type -> Parsetree.class_type_field
val pctf_val : loc:Location.t -> string * Asttypes.mutable_flag * Asttypes.virtual_flag * Parsetree.core_type -> Parsetree.class_type_field
val pctf_method : loc:Location.t -> string * Asttypes.private_flag * Asttypes.virtual_flag * Parsetree.core_type -> Parsetree.class_type_field
val pctf_constraint : loc:Location.t -> Parsetree.core_type * Parsetree.core_type -> Parsetree.class_type_field
val pctf_attribute : loc:Location.t -> Parsetree.attribute -> Parsetree.class_type_field
val pctf_extension : loc:Location.t -> Parsetree.extension -> Parsetree.class_type_field
val constructor_declaration : loc:Location.t -> name:string Asttypes.loc -> args:Parsetree.core_type list -> res:Parsetree.core_type option -> Parsetree.constructor_declaration
val ptyp_any : loc:Location.t -> Parsetree.core_type
val ptyp_var : loc:Location.t -> string -> Parsetree.core_type
val ptyp_arrow : loc:Location.t -> Asttypes.label -> Parsetree.core_type -> Parsetree.core_type -> Parsetree.core_type
val ptyp_tuple : loc:Location.t -> Parsetree.core_type list -> Parsetree.core_type
val ptyp_constr : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.core_type list -> Parsetree.core_type
val ptyp_object : loc:Location.t -> (string * Parsetree.attributes * Parsetree.core_type) list -> Asttypes.closed_flag -> Parsetree.core_type
val ptyp_class : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.core_type list -> Parsetree.core_type
val ptyp_alias : loc:Location.t -> Parsetree.core_type -> string -> Parsetree.core_type
val ptyp_variant : loc:Location.t -> Parsetree.row_field list -> Asttypes.closed_flag -> Asttypes.label list option -> Parsetree.core_type
val ptyp_poly : loc:Location.t -> string list -> Parsetree.core_type -> Parsetree.core_type
val ptyp_package : loc:Location.t -> Parsetree.package_type -> Parsetree.core_type
val ptyp_extension : loc:Location.t -> Parsetree.extension -> Parsetree.core_type
val pexp_ident : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.expression
val pexp_constant : loc:Location.t -> Asttypes.constant -> Parsetree.expression
val pexp_let : loc:Location.t -> Asttypes.rec_flag -> Parsetree.value_binding list -> Parsetree.expression -> Parsetree.expression
val pexp_function : loc:Location.t -> Parsetree.case list -> Parsetree.expression
val pexp_fun : loc:Location.t -> Asttypes.label -> Parsetree.expression option -> Parsetree.pattern -> Parsetree.expression -> Parsetree.expression
val pexp_apply : loc:Location.t -> Parsetree.expression -> (Asttypes.label * Parsetree.expression) list -> Parsetree.expression
val pexp_match : loc:Location.t -> Parsetree.expression -> Parsetree.case list -> Parsetree.expression
val pexp_try : loc:Location.t -> Parsetree.expression -> Parsetree.case list -> Parsetree.expression
val pexp_tuple : loc:Location.t -> Parsetree.expression list -> Parsetree.expression
val pexp_construct : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.expression option -> Parsetree.expression
val pexp_variant : loc:Location.t -> Asttypes.label -> Parsetree.expression option -> Parsetree.expression
val pexp_record : loc:Location.t -> (Longident.t Asttypes.loc * Parsetree.expression) list -> Parsetree.expression option -> Parsetree.expression
val pexp_field : loc:Location.t -> Parsetree.expression -> Longident.t Asttypes.loc -> Parsetree.expression
val pexp_setfield : loc:Location.t -> Parsetree.expression -> Longident.t Asttypes.loc -> Parsetree.expression -> Parsetree.expression
val pexp_array : loc:Location.t -> Parsetree.expression list -> Parsetree.expression
val pexp_ifthenelse : loc:Location.t -> Parsetree.expression -> Parsetree.expression -> Parsetree.expression option -> Parsetree.expression
val pexp_sequence : loc:Location.t -> Parsetree.expression -> Parsetree.expression -> Parsetree.expression
val pexp_while : loc:Location.t -> Parsetree.expression -> Parsetree.expression -> Parsetree.expression
val pexp_for : loc:Location.t -> Parsetree.pattern -> Parsetree.expression -> Parsetree.expression -> Asttypes.direction_flag -> Parsetree.expression -> Parsetree.expression
val pexp_constraint : loc:Location.t -> Parsetree.expression -> Parsetree.core_type -> Parsetree.expression
val pexp_coerce : loc:Location.t -> Parsetree.expression -> Parsetree.core_type option -> Parsetree.core_type -> Parsetree.expression
val pexp_send : loc:Location.t -> Parsetree.expression -> string -> Parsetree.expression
val pexp_new : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.expression
val pexp_setinstvar : loc:Location.t -> string Asttypes.loc -> Parsetree.expression -> Parsetree.expression
val pexp_override : loc:Location.t -> (string Asttypes.loc * Parsetree.expression) list -> Parsetree.expression
val pexp_letmodule : loc:Location.t -> string Asttypes.loc -> Parsetree.module_expr -> Parsetree.expression -> Parsetree.expression
val pexp_assert : loc:Location.t -> Parsetree.expression -> Parsetree.expression
val pexp_lazy : loc:Location.t -> Parsetree.expression -> Parsetree.expression
val pexp_poly : loc:Location.t -> Parsetree.expression -> Parsetree.core_type option -> Parsetree.expression
val pexp_object : loc:Location.t -> Parsetree.class_structure -> Parsetree.expression
val pexp_newtype : loc:Location.t -> string -> Parsetree.expression -> Parsetree.expression
val pexp_pack : loc:Location.t -> Parsetree.module_expr -> Parsetree.expression
val pexp_open : loc:Location.t -> Asttypes.override_flag -> Longident.t Asttypes.loc -> Parsetree.expression -> Parsetree.expression
val pexp_extension : loc:Location.t -> Parsetree.extension -> Parsetree.expression
val extension_constructor : loc:Location.t -> name:string Asttypes.loc -> kind:Parsetree.extension_constructor_kind -> Parsetree.extension_constructor
val include_infos : loc:Location.t -> 'a -> 'a Parsetree.include_infos
val label_declaration : loc:Location.t -> name:string Asttypes.loc -> mutable_:Asttypes.mutable_flag -> type_:Parsetree.core_type -> Parsetree.label_declaration
val lexing_position : fname:string -> lnum:int -> bol:int -> cnum:int -> Lexing.position
val location : start:Lexing.position -> end_:Lexing.position -> ghost:bool -> Location.t
val module_binding : loc:Location.t -> name:string Asttypes.loc -> expr:Parsetree.module_expr -> Parsetree.module_binding
val module_declaration : loc:Location.t -> name:string Asttypes.loc -> type_:Parsetree.module_type -> Parsetree.module_declaration
val pmod_ident : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.module_expr
val pmod_structure : loc:Location.t -> Parsetree.structure -> Parsetree.module_expr
val pmod_functor : loc:Location.t -> string Asttypes.loc -> Parsetree.module_type option -> Parsetree.module_expr -> Parsetree.module_expr
val pmod_apply : loc:Location.t -> Parsetree.module_expr -> Parsetree.module_expr -> Parsetree.module_expr
val pmod_constraint : loc:Location.t -> Parsetree.module_expr -> Parsetree.module_type -> Parsetree.module_expr
val pmod_unpack : loc:Location.t -> Parsetree.expression -> Parsetree.module_expr
val pmod_extension : loc:Location.t -> Parsetree.extension -> Parsetree.module_expr
val pmty_ident : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.module_type
val pmty_signature : loc:Location.t -> Parsetree.signature -> Parsetree.module_type
val pmty_functor : loc:Location.t -> string Asttypes.loc -> Parsetree.module_type option -> Parsetree.module_type -> Parsetree.module_type
val pmty_with : loc:Location.t -> Parsetree.module_type -> Parsetree.with_constraint list -> Parsetree.module_type
val pmty_typeof : loc:Location.t -> Parsetree.module_expr -> Parsetree.module_type
val pmty_extension : loc:Location.t -> Parsetree.extension -> Parsetree.module_type
val pmty_alias : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.module_type
val module_type_declaration : loc:Location.t -> name:string Asttypes.loc -> type_:Parsetree.module_type option -> Parsetree.module_type_declaration
val open_description : loc:Location.t -> lid:Longident.t Asttypes.loc -> override:Asttypes.override_flag -> Parsetree.open_description
val ppat_any : loc:Location.t -> Parsetree.pattern
val ppat_var : loc:Location.t -> string Asttypes.loc -> Parsetree.pattern
val ppat_alias : loc:Location.t -> Parsetree.pattern -> string Asttypes.loc -> Parsetree.pattern
val ppat_constant : loc:Location.t -> Asttypes.constant -> Parsetree.pattern
val ppat_interval : loc:Location.t -> Asttypes.constant -> Asttypes.constant -> Parsetree.pattern
val ppat_tuple : loc:Location.t -> Parsetree.pattern list -> Parsetree.pattern
val ppat_construct : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.pattern option -> Parsetree.pattern
val ppat_variant : loc:Location.t -> Asttypes.label -> Parsetree.pattern option -> Parsetree.pattern
val ppat_record : loc:Location.t -> (Longident.t Asttypes.loc * Parsetree.pattern) list -> Asttypes.closed_flag -> Parsetree.pattern
val ppat_array : loc:Location.t -> Parsetree.pattern list -> Parsetree.pattern
val ppat_or : loc:Location.t -> Parsetree.pattern -> Parsetree.pattern -> Parsetree.pattern
val ppat_constraint : loc:Location.t -> Parsetree.pattern -> Parsetree.core_type -> Parsetree.pattern
val ppat_type : loc:Location.t -> Longident.t Asttypes.loc -> Parsetree.pattern
val ppat_lazy : loc:Location.t -> Parsetree.pattern -> Parsetree.pattern
val ppat_unpack : loc:Location.t -> string Asttypes.loc -> Parsetree.pattern
val ppat_exception : loc:Location.t -> Parsetree.pattern -> Parsetree.pattern
val ppat_extension : loc:Location.t -> Parsetree.extension -> Parsetree.pattern
val psig_value : loc:Location.t -> Parsetree.value_description -> Parsetree.signature_item
val psig_type : loc:Location.t -> Parsetree.type_declaration list -> Parsetree.signature_item
val psig_typext : loc:Location.t -> Parsetree.type_extension -> Parsetree.signature_item
val psig_exception : loc:Location.t -> Parsetree.extension_constructor -> Parsetree.signature_item
val psig_module : loc:Location.t -> Parsetree.module_declaration -> Parsetree.signature_item
val psig_recmodule : loc:Location.t -> Parsetree.module_declaration list -> Parsetree.signature_item
val psig_modtype : loc:Location.t -> Parsetree.module_type_declaration -> Parsetree.signature_item
val psig_open : loc:Location.t -> Parsetree.open_description -> Parsetree.signature_item
val psig_include : loc:Location.t -> Parsetree.include_description -> Parsetree.signature_item
val psig_class : loc:Location.t -> Parsetree.class_description list -> Parsetree.signature_item
val psig_class_type : loc:Location.t -> Parsetree.class_type_declaration list -> Parsetree.signature_item
val psig_attribute : loc:Location.t -> Parsetree.attribute -> Parsetree.signature_item
val psig_extension : loc:Location.t -> Parsetree.extension -> Parsetree.attributes -> Parsetree.signature_item
val pstr_eval : loc:Location.t -> Parsetree.expression -> Parsetree.attributes -> Parsetree.structure_item
val pstr_value : loc:Location.t -> Asttypes.rec_flag -> Parsetree.value_binding list -> Parsetree.structure_item
val pstr_primitive : loc:Location.t -> Parsetree.value_description -> Parsetree.structure_item
val pstr_type : loc:Location.t -> Parsetree.type_declaration list -> Parsetree.structure_item
val pstr_typext : loc:Location.t -> Parsetree.type_extension -> Parsetree.structure_item
val pstr_exception : loc:Location.t -> Parsetree.extension_constructor -> Parsetree.structure_item
val pstr_module : loc:Location.t -> Parsetree.module_binding -> Parsetree.structure_item
val pstr_recmodule : loc:Location.t -> Parsetree.module_binding list -> Parsetree.structure_item
val pstr_modtype : loc:Location.t -> Parsetree.module_type_declaration -> Parsetree.structure_item
val pstr_open : loc:Location.t -> Parsetree.open_description -> Parsetree.structure_item
val pstr_class : loc:Location.t -> Parsetree.class_declaration list -> Parsetree.structure_item
val pstr_class_type : loc:Location.t -> Parsetree.class_type_declaration list -> Parsetree.structure_item
val pstr_include : loc:Location.t -> Parsetree.include_declaration -> Parsetree.structure_item
val pstr_attribute : loc:Location.t -> Parsetree.attribute -> Parsetree.structure_item
val pstr_extension : loc:Location.t -> Parsetree.extension -> Parsetree.attributes -> Parsetree.structure_item
val type_declaration : loc:Location.t -> name:string Asttypes.loc -> params:(Parsetree.core_type * Asttypes.variance) list -> cstrs:(Parsetree.core_type * Parsetree.core_type * Location.t) list -> kind:Parsetree.type_kind -> private_:Asttypes.private_flag -> manifest:Parsetree.core_type option -> Parsetree.type_declaration
val type_extension : path:Longident.t Asttypes.loc -> params:(Parsetree.core_type * Asttypes.variance) list -> constructors:Parsetree.extension_constructor list -> private_:Asttypes.private_flag -> Parsetree.type_extension
val value_binding : loc:Location.t -> pat:Parsetree.pattern -> expr:Parsetree.expression -> Parsetree.value_binding
val value_description : loc:Location.t -> name:string Asttypes.loc -> type_:Parsetree.core_type -> prim:string list -> Parsetree.value_description
include Ast_builder_intf.Additional_helpers with type 'a with_loc := 'a Ast_builder_intf.with_location
type 'a with_loc
val eint : (int -> Parsetree.expression) with_loc
val echar : (char -> Parsetree.expression) with_loc
val estring : (string -> Parsetree.expression) with_loc
val efloat : (string -> Parsetree.expression) with_loc
val eint32 : (int32 -> Parsetree.expression) with_loc
val eint64 : (int64 -> Parsetree.expression) with_loc
val enativeint : (nativeint -> Parsetree.expression) with_loc
val ebool : (bool -> Parsetree.expression) with_loc
val pint : (int -> Parsetree.pattern) with_loc
val pchar : (char -> Parsetree.pattern) with_loc
val pstring : (string -> Parsetree.pattern) with_loc
val pfloat : (string -> Parsetree.pattern) with_loc
val pint32 : (int32 -> Parsetree.pattern) with_loc
val pint64 : (int64 -> Parsetree.pattern) with_loc
val pnativeint : (nativeint -> Parsetree.pattern) with_loc
val pbool : (bool -> Parsetree.pattern) with_loc
val eunit : Parsetree.expression with_loc
val punit : Parsetree.pattern with_loc
val evar : (string -> Parsetree.expression) with_loc

evar id produces a Pexp_ident _ expression, it parses its input so you can pass any dot-separated identifier, for instance: evar ~loc "Foo.bar".

val pvar : (string -> Parsetree.pattern) with_loc
val eapply : (Parsetree.expression -> Parsetree.expression list -> Parsetree.expression) with_loc

Same as pexp_apply but without labels

val eabstract : (Parsetree.pattern list -> Parsetree.expression -> Parsetree.expression) with_loc
val pconstruct : Parsetree.constructor_declaration -> Parsetree.pattern option -> Parsetree.pattern
val econstruct : Parsetree.constructor_declaration -> Parsetree.expression option -> Parsetree.expression
val elist : (Parsetree.expression list -> Parsetree.expression) with_loc
val plist : (Parsetree.pattern list -> Parsetree.pattern) with_loc
val nonrec_type_declaration : (name:string Location.loc -> params:(Parsetree.core_type * Asttypes.variance) list -> cstrs:(Parsetree.core_type * Parsetree.core_type * Location.t) list -> kind:Parsetree.type_kind -> private_:Asttypes.private_flag -> manifest:Parsetree.core_type option -> Parsetree.type_declaration) with_loc