Module Parsetree
Abstract syntax tree produced by parsing
Warning: this module is unstable and part of compiler-libs.
type constant=|Pconst_integer of string * char option|Pconst_char of char|Pconst_string of string * string option|Pconst_float of string * char option
Extension points
type attribute={attr_name : string Asttypes.loc;attr_payload : payload;attr_loc : Location.t;}and extension= string Asttypes.loc * payloadand attributes= attribute listand payload=|PStr of structure|PSig of signature|PTyp of core_type|PPat of pattern * expression option
Core language
and core_type={ptyp_desc : core_type_desc;ptyp_loc : Location.t;ptyp_loc_stack : Location.t list;ptyp_attributes : attributes;}and core_type_desc=|Ptyp_any|Ptyp_var of string|Ptyp_arrow of Asttypes.arg_label * core_type * core_type|Ptyp_tuple of core_type list|Ptyp_constr of Longident.t Asttypes.loc * core_type list|Ptyp_object of object_field list * Asttypes.closed_flag|Ptyp_class of Longident.t Asttypes.loc * core_type list|Ptyp_alias of core_type * string|Ptyp_variant of row_field list * Asttypes.closed_flag * Asttypes.label list option|Ptyp_poly of string Asttypes.loc list * core_type|Ptyp_package of package_type|Ptyp_extension of extensionand package_type= Longident.t Asttypes.loc * (Longident.t Asttypes.loc * core_type) listand row_field={prf_desc : row_field_desc;prf_loc : Location.t;prf_attributes : attributes;}and row_field_desc=|Rtag of Asttypes.label Asttypes.loc * bool * core_type list|Rinherit of core_typeand object_field={pof_desc : object_field_desc;pof_loc : Location.t;pof_attributes : attributes;}and object_field_desc=|Otag of Asttypes.label Asttypes.loc * core_type|Oinherit of core_typeand pattern={ppat_desc : pattern_desc;ppat_loc : Location.t;ppat_loc_stack : Location.t list;ppat_attributes : attributes;}and pattern_desc=|Ppat_any|Ppat_var of string Asttypes.loc|Ppat_alias of pattern * string Asttypes.loc|Ppat_constant of constant|Ppat_interval of constant * constant|Ppat_tuple of pattern list|Ppat_construct of Longident.t Asttypes.loc * pattern option|Ppat_variant of Asttypes.label * pattern option|Ppat_record of (Longident.t Asttypes.loc * pattern) list * Asttypes.closed_flag|Ppat_array of pattern list|Ppat_or of pattern * pattern|Ppat_constraint of pattern * core_type|Ppat_type of Longident.t Asttypes.loc|Ppat_lazy of pattern|Ppat_unpack of string Asttypes.loc|Ppat_exception of pattern|Ppat_extension of extension|Ppat_open of Longident.t Asttypes.loc * patternand expression={pexp_desc : expression_desc;pexp_loc : Location.t;pexp_loc_stack : Location.t list;pexp_attributes : attributes;}and expression_desc=and case={pc_lhs : pattern;pc_guard : expression option;pc_rhs : expression;}and binding_op={pbop_op : string Asttypes.loc;pbop_pat : pattern;pbop_exp : expression;pbop_loc : Location.t;}and value_description={pval_name : string Asttypes.loc;pval_type : core_type;pval_prim : string list;pval_attributes : attributes;pval_loc : Location.t;}and type_declaration={ptype_name : string Asttypes.loc;ptype_params : (core_type * Asttypes.variance) list;ptype_cstrs : (core_type * core_type * Location.t) list;ptype_kind : type_kind;ptype_private : Asttypes.private_flag;ptype_manifest : core_type option;ptype_attributes : attributes;ptype_loc : Location.t;}and type_kind=|Ptype_abstract|Ptype_variant of constructor_declaration list|Ptype_record of label_declaration list|Ptype_openand label_declaration={pld_name : string Asttypes.loc;pld_mutable : Asttypes.mutable_flag;pld_type : core_type;pld_loc : Location.t;pld_attributes : attributes;}and constructor_declaration={pcd_name : string Asttypes.loc;pcd_args : constructor_arguments;pcd_res : core_type option;pcd_loc : Location.t;pcd_attributes : attributes;}and constructor_arguments=|Pcstr_tuple of core_type list|Pcstr_record of label_declaration listand type_extension={ptyext_path : Longident.t Asttypes.loc;ptyext_params : (core_type * Asttypes.variance) list;ptyext_constructors : extension_constructor list;ptyext_private : Asttypes.private_flag;ptyext_loc : Location.t;ptyext_attributes : attributes;}and extension_constructor={pext_name : string Asttypes.loc;pext_kind : extension_constructor_kind;pext_loc : Location.t;pext_attributes : attributes;}and type_exception={ptyexn_constructor : extension_constructor;ptyexn_loc : Location.t;ptyexn_attributes : attributes;}and extension_constructor_kind=|Pext_decl of constructor_arguments * core_type option|Pext_rebind of Longident.t Asttypes.loc
Class language
and class_type={pcty_desc : class_type_desc;pcty_loc : Location.t;pcty_attributes : attributes;}and class_type_desc=|Pcty_constr of Longident.t Asttypes.loc * core_type list|Pcty_signature of class_signature|Pcty_arrow of Asttypes.arg_label * core_type * class_type|Pcty_extension of extension|Pcty_open of open_description * class_typeand class_signature={pcsig_self : core_type;pcsig_fields : class_type_field list;}and class_type_field={pctf_desc : class_type_field_desc;pctf_loc : Location.t;pctf_attributes : attributes;}and class_type_field_desc=|Pctf_inherit of class_type|Pctf_val of Asttypes.label Asttypes.loc * Asttypes.mutable_flag * Asttypes.virtual_flag * core_type|Pctf_method of Asttypes.label Asttypes.loc * Asttypes.private_flag * Asttypes.virtual_flag * core_type|Pctf_constraint of core_type * core_type|Pctf_attribute of attribute|Pctf_extension of extensionand 'a class_infos={pci_virt : Asttypes.virtual_flag;pci_params : (core_type * Asttypes.variance) list;pci_name : string Asttypes.loc;pci_expr : 'a;pci_loc : Location.t;pci_attributes : attributes;}and class_description= class_type class_infosand class_type_declaration= class_type class_infosand class_expr={pcl_desc : class_expr_desc;pcl_loc : Location.t;pcl_attributes : attributes;}and class_expr_desc=|Pcl_constr of Longident.t Asttypes.loc * core_type list|Pcl_structure of class_structure|Pcl_fun of Asttypes.arg_label * expression option * pattern * class_expr|Pcl_apply of class_expr * (Asttypes.arg_label * expression) list|Pcl_let of Asttypes.rec_flag * value_binding list * class_expr|Pcl_constraint of class_expr * class_type|Pcl_extension of extension|Pcl_open of open_description * class_exprand class_structure={pcstr_self : pattern;pcstr_fields : class_field list;}and class_field={pcf_desc : class_field_desc;pcf_loc : Location.t;pcf_attributes : attributes;}and class_field_desc=|Pcf_inherit of Asttypes.override_flag * class_expr * string Asttypes.loc option|Pcf_val of Asttypes.label Asttypes.loc * Asttypes.mutable_flag * class_field_kind|Pcf_method of Asttypes.label Asttypes.loc * Asttypes.private_flag * class_field_kind|Pcf_constraint of core_type * core_type|Pcf_initializer of expression|Pcf_attribute of attribute|Pcf_extension of extensionand class_field_kind=|Cfk_virtual of core_type|Cfk_concrete of Asttypes.override_flag * expressionand class_declaration= class_expr class_infos
Module language
and module_type={pmty_desc : module_type_desc;pmty_loc : Location.t;pmty_attributes : attributes;}and module_type_desc=|Pmty_ident of Longident.t Asttypes.loc|Pmty_signature of signature|Pmty_functor of string Asttypes.loc * module_type option * module_type|Pmty_with of module_type * with_constraint list|Pmty_typeof of module_expr|Pmty_extension of extension|Pmty_alias of Longident.t Asttypes.locand signature= signature_item listand signature_item={psig_desc : signature_item_desc;psig_loc : Location.t;}and signature_item_desc=|Psig_value of value_description|Psig_type of Asttypes.rec_flag * type_declaration list|Psig_typesubst of type_declaration list|Psig_typext of type_extension|Psig_exception of type_exception|Psig_module of module_declaration|Psig_modsubst of module_substitution|Psig_recmodule of module_declaration list|Psig_modtype of module_type_declaration|Psig_open of open_description|Psig_include of include_description|Psig_class of class_description list|Psig_class_type of class_type_declaration list|Psig_attribute of attribute|Psig_extension of extension * attributesand module_declaration={pmd_name : string Asttypes.loc;pmd_type : module_type;pmd_attributes : attributes;pmd_loc : Location.t;}and module_substitution={pms_name : string Asttypes.loc;pms_manifest : Longident.t Asttypes.loc;pms_attributes : attributes;pms_loc : Location.t;}and module_type_declaration={pmtd_name : string Asttypes.loc;pmtd_type : module_type option;pmtd_attributes : attributes;pmtd_loc : Location.t;}and 'a open_infos={popen_expr : 'a;popen_override : Asttypes.override_flag;popen_loc : Location.t;popen_attributes : attributes;}and open_description= Longident.t Asttypes.loc open_infosand open_declaration= module_expr open_infosand 'a include_infos={pincl_mod : 'a;pincl_loc : Location.t;pincl_attributes : attributes;}and include_description= module_type include_infosand include_declaration= module_expr include_infosand with_constraint=|Pwith_type of Longident.t Asttypes.loc * type_declaration|Pwith_module of Longident.t Asttypes.loc * Longident.t Asttypes.loc|Pwith_typesubst of Longident.t Asttypes.loc * type_declaration|Pwith_modsubst of Longident.t Asttypes.loc * Longident.t Asttypes.locand module_expr={pmod_desc : module_expr_desc;pmod_loc : Location.t;pmod_attributes : attributes;}and module_expr_desc=|Pmod_ident of Longident.t Asttypes.loc|Pmod_structure of structure|Pmod_functor of string Asttypes.loc * module_type option * module_expr|Pmod_apply of module_expr * module_expr|Pmod_constraint of module_expr * module_type|Pmod_unpack of expression|Pmod_extension of extensionand structure= structure_item listand structure_item={pstr_desc : structure_item_desc;pstr_loc : Location.t;}and structure_item_desc=|Pstr_eval of expression * attributes|Pstr_value of Asttypes.rec_flag * value_binding list|Pstr_primitive of value_description|Pstr_type of Asttypes.rec_flag * type_declaration list|Pstr_typext of type_extension|Pstr_exception of type_exception|Pstr_module of module_binding|Pstr_recmodule of module_binding list|Pstr_modtype of module_type_declaration|Pstr_open of open_declaration|Pstr_class of class_declaration list|Pstr_class_type of class_type_declaration list|Pstr_include of include_declaration|Pstr_attribute of attribute|Pstr_extension of extension * attributesand value_binding={pvb_pat : pattern;pvb_expr : expression;pvb_attributes : attributes;pvb_loc : Location.t;}and module_binding={pmb_name : string Asttypes.loc;pmb_expr : module_expr;pmb_attributes : attributes;pmb_loc : Location.t;}
Toplevel
type toplevel_phrase=|Ptop_def of structure|Ptop_dir of toplevel_directiveand toplevel_directive={pdir_name : string Asttypes.loc;pdir_arg : directive_argument option;pdir_loc : Location.t;}and directive_argument={pdira_desc : directive_argument_desc;pdira_loc : Location.t;}and directive_argument_desc=|Pdir_string of string|Pdir_int of string * char option|Pdir_ident of Longident.t|Pdir_bool of bool