diff --git a/ast/ast.ml b/ast/ast.ml index 557abb06..1f3bd371 100644 --- a/ast/ast.ml +++ b/ast/ast.ml @@ -26,9 +26,9 @@ open Import - renaming a few types: - - Location.t -> location - - Longident.t -> longident - - adding a type longident_loc = longident loc and replacing all the occurrences of the + - adding a type longident_loc = longident_loc and replacing all the occurrences of the latter by the former. This is so that we can override iteration at the level of a - longident loc + longident_loc - adding a type cases = case list - replacing all occurrences of "case list" by "cases" - replacing all the (*IF_CURRENT = Foo.bar*) by: = Foo.bar @@ -179,7 +179,7 @@ and core_type_desc = Parsetree.core_type_desc = [T1 * ... * Tn]. Invariant: [n >= 2]. *) - | Ptyp_constr of longident loc * core_type list + | Ptyp_constr of longident_loc * core_type list (** [Ptyp_constr(lident, l)] represents: - [tconstr] when [l=[]], - [T tconstr] when [l=[T]], @@ -190,7 +190,7 @@ and core_type_desc = Parsetree.core_type_desc = {{!Asttypes.closed_flag.Closed} [Closed]}, - [< l1:T1; ...; ln:Tn; .. >] when [flag] is {{!Asttypes.closed_flag.Open} [Open]}. *) - | Ptyp_class of longident loc * core_type list + | Ptyp_class of longident_loc * core_type list (** [Ptyp_class(tconstr, l)] represents: - [#tconstr] when [l=[]], - [T #tconstr] when [l=[T]], @@ -238,10 +238,10 @@ and core_type_desc = Parsetree.core_type_desc = - As the {{!value_description.pval_type} [pval_type]} field of a {!value_description}. *) | Ptyp_package of package_type (** [(module S)]. *) - | Ptyp_open of longident loc * core_type (** [M.(T)] *) + | Ptyp_open of longident_loc * core_type (** [M.(T)] *) | Ptyp_extension of extension (** [[%id]]. *) -and package_type = longident loc * (longident loc * core_type) list +and package_type = longident_loc * (longident_loc * core_type) list (** As {!package_type} typed values: - [(S, [])] represents [(module S)], - [(S, [(t1, T1) ; ... ; (tn, Tn)])] represents @@ -302,7 +302,7 @@ and pattern_desc = Parsetree.pattern_desc = (** Patterns [(P1, ..., Pn)]. Invariant: [n >= 2] *) - | Ppat_construct of longident loc * (string loc list * pattern) option + | Ppat_construct of longident_loc * (string loc list * pattern) option (** [Ppat_construct(C, args)] represents: - [C] when [args] is [None], - [C P] when [args] is [Some ([], P)] @@ -313,7 +313,7 @@ and pattern_desc = Parsetree.pattern_desc = (** [Ppat_variant(`A, pat)] represents: - [`A] when [pat] is [None], - [`A P] when [pat] is [Some P] *) - | Ppat_record of (longident loc * pattern) list * closed_flag + | Ppat_record of (longident_loc * pattern) list * closed_flag (** [Ppat_record([(l1, P1) ; ... ; (ln, Pn)], flag)] represents: - [{ l1=P1; ...; ln=Pn }] when [flag] is {{!Asttypes.closed_flag.Closed} [Closed]} @@ -324,7 +324,7 @@ and pattern_desc = Parsetree.pattern_desc = | Ppat_array of pattern list (** Pattern [[| P1; ...; Pn |]] *) | Ppat_or of pattern * pattern (** Pattern [P1 | P2] *) | Ppat_constraint of pattern * core_type (** Pattern [(P : T)] *) - | Ppat_type of longident loc (** Pattern [#tconst] *) + | Ppat_type of longident_loc (** Pattern [#tconst] *) | Ppat_lazy of pattern (** Pattern [lazy P] *) | Ppat_unpack of string option loc (** [Ppat_unpack(s)] represents: @@ -335,7 +335,7 @@ and pattern_desc = Parsetree.pattern_desc = [Ppat_constraint(Ppat_unpack(Some "P"), Ptyp_package S)] *) | Ppat_exception of pattern (** Pattern [exception P] *) | Ppat_extension of extension (** Pattern [[%id]] *) - | Ppat_open of longident loc * pattern (** Pattern [M.(P)] *) + | Ppat_open of longident_loc * pattern (** Pattern [M.(P)] *) (** {2 Value expressions} *) @@ -347,7 +347,7 @@ and expression = Parsetree.expression = { } and expression_desc = Parsetree.expression_desc = - | Pexp_ident of longident loc (** Identifiers such as [x] and [M.x] *) + | Pexp_ident of longident_loc (** Identifiers such as [x] and [M.x] *) | Pexp_constant of constant (** Expressions constant such as [1], ['a'], ["true"], [1.0], [1l], [1L], [1n] *) @@ -386,7 +386,7 @@ and expression_desc = Parsetree.expression_desc = (** Expressions [(E1, ..., En)] Invariant: [n >= 2] *) - | Pexp_construct of longident loc * expression option + | Pexp_construct of longident_loc * expression option (** [Pexp_construct(C, exp)] represents: - [C] when [exp] is [None], - [C E] when [exp] is [Some E], @@ -395,14 +395,14 @@ and expression_desc = Parsetree.expression_desc = (** [Pexp_variant(`A, exp)] represents - [`A] when [exp] is [None] - [`A E] when [exp] is [Some E] *) - | Pexp_record of (longident loc * expression) list * expression option + | Pexp_record of (longident_loc * expression) list * expression option (** [Pexp_record([(l1,P1) ; ... ; (ln,Pn)], exp0)] represents - [{ l1=P1; ...; ln=Pn }] when [exp0] is [None] - [{ E0 with l1=P1; ...; ln=Pn }] when [exp0] is [Some E0] Invariant: [n > 0] *) - | Pexp_field of expression * longident loc (** [E.l] *) - | Pexp_setfield of expression * longident loc * expression + | Pexp_field of expression * longident_loc (** [E.l] *) + | Pexp_setfield of expression * longident_loc * expression (** [E1.l <- E2] *) | Pexp_array of expression list (** [[| E1; ...; En |]] *) | Pexp_ifthenelse of expression * expression * expression option @@ -421,7 +421,7 @@ and expression_desc = Parsetree.expression_desc = - [(E :> T)] when [from] is [None], - [(E : T0 :> T)] when [from] is [Some T0]. *) | Pexp_send of expression * label loc (** [E # m] *) - | Pexp_new of longident loc (** [new M.c] *) + | Pexp_new of longident_loc (** [new M.c] *) | Pexp_setinstvar of label loc * expression (** [x <- 2] *) | Pexp_override of (label loc * expression) list (** [{< x1 = E1; ...; xn = En >}] *) @@ -628,7 +628,7 @@ and constructor_arguments = Parsetree.constructor_arguments = [args = Pcstr_record [...]]. *) and type_extension = Parsetree.type_extension = { - ptyext_path : longident loc; + ptyext_path : longident_loc; ptyext_params : (core_type * (variance * injectivity)) list; ptyext_constructors : extension_constructor list; ptyext_private : private_flag; @@ -696,7 +696,7 @@ and class_type = Parsetree.class_type = { } and class_type_desc = Parsetree.class_type_desc = - | Pcty_constr of longident loc * core_type list + | Pcty_constr of longident_loc * core_type list (** - [c] - [['a1, ..., 'an] c] *) | Pcty_signature of class_signature (** [object ... end] *) @@ -764,7 +764,7 @@ and class_expr = Parsetree.class_expr = { } and class_expr_desc = Parsetree.class_expr_desc = - | Pcl_constr of longident loc * core_type list + | Pcl_constr of longident_loc * core_type list (** [c] and [['a1, ..., 'an] c] *) | Pcl_structure of class_structure (** [object ... end] *) | Pcl_fun of arg_label * expression option * pattern * class_expr @@ -863,14 +863,14 @@ and module_type = Parsetree.module_type = { } and module_type_desc = Parsetree.module_type_desc = - | Pmty_ident of longident loc (** [Pmty_ident(S)] represents [S] *) + | Pmty_ident of longident_loc (** [Pmty_ident(S)] represents [S] *) | Pmty_signature of signature (** [sig ... end] *) | Pmty_functor of functor_parameter * module_type (** [functor(X : MT1) -> MT2] *) | Pmty_with of module_type * with_constraint list (** [MT with ...] *) | Pmty_typeof of module_expr (** [module type of ME] *) | Pmty_extension of extension (** [[%id]] *) - | Pmty_alias of longident loc (** [(module M)] *) + | Pmty_alias of longident_loc (** [(module M)] *) and functor_parameter = Parsetree.functor_parameter = | Unit (** [()] *) @@ -922,7 +922,7 @@ and module_declaration = Parsetree.module_declaration = { and module_substitution = Parsetree.module_substitution = { pms_name : string loc; - pms_manifest : longident loc; + pms_manifest : longident_loc; pms_attributes : attributes; (** [... [\@\@id1] [\@\@id2]] *) pms_loc : location; } @@ -952,7 +952,7 @@ and 'a open_infos = 'a Parsetree.open_infos = { - [open X] when {{!open_infos.popen_override} [popen_override]} is {{!Asttypes.override_flag.Fresh} [Fresh]} *) -and open_description = longident loc open_infos +and open_description = longident_loc open_infos (** Values of type [open_description] represents: - [open M.N] - [open M(N).O] *) @@ -976,19 +976,19 @@ and include_declaration = module_expr include_infos (** Values of type [include_declaration] represents [include ME] *) and with_constraint = Parsetree.with_constraint = - | Pwith_type of longident loc * type_declaration + | Pwith_type of longident_loc * type_declaration (** [with type X.t = ...] Note: the last component of the longident must match the name of the type_declaration. *) - | Pwith_module of longident loc * longident loc (** [with module X.Y = Z] *) - | Pwith_modtype of longident loc * module_type + | Pwith_module of longident_loc * longident_loc (** [with module X.Y = Z] *) + | Pwith_modtype of longident_loc * module_type (** [with module type X.Y = Z] *) - | Pwith_modtypesubst of longident loc * module_type + | Pwith_modtypesubst of longident_loc * module_type (** [with module type X.Y := sig end] *) - | Pwith_typesubst of longident loc * type_declaration + | Pwith_typesubst of longident_loc * type_declaration (** [with type X.t := ..., same format as [Pwith_type]] *) - | Pwith_modsubst of longident loc * longident loc + | Pwith_modsubst of longident_loc * longident_loc (** [with module X.Y := Z] *) (** {2 Value expressions for the module language} *) @@ -1000,7 +1000,7 @@ and module_expr = Parsetree.module_expr = { } and module_expr_desc = Parsetree.module_expr_desc = - | Pmod_ident of longident loc (** [X] *) + | Pmod_ident of longident_loc (** [X] *) | Pmod_structure of structure (** [struct ... end] *) | Pmod_functor of functor_parameter * module_expr (** [functor(X : MT1) -> ME] *) @@ -1246,7 +1246,7 @@ class virtual map = let a = self#list self#core_type a in Ptyp_tuple a | Ptyp_constr (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in Ptyp_constr (a, b) | Ptyp_object (a, b) -> @@ -1254,7 +1254,7 @@ class virtual map = let b = self#closed_flag b in Ptyp_object (a, b) | Ptyp_class (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in Ptyp_class (a, b) | Ptyp_alias (a, b) -> @@ -1274,7 +1274,7 @@ class virtual map = let a = self#package_type a in Ptyp_package a | Ptyp_open (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#core_type b in Ptyp_open (a, b) | Ptyp_extension a -> @@ -1283,11 +1283,11 @@ class virtual map = method package_type : package_type -> package_type = fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list (fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#core_type b in (a, b)) b @@ -1361,7 +1361,7 @@ class virtual map = let a = self#list self#pattern a in Ppat_tuple a | Ppat_construct (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#option (fun (a, b) -> @@ -1379,7 +1379,7 @@ class virtual map = let a = self#list (fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#pattern b in (a, b)) a @@ -1398,7 +1398,7 @@ class virtual map = let b = self#core_type b in Ppat_constraint (a, b) | Ppat_type a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in Ppat_type a | Ppat_lazy a -> let a = self#pattern a in @@ -1413,7 +1413,7 @@ class virtual map = let a = self#extension a in Ppat_extension a | Ppat_open (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#pattern b in Ppat_open (a, b) @@ -1429,7 +1429,7 @@ class virtual map = fun x -> match x with | Pexp_ident a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in Pexp_ident a | Pexp_constant a -> let a = self#constant a in @@ -1467,7 +1467,7 @@ class virtual map = let a = self#list self#expression a in Pexp_tuple a | Pexp_construct (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#option self#expression b in Pexp_construct (a, b) | Pexp_variant (a, b) -> @@ -1478,7 +1478,7 @@ class virtual map = let a = self#list (fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#expression b in (a, b)) a @@ -1487,11 +1487,11 @@ class virtual map = Pexp_record (a, b) | Pexp_field (a, b) -> let a = self#expression a in - let b = self#loc self#longident b in + let b = self#longident_loc b in Pexp_field (a, b) | Pexp_setfield (a, b, c) -> let a = self#expression a in - let b = self#loc self#longident b in + let b = self#longident_loc b in let c = self#expression c in Pexp_setfield (a, b, c) | Pexp_array a -> @@ -1531,7 +1531,7 @@ class virtual map = let b = self#loc self#label b in Pexp_send (a, b) | Pexp_new a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in Pexp_new a | Pexp_setinstvar (a, b) -> let a = self#loc self#label a in @@ -1763,7 +1763,7 @@ class virtual map = ptyext_loc; ptyext_attributes; } -> - let ptyext_path = self#loc self#longident ptyext_path in + let ptyext_path = self#longident_loc ptyext_path in let ptyext_params = self#list (fun (a, b) -> @@ -1835,7 +1835,7 @@ class virtual map = fun x -> match x with | Pcty_constr (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in Pcty_constr (a, b) | Pcty_signature a -> @@ -1954,7 +1954,7 @@ class virtual map = fun x -> match x with | Pcl_constr (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in Pcl_constr (a, b) | Pcl_structure a -> @@ -2079,7 +2079,7 @@ class virtual map = fun x -> match x with | Pmty_ident a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in Pmty_ident a | Pmty_signature a -> let a = self#signature a in @@ -2099,7 +2099,7 @@ class virtual map = let a = self#extension a in Pmty_extension a | Pmty_alias a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in Pmty_alias a method functor_parameter : functor_parameter -> functor_parameter = @@ -2184,7 +2184,7 @@ class virtual map = method module_substitution : module_substitution -> module_substitution = fun { pms_name; pms_manifest; pms_attributes; pms_loc } -> let pms_name = self#loc self#string pms_name in - let pms_manifest = self#loc self#longident pms_manifest in + let pms_manifest = self#longident_loc pms_manifest in let pms_attributes = self#attributes pms_attributes in let pms_loc = self#location pms_loc in { pms_name; pms_manifest; pms_attributes; pms_loc } @@ -2207,7 +2207,7 @@ class virtual map = { popen_expr; popen_override; popen_loc; popen_attributes } method open_description : open_description -> open_description = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : open_declaration -> open_declaration = self#open_infos self#module_expr @@ -2230,28 +2230,28 @@ class virtual map = fun x -> match x with | Pwith_type (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#type_declaration b in Pwith_type (a, b) | Pwith_module (a, b) -> - let a = self#loc self#longident a in - let b = self#loc self#longident b in + let a = self#longident_loc a in + let b = self#longident_loc b in Pwith_module (a, b) | Pwith_modtype (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#module_type b in Pwith_modtype (a, b) | Pwith_modtypesubst (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#module_type b in Pwith_modtypesubst (a, b) | Pwith_typesubst (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#type_declaration b in Pwith_typesubst (a, b) | Pwith_modsubst (a, b) -> - let a = self#loc self#longident a in - let b = self#loc self#longident b in + let a = self#longident_loc a in + let b = self#longident_loc b in Pwith_modsubst (a, b) method module_expr : module_expr -> module_expr = @@ -2265,7 +2265,7 @@ class virtual map = fun x -> match x with | Pmod_ident a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in Pmod_ident a | Pmod_structure a -> let a = self#structure a in @@ -2544,13 +2544,13 @@ class virtual iter = self#core_type c | Ptyp_tuple a -> self#list self#core_type a | Ptyp_constr (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#list self#core_type b | Ptyp_object (a, b) -> self#list self#object_field a; self#closed_flag b | Ptyp_class (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#list self#core_type b | Ptyp_alias (a, b) -> self#core_type a; @@ -2564,16 +2564,16 @@ class virtual iter = self#core_type b | Ptyp_package a -> self#package_type a | Ptyp_open (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#core_type b | Ptyp_extension a -> self#extension a method package_type : package_type -> unit = fun (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#list (fun (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#core_type b) b @@ -2627,7 +2627,7 @@ class virtual iter = self#constant b | Ppat_tuple a -> self#list self#pattern a | Ppat_construct (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#option (fun (a, b) -> self#list (self#loc self#string) a; @@ -2639,7 +2639,7 @@ class virtual iter = | Ppat_record (a, b) -> self#list (fun (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#pattern b) a; self#closed_flag b @@ -2650,13 +2650,13 @@ class virtual iter = | Ppat_constraint (a, b) -> self#pattern a; self#core_type b - | Ppat_type a -> self#loc self#longident a + | Ppat_type a -> self#longident_loc a | Ppat_lazy a -> self#pattern a | Ppat_unpack a -> self#loc (self#option self#string) a | Ppat_exception a -> self#pattern a | Ppat_extension a -> self#extension a | Ppat_open (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#pattern b method expression : expression -> unit = @@ -2669,7 +2669,7 @@ class virtual iter = method expression_desc : expression_desc -> unit = fun x -> match x with - | Pexp_ident a -> self#loc self#longident a + | Pexp_ident a -> self#longident_loc a | Pexp_constant a -> self#constant a | Pexp_let (a, b, c) -> self#rec_flag a; @@ -2694,7 +2694,7 @@ class virtual iter = self#cases b | Pexp_tuple a -> self#list self#expression a | Pexp_construct (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#option self#expression b | Pexp_variant (a, b) -> self#label a; @@ -2702,16 +2702,16 @@ class virtual iter = | Pexp_record (a, b) -> self#list (fun (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#expression b) a; self#option self#expression b | Pexp_field (a, b) -> self#expression a; - self#loc self#longident b + self#longident_loc b | Pexp_setfield (a, b, c) -> self#expression a; - self#loc self#longident b; + self#longident_loc b; self#expression c | Pexp_array a -> self#list self#expression a | Pexp_ifthenelse (a, b, c) -> @@ -2740,7 +2740,7 @@ class virtual iter = | Pexp_send (a, b) -> self#expression a; self#loc self#label b - | Pexp_new a -> self#loc self#longident a + | Pexp_new a -> self#longident_loc a | Pexp_setinstvar (a, b) -> self#loc self#label a; self#expression b @@ -2904,7 +2904,7 @@ class virtual iter = ptyext_loc; ptyext_attributes; } -> - self#loc self#longident ptyext_path; + self#longident_loc ptyext_path; self#list (fun (a, b) -> self#core_type a; @@ -2950,7 +2950,7 @@ class virtual iter = fun x -> match x with | Pcty_constr (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#list self#core_type b | Pcty_signature a -> self#class_signature a | Pcty_arrow (a, b, c) -> @@ -3032,7 +3032,7 @@ class virtual iter = fun x -> match x with | Pcl_constr (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#list self#core_type b | Pcl_structure a -> self#class_structure a | Pcl_fun (a, b, c, d) -> @@ -3118,7 +3118,7 @@ class virtual iter = method module_type_desc : module_type_desc -> unit = fun x -> match x with - | Pmty_ident a -> self#loc self#longident a + | Pmty_ident a -> self#longident_loc a | Pmty_signature a -> self#signature a | Pmty_functor (a, b) -> self#functor_parameter a; @@ -3128,7 +3128,7 @@ class virtual iter = self#list self#with_constraint b | Pmty_typeof a -> self#module_expr a | Pmty_extension a -> self#extension a - | Pmty_alias a -> self#loc self#longident a + | Pmty_alias a -> self#longident_loc a method functor_parameter : functor_parameter -> unit = fun x -> @@ -3179,7 +3179,7 @@ class virtual iter = method module_substitution : module_substitution -> unit = fun { pms_name; pms_manifest; pms_attributes; pms_loc } -> self#loc self#string pms_name; - self#loc self#longident pms_manifest; + self#longident_loc pms_manifest; self#attributes pms_attributes; self#location pms_loc @@ -3198,7 +3198,7 @@ class virtual iter = self#attributes popen_attributes method open_description : open_description -> unit = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : open_declaration -> unit = self#open_infos self#module_expr @@ -3219,23 +3219,23 @@ class virtual iter = fun x -> match x with | Pwith_type (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#type_declaration b | Pwith_module (a, b) -> - self#loc self#longident a; - self#loc self#longident b + self#longident_loc a; + self#longident_loc b | Pwith_modtype (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#module_type b | Pwith_modtypesubst (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#module_type b | Pwith_typesubst (a, b) -> - self#loc self#longident a; + self#longident_loc a; self#type_declaration b | Pwith_modsubst (a, b) -> - self#loc self#longident a; - self#loc self#longident b + self#longident_loc a; + self#longident_loc b method module_expr : module_expr -> unit = fun { pmod_desc; pmod_loc; pmod_attributes } -> @@ -3246,7 +3246,7 @@ class virtual iter = method module_expr_desc : module_expr_desc -> unit = fun x -> match x with - | Pmod_ident a -> self#loc self#longident a + | Pmod_ident a -> self#longident_loc a | Pmod_structure a -> self#structure a | Pmod_functor (a, b) -> self#functor_parameter a; @@ -3485,7 +3485,7 @@ class virtual ['acc] fold = acc | Ptyp_tuple a -> self#list self#core_type a acc | Ptyp_constr (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#list self#core_type b acc in acc | Ptyp_object (a, b) -> @@ -3493,7 +3493,7 @@ class virtual ['acc] fold = let acc = self#closed_flag b acc in acc | Ptyp_class (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#list self#core_type b acc in acc | Ptyp_alias (a, b) -> @@ -3511,18 +3511,18 @@ class virtual ['acc] fold = acc | Ptyp_package a -> self#package_type a acc | Ptyp_open (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#core_type b acc in acc | Ptyp_extension a -> self#extension a acc method package_type : package_type -> 'acc -> 'acc = fun (a, b) acc -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#list (fun (a, b) acc -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#core_type b acc in acc) b acc @@ -3586,7 +3586,7 @@ class virtual ['acc] fold = acc | Ppat_tuple a -> self#list self#pattern a acc | Ppat_construct (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#option (fun (a, b) acc -> @@ -3604,7 +3604,7 @@ class virtual ['acc] fold = let acc = self#list (fun (a, b) acc -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#pattern b acc in acc) a acc @@ -3620,13 +3620,13 @@ class virtual ['acc] fold = let acc = self#pattern a acc in let acc = self#core_type b acc in acc - | Ppat_type a -> self#loc self#longident a acc + | Ppat_type a -> self#longident_loc a acc | Ppat_lazy a -> self#pattern a acc | Ppat_unpack a -> self#loc (self#option self#string) a acc | Ppat_exception a -> self#pattern a acc | Ppat_extension a -> self#extension a acc | Ppat_open (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#pattern b acc in acc @@ -3641,7 +3641,7 @@ class virtual ['acc] fold = method expression_desc : expression_desc -> 'acc -> 'acc = fun x acc -> match x with - | Pexp_ident a -> self#loc self#longident a acc + | Pexp_ident a -> self#longident_loc a acc | Pexp_constant a -> self#constant a acc | Pexp_let (a, b, c) -> let acc = self#rec_flag a acc in @@ -3674,7 +3674,7 @@ class virtual ['acc] fold = acc | Pexp_tuple a -> self#list self#expression a acc | Pexp_construct (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#option self#expression b acc in acc | Pexp_variant (a, b) -> @@ -3685,7 +3685,7 @@ class virtual ['acc] fold = let acc = self#list (fun (a, b) acc -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#expression b acc in acc) a acc @@ -3694,11 +3694,11 @@ class virtual ['acc] fold = acc | Pexp_field (a, b) -> let acc = self#expression a acc in - let acc = self#loc self#longident b acc in + let acc = self#longident_loc b acc in acc | Pexp_setfield (a, b, c) -> let acc = self#expression a acc in - let acc = self#loc self#longident b acc in + let acc = self#longident_loc b acc in let acc = self#expression c acc in acc | Pexp_array a -> self#list self#expression a acc @@ -3735,7 +3735,7 @@ class virtual ['acc] fold = let acc = self#expression a acc in let acc = self#loc self#label b acc in acc - | Pexp_new a -> self#loc self#longident a acc + | Pexp_new a -> self#longident_loc a acc | Pexp_setinstvar (a, b) -> let acc = self#loc self#label a acc in let acc = self#expression b acc in @@ -3927,7 +3927,7 @@ class virtual ['acc] fold = ptyext_loc; ptyext_attributes; } acc -> - let acc = self#loc self#longident ptyext_path acc in + let acc = self#longident_loc ptyext_path acc in let acc = self#list (fun (a, b) acc -> @@ -3987,7 +3987,7 @@ class virtual ['acc] fold = fun x acc -> match x with | Pcty_constr (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#list self#core_type b acc in acc | Pcty_signature a -> self#class_signature a acc @@ -4087,7 +4087,7 @@ class virtual ['acc] fold = fun x acc -> match x with | Pcl_constr (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#list self#core_type b acc in acc | Pcl_structure a -> self#class_structure a acc @@ -4190,7 +4190,7 @@ class virtual ['acc] fold = method module_type_desc : module_type_desc -> 'acc -> 'acc = fun x acc -> match x with - | Pmty_ident a -> self#loc self#longident a acc + | Pmty_ident a -> self#longident_loc a acc | Pmty_signature a -> self#signature a acc | Pmty_functor (a, b) -> let acc = self#functor_parameter a acc in @@ -4202,7 +4202,7 @@ class virtual ['acc] fold = acc | Pmty_typeof a -> self#module_expr a acc | Pmty_extension a -> self#extension a acc - | Pmty_alias a -> self#loc self#longident a acc + | Pmty_alias a -> self#longident_loc a acc method functor_parameter : functor_parameter -> 'acc -> 'acc = fun x acc -> @@ -4258,7 +4258,7 @@ class virtual ['acc] fold = method module_substitution : module_substitution -> 'acc -> 'acc = fun { pms_name; pms_manifest; pms_attributes; pms_loc } acc -> let acc = self#loc self#string pms_name acc in - let acc = self#loc self#longident pms_manifest acc in + let acc = self#longident_loc pms_manifest acc in let acc = self#attributes pms_attributes acc in let acc = self#location pms_loc acc in acc @@ -4281,7 +4281,7 @@ class virtual ['acc] fold = acc method open_description : open_description -> 'acc -> 'acc = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : open_declaration -> 'acc -> 'acc = self#open_infos self#module_expr @@ -4304,28 +4304,28 @@ class virtual ['acc] fold = fun x acc -> match x with | Pwith_type (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#type_declaration b acc in acc | Pwith_module (a, b) -> - let acc = self#loc self#longident a acc in - let acc = self#loc self#longident b acc in + let acc = self#longident_loc a acc in + let acc = self#longident_loc b acc in acc | Pwith_modtype (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#module_type b acc in acc | Pwith_modtypesubst (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#module_type b acc in acc | Pwith_typesubst (a, b) -> - let acc = self#loc self#longident a acc in + let acc = self#longident_loc a acc in let acc = self#type_declaration b acc in acc | Pwith_modsubst (a, b) -> - let acc = self#loc self#longident a acc in - let acc = self#loc self#longident b acc in + let acc = self#longident_loc a acc in + let acc = self#longident_loc b acc in acc method module_expr : module_expr -> 'acc -> 'acc = @@ -4338,7 +4338,7 @@ class virtual ['acc] fold = method module_expr_desc : module_expr_desc -> 'acc -> 'acc = fun x acc -> match x with - | Pmod_ident a -> self#loc self#longident a acc + | Pmod_ident a -> self#longident_loc a acc | Pmod_structure a -> self#structure a acc | Pmod_functor (a, b) -> let acc = self#functor_parameter a acc in @@ -4631,7 +4631,7 @@ class virtual ['acc] fold_map = let a, acc = self#list self#core_type a acc in (Ptyp_tuple a, acc) | Ptyp_constr (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#list self#core_type b acc in (Ptyp_constr (a, b), acc) | Ptyp_object (a, b) -> @@ -4639,7 +4639,7 @@ class virtual ['acc] fold_map = let b, acc = self#closed_flag b acc in (Ptyp_object (a, b), acc) | Ptyp_class (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#list self#core_type b acc in (Ptyp_class (a, b), acc) | Ptyp_alias (a, b) -> @@ -4659,7 +4659,7 @@ class virtual ['acc] fold_map = let a, acc = self#package_type a acc in (Ptyp_package a, acc) | Ptyp_open (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#core_type b acc in (Ptyp_open (a, b), acc) | Ptyp_extension a -> @@ -4668,11 +4668,11 @@ class virtual ['acc] fold_map = method package_type : package_type -> 'acc -> package_type * 'acc = fun (a, b) acc -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#list (fun (a, b) acc -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#core_type b acc in ((a, b), acc)) b acc @@ -4747,7 +4747,7 @@ class virtual ['acc] fold_map = let a, acc = self#list self#pattern a acc in (Ppat_tuple a, acc) | Ppat_construct (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#option (fun (a, b) acc -> @@ -4765,7 +4765,7 @@ class virtual ['acc] fold_map = let a, acc = self#list (fun (a, b) acc -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#pattern b acc in ((a, b), acc)) a acc @@ -4784,7 +4784,7 @@ class virtual ['acc] fold_map = let b, acc = self#core_type b acc in (Ppat_constraint (a, b), acc) | Ppat_type a -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in (Ppat_type a, acc) | Ppat_lazy a -> let a, acc = self#pattern a acc in @@ -4799,7 +4799,7 @@ class virtual ['acc] fold_map = let a, acc = self#extension a acc in (Ppat_extension a, acc) | Ppat_open (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#pattern b acc in (Ppat_open (a, b), acc) @@ -4815,7 +4815,7 @@ class virtual ['acc] fold_map = fun x acc -> match x with | Pexp_ident a -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in (Pexp_ident a, acc) | Pexp_constant a -> let a, acc = self#constant a acc in @@ -4853,7 +4853,7 @@ class virtual ['acc] fold_map = let a, acc = self#list self#expression a acc in (Pexp_tuple a, acc) | Pexp_construct (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#option self#expression b acc in (Pexp_construct (a, b), acc) | Pexp_variant (a, b) -> @@ -4864,7 +4864,7 @@ class virtual ['acc] fold_map = let a, acc = self#list (fun (a, b) acc -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#expression b acc in ((a, b), acc)) a acc @@ -4873,11 +4873,11 @@ class virtual ['acc] fold_map = (Pexp_record (a, b), acc) | Pexp_field (a, b) -> let a, acc = self#expression a acc in - let b, acc = self#loc self#longident b acc in + let b, acc = self#longident_loc b acc in (Pexp_field (a, b), acc) | Pexp_setfield (a, b, c) -> let a, acc = self#expression a acc in - let b, acc = self#loc self#longident b acc in + let b, acc = self#longident_loc b acc in let c, acc = self#expression c acc in (Pexp_setfield (a, b, c), acc) | Pexp_array a -> @@ -4917,7 +4917,7 @@ class virtual ['acc] fold_map = let b, acc = self#loc self#label b acc in (Pexp_send (a, b), acc) | Pexp_new a -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in (Pexp_new a, acc) | Pexp_setinstvar (a, b) -> let a, acc = self#loc self#label a acc in @@ -5157,7 +5157,7 @@ class virtual ['acc] fold_map = ptyext_loc; ptyext_attributes; } acc -> - let ptyext_path, acc = self#loc self#longident ptyext_path acc in + let ptyext_path, acc = self#longident_loc ptyext_path acc in let ptyext_params, acc = self#list (fun (a, b) acc -> @@ -5231,7 +5231,7 @@ class virtual ['acc] fold_map = fun x acc -> match x with | Pcty_constr (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#list self#core_type b acc in (Pcty_constr (a, b), acc) | Pcty_signature a -> @@ -5361,7 +5361,7 @@ class virtual ['acc] fold_map = fun x acc -> match x with | Pcl_constr (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#list self#core_type b acc in (Pcl_constr (a, b), acc) | Pcl_structure a -> @@ -5490,7 +5490,7 @@ class virtual ['acc] fold_map = fun x acc -> match x with | Pmty_ident a -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in (Pmty_ident a, acc) | Pmty_signature a -> let a, acc = self#signature a acc in @@ -5510,7 +5510,7 @@ class virtual ['acc] fold_map = let a, acc = self#extension a acc in (Pmty_extension a, acc) | Pmty_alias a -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in (Pmty_alias a, acc) method functor_parameter : @@ -5600,7 +5600,7 @@ class virtual ['acc] fold_map = module_substitution -> 'acc -> module_substitution * 'acc = fun { pms_name; pms_manifest; pms_attributes; pms_loc } acc -> let pms_name, acc = self#loc self#string pms_name acc in - let pms_manifest, acc = self#loc self#longident pms_manifest acc in + let pms_manifest, acc = self#longident_loc pms_manifest acc in let pms_attributes, acc = self#attributes pms_attributes acc in let pms_loc, acc = self#location pms_loc acc in ({ pms_name; pms_manifest; pms_attributes; pms_loc }, acc) @@ -5629,7 +5629,7 @@ class virtual ['acc] fold_map = method open_description : open_description -> 'acc -> open_description * 'acc = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : open_declaration -> 'acc -> open_declaration * 'acc = @@ -5659,28 +5659,28 @@ class virtual ['acc] fold_map = fun x acc -> match x with | Pwith_type (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#type_declaration b acc in (Pwith_type (a, b), acc) | Pwith_module (a, b) -> - let a, acc = self#loc self#longident a acc in - let b, acc = self#loc self#longident b acc in + let a, acc = self#longident_loc a acc in + let b, acc = self#longident_loc b acc in (Pwith_module (a, b), acc) | Pwith_modtype (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#module_type b acc in (Pwith_modtype (a, b), acc) | Pwith_modtypesubst (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#module_type b acc in (Pwith_modtypesubst (a, b), acc) | Pwith_typesubst (a, b) -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in let b, acc = self#type_declaration b acc in (Pwith_typesubst (a, b), acc) | Pwith_modsubst (a, b) -> - let a, acc = self#loc self#longident a acc in - let b, acc = self#loc self#longident b acc in + let a, acc = self#longident_loc a acc in + let b, acc = self#longident_loc b acc in (Pwith_modsubst (a, b), acc) method module_expr : module_expr -> 'acc -> module_expr * 'acc = @@ -5695,7 +5695,7 @@ class virtual ['acc] fold_map = fun x acc -> match x with | Pmod_ident a -> - let a, acc = self#loc self#longident a acc in + let a, acc = self#longident_loc a acc in (Pmod_ident a, acc) | Pmod_structure a -> let a, acc = self#structure a acc in @@ -6025,7 +6025,7 @@ class virtual ['ctx] map_with_context = let a = self#list self#core_type ctx a in Ptyp_tuple a | Ptyp_constr (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in Ptyp_constr (a, b) | Ptyp_object (a, b) -> @@ -6033,7 +6033,7 @@ class virtual ['ctx] map_with_context = let b = self#closed_flag ctx b in Ptyp_object (a, b) | Ptyp_class (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in Ptyp_class (a, b) | Ptyp_alias (a, b) -> @@ -6053,7 +6053,7 @@ class virtual ['ctx] map_with_context = let a = self#package_type ctx a in Ptyp_package a | Ptyp_open (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#core_type ctx b in Ptyp_open (a, b) | Ptyp_extension a -> @@ -6062,11 +6062,11 @@ class virtual ['ctx] map_with_context = method package_type : 'ctx -> package_type -> package_type = fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list (fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#core_type ctx b in (a, b)) ctx b @@ -6140,7 +6140,7 @@ class virtual ['ctx] map_with_context = let a = self#list self#pattern ctx a in Ppat_tuple a | Ppat_construct (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#option (fun ctx (a, b) -> @@ -6158,7 +6158,7 @@ class virtual ['ctx] map_with_context = let a = self#list (fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#pattern ctx b in (a, b)) ctx a @@ -6177,7 +6177,7 @@ class virtual ['ctx] map_with_context = let b = self#core_type ctx b in Ppat_constraint (a, b) | Ppat_type a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in Ppat_type a | Ppat_lazy a -> let a = self#pattern ctx a in @@ -6192,7 +6192,7 @@ class virtual ['ctx] map_with_context = let a = self#extension ctx a in Ppat_extension a | Ppat_open (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#pattern ctx b in Ppat_open (a, b) @@ -6208,7 +6208,7 @@ class virtual ['ctx] map_with_context = fun ctx x -> match x with | Pexp_ident a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in Pexp_ident a | Pexp_constant a -> let a = self#constant ctx a in @@ -6246,7 +6246,7 @@ class virtual ['ctx] map_with_context = let a = self#list self#expression ctx a in Pexp_tuple a | Pexp_construct (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#option self#expression ctx b in Pexp_construct (a, b) | Pexp_variant (a, b) -> @@ -6257,7 +6257,7 @@ class virtual ['ctx] map_with_context = let a = self#list (fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#expression ctx b in (a, b)) ctx a @@ -6266,11 +6266,11 @@ class virtual ['ctx] map_with_context = Pexp_record (a, b) | Pexp_field (a, b) -> let a = self#expression ctx a in - let b = self#loc self#longident ctx b in + let b = self#longident_loc ctx b in Pexp_field (a, b) | Pexp_setfield (a, b, c) -> let a = self#expression ctx a in - let b = self#loc self#longident ctx b in + let b = self#longident_loc ctx b in let c = self#expression ctx c in Pexp_setfield (a, b, c) | Pexp_array a -> @@ -6310,7 +6310,7 @@ class virtual ['ctx] map_with_context = let b = self#loc self#label ctx b in Pexp_send (a, b) | Pexp_new a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in Pexp_new a | Pexp_setinstvar (a, b) -> let a = self#loc self#label ctx a in @@ -6546,7 +6546,7 @@ class virtual ['ctx] map_with_context = ptyext_loc; ptyext_attributes; } -> - let ptyext_path = self#loc self#longident ctx ptyext_path in + let ptyext_path = self#longident_loc ctx ptyext_path in let ptyext_params = self#list (fun ctx (a, b) -> @@ -6618,7 +6618,7 @@ class virtual ['ctx] map_with_context = fun ctx x -> match x with | Pcty_constr (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in Pcty_constr (a, b) | Pcty_signature a -> @@ -6738,7 +6738,7 @@ class virtual ['ctx] map_with_context = fun ctx x -> match x with | Pcl_constr (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in Pcl_constr (a, b) | Pcl_structure a -> @@ -6863,7 +6863,7 @@ class virtual ['ctx] map_with_context = fun ctx x -> match x with | Pmty_ident a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in Pmty_ident a | Pmty_signature a -> let a = self#signature ctx a in @@ -6883,7 +6883,7 @@ class virtual ['ctx] map_with_context = let a = self#extension ctx a in Pmty_extension a | Pmty_alias a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in Pmty_alias a method functor_parameter : 'ctx -> functor_parameter -> functor_parameter = @@ -6972,7 +6972,7 @@ class virtual ['ctx] map_with_context = 'ctx -> module_substitution -> module_substitution = fun ctx { pms_name; pms_manifest; pms_attributes; pms_loc } -> let pms_name = self#loc self#string ctx pms_name in - let pms_manifest = self#loc self#longident ctx pms_manifest in + let pms_manifest = self#longident_loc ctx pms_manifest in let pms_attributes = self#attributes ctx pms_attributes in let pms_loc = self#location ctx pms_loc in { pms_name; pms_manifest; pms_attributes; pms_loc } @@ -6996,7 +6996,7 @@ class virtual ['ctx] map_with_context = { popen_expr; popen_override; popen_loc; popen_attributes } method open_description : 'ctx -> open_description -> open_description = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : 'ctx -> open_declaration -> open_declaration = self#open_infos self#module_expr @@ -7021,28 +7021,28 @@ class virtual ['ctx] map_with_context = fun ctx x -> match x with | Pwith_type (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#type_declaration ctx b in Pwith_type (a, b) | Pwith_module (a, b) -> - let a = self#loc self#longident ctx a in - let b = self#loc self#longident ctx b in + let a = self#longident_loc ctx a in + let b = self#longident_loc ctx b in Pwith_module (a, b) | Pwith_modtype (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#module_type ctx b in Pwith_modtype (a, b) | Pwith_modtypesubst (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#module_type ctx b in Pwith_modtypesubst (a, b) | Pwith_typesubst (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#type_declaration ctx b in Pwith_typesubst (a, b) | Pwith_modsubst (a, b) -> - let a = self#loc self#longident ctx a in - let b = self#loc self#longident ctx b in + let a = self#longident_loc ctx a in + let b = self#longident_loc ctx b in Pwith_modsubst (a, b) method module_expr : 'ctx -> module_expr -> module_expr = @@ -7056,7 +7056,7 @@ class virtual ['ctx] map_with_context = fun ctx x -> match x with | Pmod_ident a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in Pmod_ident a | Pmod_structure a -> let a = self#structure ctx a in @@ -7443,7 +7443,7 @@ class virtual ['res] lift = let a = self#list self#core_type a in self#constr "Ptyp_tuple" [ a ] | Ptyp_constr (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in self#constr "Ptyp_constr" [ a; b ] | Ptyp_object (a, b) -> @@ -7451,7 +7451,7 @@ class virtual ['res] lift = let b = self#closed_flag b in self#constr "Ptyp_object" [ a; b ] | Ptyp_class (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in self#constr "Ptyp_class" [ a; b ] | Ptyp_alias (a, b) -> @@ -7471,7 +7471,7 @@ class virtual ['res] lift = let a = self#package_type a in self#constr "Ptyp_package" [ a ] | Ptyp_open (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#core_type b in self#constr "Ptyp_open" [ a; b ] | Ptyp_extension a -> @@ -7480,11 +7480,11 @@ class virtual ['res] lift = method package_type : package_type -> 'res = fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list (fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#core_type b in self#tuple [ a; b ]) b @@ -7574,7 +7574,7 @@ class virtual ['res] lift = let a = self#list self#pattern a in self#constr "Ppat_tuple" [ a ] | Ppat_construct (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#option (fun (a, b) -> @@ -7592,7 +7592,7 @@ class virtual ['res] lift = let a = self#list (fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#pattern b in self#tuple [ a; b ]) a @@ -7611,7 +7611,7 @@ class virtual ['res] lift = let b = self#core_type b in self#constr "Ppat_constraint" [ a; b ] | Ppat_type a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in self#constr "Ppat_type" [ a ] | Ppat_lazy a -> let a = self#pattern a in @@ -7626,7 +7626,7 @@ class virtual ['res] lift = let a = self#extension a in self#constr "Ppat_extension" [ a ] | Ppat_open (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#pattern b in self#constr "Ppat_open" [ a; b ] @@ -7648,7 +7648,7 @@ class virtual ['res] lift = fun x -> match x with | Pexp_ident a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in self#constr "Pexp_ident" [ a ] | Pexp_constant a -> let a = self#constant a in @@ -7686,7 +7686,7 @@ class virtual ['res] lift = let a = self#list self#expression a in self#constr "Pexp_tuple" [ a ] | Pexp_construct (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#option self#expression b in self#constr "Pexp_construct" [ a; b ] | Pexp_variant (a, b) -> @@ -7697,7 +7697,7 @@ class virtual ['res] lift = let a = self#list (fun (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#expression b in self#tuple [ a; b ]) a @@ -7706,11 +7706,11 @@ class virtual ['res] lift = self#constr "Pexp_record" [ a; b ] | Pexp_field (a, b) -> let a = self#expression a in - let b = self#loc self#longident b in + let b = self#longident_loc b in self#constr "Pexp_field" [ a; b ] | Pexp_setfield (a, b, c) -> let a = self#expression a in - let b = self#loc self#longident b in + let b = self#longident_loc b in let c = self#expression c in self#constr "Pexp_setfield" [ a; b; c ] | Pexp_array a -> @@ -7750,7 +7750,7 @@ class virtual ['res] lift = let b = self#loc self#label b in self#constr "Pexp_send" [ a; b ] | Pexp_new a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in self#constr "Pexp_new" [ a ] | Pexp_setinstvar (a, b) -> let a = self#loc self#label a in @@ -8010,7 +8010,7 @@ class virtual ['res] lift = ptyext_loc; ptyext_attributes; } -> - let ptyext_path = self#loc self#longident ptyext_path in + let ptyext_path = self#longident_loc ptyext_path in let ptyext_params = self#list (fun (a, b) -> @@ -8097,7 +8097,7 @@ class virtual ['res] lift = fun x -> match x with | Pcty_constr (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in self#constr "Pcty_constr" [ a; b ] | Pcty_signature a -> @@ -8233,7 +8233,7 @@ class virtual ['res] lift = fun x -> match x with | Pcl_constr (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#list self#core_type b in self#constr "Pcl_constr" [ a; b ] | Pcl_structure a -> @@ -8369,7 +8369,7 @@ class virtual ['res] lift = fun x -> match x with | Pmty_ident a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in self#constr "Pmty_ident" [ a ] | Pmty_signature a -> let a = self#signature a in @@ -8389,7 +8389,7 @@ class virtual ['res] lift = let a = self#extension a in self#constr "Pmty_extension" [ a ] | Pmty_alias a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in self#constr "Pmty_alias" [ a ] method functor_parameter : functor_parameter -> 'res = @@ -8480,7 +8480,7 @@ class virtual ['res] lift = method module_substitution : module_substitution -> 'res = fun { pms_name; pms_manifest; pms_attributes; pms_loc } -> let pms_name = self#loc self#string pms_name in - let pms_manifest = self#loc self#longident pms_manifest in + let pms_manifest = self#longident_loc pms_manifest in let pms_attributes = self#attributes pms_attributes in let pms_loc = self#location pms_loc in self#record @@ -8520,7 +8520,7 @@ class virtual ['res] lift = ] method open_description : open_description -> 'res = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : open_declaration -> 'res = self#open_infos self#module_expr @@ -8547,28 +8547,28 @@ class virtual ['res] lift = fun x -> match x with | Pwith_type (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#type_declaration b in self#constr "Pwith_type" [ a; b ] | Pwith_module (a, b) -> - let a = self#loc self#longident a in - let b = self#loc self#longident b in + let a = self#longident_loc a in + let b = self#longident_loc b in self#constr "Pwith_module" [ a; b ] | Pwith_modtype (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#module_type b in self#constr "Pwith_modtype" [ a; b ] | Pwith_modtypesubst (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#module_type b in self#constr "Pwith_modtypesubst" [ a; b ] | Pwith_typesubst (a, b) -> - let a = self#loc self#longident a in + let a = self#longident_loc a in let b = self#type_declaration b in self#constr "Pwith_typesubst" [ a; b ] | Pwith_modsubst (a, b) -> - let a = self#loc self#longident a in - let b = self#loc self#longident b in + let a = self#longident_loc a in + let b = self#longident_loc b in self#constr "Pwith_modsubst" [ a; b ] method module_expr : module_expr -> 'res = @@ -8587,7 +8587,7 @@ class virtual ['res] lift = fun x -> match x with | Pmod_ident a -> - let a = self#loc self#longident a in + let a = self#longident_loc a in self#constr "Pmod_ident" [ a ] | Pmod_structure a -> let a = self#structure a in @@ -9014,7 +9014,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Ptyp_tuple (Stdlib.fst a), self#constr ctx "Ptyp_tuple" [ Stdlib.snd a ] ) | Ptyp_constr (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in ( Ptyp_constr (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Ptyp_constr" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -9024,7 +9024,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Ptyp_object (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Ptyp_object" [ Stdlib.snd a; Stdlib.snd b ] ) | Ptyp_class (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in ( Ptyp_class (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Ptyp_class" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -9050,7 +9050,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Ptyp_package (Stdlib.fst a), self#constr ctx "Ptyp_package" [ Stdlib.snd a ] ) | Ptyp_open (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#core_type ctx b in ( Ptyp_open (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Ptyp_open" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -9061,11 +9061,11 @@ class virtual ['ctx, 'res] lift_map_with_context = method package_type : 'ctx -> package_type -> package_type * 'res = fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list (fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#core_type ctx b in ( (Stdlib.fst a, Stdlib.fst b), self#tuple ctx [ Stdlib.snd a; Stdlib.snd b ] )) @@ -9184,7 +9184,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Ppat_tuple (Stdlib.fst a), self#constr ctx "Ppat_tuple" [ Stdlib.snd a ] ) | Ppat_construct (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#option (fun ctx (a, b) -> @@ -9205,7 +9205,7 @@ class virtual ['ctx, 'res] lift_map_with_context = let a = self#list (fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#pattern ctx b in ( (Stdlib.fst a, Stdlib.fst b), self#tuple ctx [ Stdlib.snd a; Stdlib.snd b ] )) @@ -9230,7 +9230,7 @@ class virtual ['ctx, 'res] lift_map_with_context = self#constr ctx "Ppat_constraint" [ Stdlib.snd a; Stdlib.snd b ] ) | Ppat_type a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in ( Ppat_type (Stdlib.fst a), self#constr ctx "Ppat_type" [ Stdlib.snd a ] ) | Ppat_lazy a -> @@ -9250,7 +9250,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Ppat_extension (Stdlib.fst a), self#constr ctx "Ppat_extension" [ Stdlib.snd a ] ) | Ppat_open (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#pattern ctx b in ( Ppat_open (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Ppat_open" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -9279,7 +9279,7 @@ class virtual ['ctx, 'res] lift_map_with_context = fun ctx x -> match x with | Pexp_ident a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in ( Pexp_ident (Stdlib.fst a), self#constr ctx "Pexp_ident" [ Stdlib.snd a ] ) | Pexp_constant a -> @@ -9328,7 +9328,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Pexp_tuple (Stdlib.fst a), self#constr ctx "Pexp_tuple" [ Stdlib.snd a ] ) | Pexp_construct (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#option self#expression ctx b in ( Pexp_construct (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pexp_construct" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -9341,7 +9341,7 @@ class virtual ['ctx, 'res] lift_map_with_context = let a = self#list (fun ctx (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#expression ctx b in ( (Stdlib.fst a, Stdlib.fst b), self#tuple ctx [ Stdlib.snd a; Stdlib.snd b ] )) @@ -9352,12 +9352,12 @@ class virtual ['ctx, 'res] lift_map_with_context = self#constr ctx "Pexp_record" [ Stdlib.snd a; Stdlib.snd b ] ) | Pexp_field (a, b) -> let a = self#expression ctx a in - let b = self#loc self#longident ctx b in + let b = self#longident_loc ctx b in ( Pexp_field (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pexp_field" [ Stdlib.snd a; Stdlib.snd b ] ) | Pexp_setfield (a, b, c) -> let a = self#expression ctx a in - let b = self#loc self#longident ctx b in + let b = self#longident_loc ctx b in let c = self#expression ctx c in ( Pexp_setfield (Stdlib.fst a, Stdlib.fst b, Stdlib.fst c), self#constr ctx "Pexp_setfield" @@ -9422,7 +9422,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Pexp_send (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pexp_send" [ Stdlib.snd a; Stdlib.snd b ] ) | Pexp_new a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in ( Pexp_new (Stdlib.fst a), self#constr ctx "Pexp_new" [ Stdlib.snd a ] ) | Pexp_setinstvar (a, b) -> @@ -9790,7 +9790,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ptyext_loc; ptyext_attributes; } -> - let ptyext_path = self#loc self#longident ctx ptyext_path in + let ptyext_path = self#longident_loc ctx ptyext_path in let ptyext_params = self#list (fun ctx (a, b) -> @@ -9909,7 +9909,7 @@ class virtual ['ctx, 'res] lift_map_with_context = fun ctx x -> match x with | Pcty_constr (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in ( Pcty_constr (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pcty_constr" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -10100,7 +10100,7 @@ class virtual ['ctx, 'res] lift_map_with_context = fun ctx x -> match x with | Pcl_constr (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#list self#core_type ctx b in ( Pcl_constr (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pcl_constr" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -10280,7 +10280,7 @@ class virtual ['ctx, 'res] lift_map_with_context = fun ctx x -> match x with | Pmty_ident a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in ( Pmty_ident (Stdlib.fst a), self#constr ctx "Pmty_ident" [ Stdlib.snd a ] ) | Pmty_signature a -> @@ -10306,7 +10306,7 @@ class virtual ['ctx, 'res] lift_map_with_context = ( Pmty_extension (Stdlib.fst a), self#constr ctx "Pmty_extension" [ Stdlib.snd a ] ) | Pmty_alias a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in ( Pmty_alias (Stdlib.fst a), self#constr ctx "Pmty_alias" [ Stdlib.snd a ] ) @@ -10431,7 +10431,7 @@ class virtual ['ctx, 'res] lift_map_with_context = 'ctx -> module_substitution -> module_substitution * 'res = fun ctx { pms_name; pms_manifest; pms_attributes; pms_loc } -> let pms_name = self#loc self#string ctx pms_name in - let pms_manifest = self#loc self#longident ctx pms_manifest in + let pms_manifest = self#longident_loc ctx pms_manifest in let pms_attributes = self#attributes ctx pms_attributes in let pms_loc = self#location ctx pms_loc in ( { @@ -10496,7 +10496,7 @@ class virtual ['ctx, 'res] lift_map_with_context = method open_description : 'ctx -> open_description -> open_description * 'res = - self#open_infos (self#loc self#longident) + self#open_infos self#longident_loc method open_declaration : 'ctx -> open_declaration -> open_declaration * 'res = @@ -10536,35 +10536,35 @@ class virtual ['ctx, 'res] lift_map_with_context = fun ctx x -> match x with | Pwith_type (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#type_declaration ctx b in ( Pwith_type (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pwith_type" [ Stdlib.snd a; Stdlib.snd b ] ) | Pwith_module (a, b) -> - let a = self#loc self#longident ctx a in - let b = self#loc self#longident ctx b in + let a = self#longident_loc ctx a in + let b = self#longident_loc ctx b in ( Pwith_module (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pwith_module" [ Stdlib.snd a; Stdlib.snd b ] ) | Pwith_modtype (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#module_type ctx b in ( Pwith_modtype (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pwith_modtype" [ Stdlib.snd a; Stdlib.snd b ] ) | Pwith_modtypesubst (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#module_type ctx b in ( Pwith_modtypesubst (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pwith_modtypesubst" [ Stdlib.snd a; Stdlib.snd b ] ) | Pwith_typesubst (a, b) -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in let b = self#type_declaration ctx b in ( Pwith_typesubst (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pwith_typesubst" [ Stdlib.snd a; Stdlib.snd b ] ) | Pwith_modsubst (a, b) -> - let a = self#loc self#longident ctx a in - let b = self#loc self#longident ctx b in + let a = self#longident_loc ctx a in + let b = self#longident_loc ctx b in ( Pwith_modsubst (Stdlib.fst a, Stdlib.fst b), self#constr ctx "Pwith_modsubst" [ Stdlib.snd a; Stdlib.snd b ] ) @@ -10590,7 +10590,7 @@ class virtual ['ctx, 'res] lift_map_with_context = fun ctx x -> match x with | Pmod_ident a -> - let a = self#loc self#longident ctx a in + let a = self#longident_loc ctx a in ( Pmod_ident (Stdlib.fst a), self#constr ctx "Pmod_ident" [ Stdlib.snd a ] ) | Pmod_structure a ->