sig
  type 'a with_loc = 'a Location.loc
  type loc = Location.t
  type lid = Longident.t Ast_helper.with_loc
  type str = string Ast_helper.with_loc
  type str_opt = string option Ast_helper.with_loc
  type attrs = Parsetree.attribute list
  val default_loc : Ast_helper.loc Stdlib.ref
  val with_default_loc : Ast_helper.loc -> (unit -> 'a) -> 'a
  module Const :
    sig
      val char : char -> Parsetree.constant
      val string :
        ?quotation_delimiter:string ->
        ?loc:Location.t -> string -> Parsetree.constant
      val integer : ?suffix:char -> string -> Parsetree.constant
      val int : ?suffix:char -> int -> Parsetree.constant
      val int32 : ?suffix:char -> int32 -> Parsetree.constant
      val int64 : ?suffix:char -> int64 -> Parsetree.constant
      val nativeint : ?suffix:char -> nativeint -> Parsetree.constant
      val float : ?suffix:char -> string -> Parsetree.constant
    end
  module Attr :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        Ast_helper.str -> Parsetree.payload -> Parsetree.attribute
    end
  module Typ :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.core_type_desc -> Parsetree.core_type
      val attr :
        Parsetree.core_type -> Parsetree.attribute -> Parsetree.core_type
      val any :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> unit -> Parsetree.core_type
      val var :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> string -> Parsetree.core_type
      val arrow :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.arg_label ->
        Parsetree.core_type -> Parsetree.core_type -> Parsetree.core_type
      val tuple :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.core_type list -> Parsetree.core_type
      val constr :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid -> Parsetree.core_type list -> Parsetree.core_type
      val object_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.object_field list ->
        Asttypes.closed_flag -> Parsetree.core_type
      val class_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid -> Parsetree.core_type list -> Parsetree.core_type
      val alias :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.core_type -> string -> Parsetree.core_type
      val variant :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.row_field list ->
        Asttypes.closed_flag ->
        Asttypes.label list option -> Parsetree.core_type
      val poly :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str list -> Parsetree.core_type -> Parsetree.core_type
      val package :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid ->
        (Ast_helper.lid * Parsetree.core_type) list -> Parsetree.core_type
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Parsetree.extension -> Parsetree.core_type
      val force_poly : Parsetree.core_type -> Parsetree.core_type
      val varify_constructors :
        Ast_helper.str list -> Parsetree.core_type -> Parsetree.core_type
    end
  module Pat :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern_desc -> Parsetree.pattern
      val attr :
        Parsetree.pattern -> Parsetree.attribute -> Parsetree.pattern
      val any :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> unit -> Parsetree.pattern
      val var :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.str -> Parsetree.pattern
      val alias :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern -> Ast_helper.str -> Parsetree.pattern
      val constant :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Parsetree.constant -> Parsetree.pattern
      val interval :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.constant -> Parsetree.constant -> Parsetree.pattern
      val tuple :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern list -> Parsetree.pattern
      val construct :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid ->
        (Ast_helper.str list * Parsetree.pattern) option -> Parsetree.pattern
      val variant :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.label -> Parsetree.pattern option -> Parsetree.pattern
      val record :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        (Ast_helper.lid * Parsetree.pattern) list ->
        Asttypes.closed_flag -> Parsetree.pattern
      val array :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern list -> Parsetree.pattern
      val or_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern -> Parsetree.pattern -> Parsetree.pattern
      val constraint_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern -> Parsetree.core_type -> Parsetree.pattern
      val type_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.lid -> Parsetree.pattern
      val lazy_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Parsetree.pattern -> Parsetree.pattern
      val unpack :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.str_opt -> Parsetree.pattern
      val open_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid -> Parsetree.pattern -> Parsetree.pattern
      val exception_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Parsetree.pattern -> Parsetree.pattern
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Parsetree.extension -> Parsetree.pattern
    end
  module Exp :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression_desc -> Parsetree.expression
      val attr :
        Parsetree.expression -> Parsetree.attribute -> Parsetree.expression
      val ident :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.lid -> Parsetree.expression
      val constant :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Parsetree.constant -> Parsetree.expression
      val let_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.rec_flag ->
        Parsetree.value_binding list ->
        Parsetree.expression -> Parsetree.expression
      val fun_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.arg_label ->
        Parsetree.expression option ->
        Parsetree.pattern -> Parsetree.expression -> Parsetree.expression
      val function_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.case list -> Parsetree.expression
      val apply :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression ->
        (Asttypes.arg_label * Parsetree.expression) list ->
        Parsetree.expression
      val match_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.case list -> Parsetree.expression
      val try_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.case list -> Parsetree.expression
      val tuple :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression list -> Parsetree.expression
      val construct :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid -> Parsetree.expression option -> Parsetree.expression
      val variant :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.label -> Parsetree.expression option -> Parsetree.expression
      val record :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        (Ast_helper.lid * Parsetree.expression) list ->
        Parsetree.expression option -> Parsetree.expression
      val field :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Ast_helper.lid -> Parsetree.expression
      val setfield :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression ->
        Ast_helper.lid -> Parsetree.expression -> Parsetree.expression
      val array :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression list -> Parsetree.expression
      val ifthenelse :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression ->
        Parsetree.expression ->
        Parsetree.expression option -> Parsetree.expression
      val sequence :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.expression -> Parsetree.expression
      val while_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.expression -> Parsetree.expression
      val for_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.pattern ->
        Parsetree.expression ->
        Parsetree.expression ->
        Asttypes.direction_flag ->
        Parsetree.expression -> Parsetree.expression
      val coerce :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression ->
        Parsetree.core_type option ->
        Parsetree.core_type -> Parsetree.expression
      val constraint_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.core_type -> Parsetree.expression
      val send :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Ast_helper.str -> Parsetree.expression
      val new_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.lid -> Parsetree.expression
      val setinstvar :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str -> Parsetree.expression -> Parsetree.expression
      val override :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        (Ast_helper.str * Parsetree.expression) list -> Parsetree.expression
      val letmodule :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str_opt ->
        Parsetree.module_expr -> Parsetree.expression -> Parsetree.expression
      val letexception :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension_constructor ->
        Parsetree.expression -> Parsetree.expression
      val assert_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.expression
      val lazy_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.expression
      val poly :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression ->
        Parsetree.core_type option -> Parsetree.expression
      val object_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_structure -> Parsetree.expression
      val newtype :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str -> Parsetree.expression -> Parsetree.expression
      val pack :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_expr -> Parsetree.expression
      val open_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.open_declaration ->
        Parsetree.expression -> Parsetree.expression
      val letop :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.binding_op ->
        Parsetree.binding_op list ->
        Parsetree.expression -> Parsetree.expression
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.expression
      val unreachable :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> unit -> Parsetree.expression
      val case :
        Parsetree.pattern ->
        ?guard:Parsetree.expression -> Parsetree.expression -> Parsetree.case
      val binding_op :
        Ast_helper.str ->
        Parsetree.pattern ->
        Parsetree.expression -> Ast_helper.loc -> Parsetree.binding_op
    end
  module Val :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?prim:string list ->
        Ast_helper.str -> Parsetree.core_type -> Parsetree.value_description
    end
  module Type :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        ?params:(Parsetree.core_type *
                 (Asttypes.variance * Asttypes.injectivity))
                list ->
        ?cstrs:(Parsetree.core_type * Parsetree.core_type * Ast_helper.loc)
               list ->
        ?kind:Parsetree.type_kind ->
        ?priv:Asttypes.private_flag ->
        ?manifest:Parsetree.core_type ->
        Ast_helper.str -> Parsetree.type_declaration
      val constructor :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?info:Docstrings.info ->
        ?vars:Ast_helper.str list ->
        ?args:Parsetree.constructor_arguments ->
        ?res:Parsetree.core_type ->
        Ast_helper.str -> Parsetree.constructor_declaration
      val field :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?info:Docstrings.info ->
        ?mut:Asttypes.mutable_flag ->
        Ast_helper.str -> Parsetree.core_type -> Parsetree.label_declaration
    end
  module Te :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?params:(Parsetree.core_type *
                 (Asttypes.variance * Asttypes.injectivity))
                list ->
        ?priv:Asttypes.private_flag ->
        Ast_helper.lid ->
        Parsetree.extension_constructor list -> Parsetree.type_extension
      val mk_exception :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        Parsetree.extension_constructor -> Parsetree.type_exception
      val constructor :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?info:Docstrings.info ->
        Ast_helper.str ->
        Parsetree.extension_constructor_kind ->
        Parsetree.extension_constructor
      val decl :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?info:Docstrings.info ->
        ?vars:Ast_helper.str list ->
        ?args:Parsetree.constructor_arguments ->
        ?res:Parsetree.core_type ->
        Ast_helper.str -> Parsetree.extension_constructor
      val rebind :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?info:Docstrings.info ->
        Ast_helper.str -> Ast_helper.lid -> Parsetree.extension_constructor
    end
  module Mty :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_type_desc -> Parsetree.module_type
      val attr :
        Parsetree.module_type -> Parsetree.attribute -> Parsetree.module_type
      val ident :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.lid -> Parsetree.module_type
      val alias :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.lid -> Parsetree.module_type
      val signature :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.signature -> Parsetree.module_type
      val functor_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.functor_parameter ->
        Parsetree.module_type -> Parsetree.module_type
      val with_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_type ->
        Parsetree.with_constraint list -> Parsetree.module_type
      val typeof_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_expr -> Parsetree.module_type
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.module_type
    end
  module Mod :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_expr_desc -> Parsetree.module_expr
      val attr :
        Parsetree.module_expr -> Parsetree.attribute -> Parsetree.module_expr
      val ident :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs -> Ast_helper.lid -> Parsetree.module_expr
      val structure :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.structure -> Parsetree.module_expr
      val functor_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.functor_parameter ->
        Parsetree.module_expr -> Parsetree.module_expr
      val apply :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_expr ->
        Parsetree.module_expr -> Parsetree.module_expr
      val constraint_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.module_expr ->
        Parsetree.module_type -> Parsetree.module_expr
      val unpack :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.module_expr
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.module_expr
    end
  module Sig :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        Parsetree.signature_item_desc -> Parsetree.signature_item
      val value :
        ?loc:Ast_helper.loc ->
        Parsetree.value_description -> Parsetree.signature_item
      val type_ :
        ?loc:Ast_helper.loc ->
        Asttypes.rec_flag ->
        Parsetree.type_declaration list -> Parsetree.signature_item
      val type_subst :
        ?loc:Ast_helper.loc ->
        Parsetree.type_declaration list -> Parsetree.signature_item
      val type_extension :
        ?loc:Ast_helper.loc ->
        Parsetree.type_extension -> Parsetree.signature_item
      val exception_ :
        ?loc:Ast_helper.loc ->
        Parsetree.type_exception -> Parsetree.signature_item
      val module_ :
        ?loc:Ast_helper.loc ->
        Parsetree.module_declaration -> Parsetree.signature_item
      val mod_subst :
        ?loc:Ast_helper.loc ->
        Parsetree.module_substitution -> Parsetree.signature_item
      val rec_module :
        ?loc:Ast_helper.loc ->
        Parsetree.module_declaration list -> Parsetree.signature_item
      val modtype :
        ?loc:Ast_helper.loc ->
        Parsetree.module_type_declaration -> Parsetree.signature_item
      val modtype_subst :
        ?loc:Ast_helper.loc ->
        Parsetree.module_type_declaration -> Parsetree.signature_item
      val open_ :
        ?loc:Ast_helper.loc ->
        Parsetree.open_description -> Parsetree.signature_item
      val include_ :
        ?loc:Ast_helper.loc ->
        Parsetree.include_description -> Parsetree.signature_item
      val class_ :
        ?loc:Ast_helper.loc ->
        Parsetree.class_description list -> Parsetree.signature_item
      val class_type :
        ?loc:Ast_helper.loc ->
        Parsetree.class_type_declaration list -> Parsetree.signature_item
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.signature_item
      val attribute :
        ?loc:Ast_helper.loc ->
        Parsetree.attribute -> Parsetree.signature_item
      val text : Docstrings.text -> Parsetree.signature_item list
    end
  module Str :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        Parsetree.structure_item_desc -> Parsetree.structure_item
      val eval :
        ?loc:Ast_helper.loc ->
        ?attrs:Parsetree.attributes ->
        Parsetree.expression -> Parsetree.structure_item
      val value :
        ?loc:Ast_helper.loc ->
        Asttypes.rec_flag ->
        Parsetree.value_binding list -> Parsetree.structure_item
      val primitive :
        ?loc:Ast_helper.loc ->
        Parsetree.value_description -> Parsetree.structure_item
      val type_ :
        ?loc:Ast_helper.loc ->
        Asttypes.rec_flag ->
        Parsetree.type_declaration list -> Parsetree.structure_item
      val type_extension :
        ?loc:Ast_helper.loc ->
        Parsetree.type_extension -> Parsetree.structure_item
      val exception_ :
        ?loc:Ast_helper.loc ->
        Parsetree.type_exception -> Parsetree.structure_item
      val module_ :
        ?loc:Ast_helper.loc ->
        Parsetree.module_binding -> Parsetree.structure_item
      val rec_module :
        ?loc:Ast_helper.loc ->
        Parsetree.module_binding list -> Parsetree.structure_item
      val modtype :
        ?loc:Ast_helper.loc ->
        Parsetree.module_type_declaration -> Parsetree.structure_item
      val open_ :
        ?loc:Ast_helper.loc ->
        Parsetree.open_declaration -> Parsetree.structure_item
      val class_ :
        ?loc:Ast_helper.loc ->
        Parsetree.class_declaration list -> Parsetree.structure_item
      val class_type :
        ?loc:Ast_helper.loc ->
        Parsetree.class_type_declaration list -> Parsetree.structure_item
      val include_ :
        ?loc:Ast_helper.loc ->
        Parsetree.include_declaration -> Parsetree.structure_item
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.structure_item
      val attribute :
        ?loc:Ast_helper.loc ->
        Parsetree.attribute -> Parsetree.structure_item
      val text : Docstrings.text -> Parsetree.structure_item list
    end
  module Md :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        Ast_helper.str_opt ->
        Parsetree.module_type -> Parsetree.module_declaration
    end
  module Ms :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        Ast_helper.str -> Ast_helper.lid -> Parsetree.module_substitution
    end
  module Mtd :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        ?typ:Parsetree.module_type ->
        Ast_helper.str -> Parsetree.module_type_declaration
    end
  module Mb :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        Ast_helper.str_opt ->
        Parsetree.module_expr -> Parsetree.module_binding
    end
  module Opn :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?override:Asttypes.override_flag -> 'a -> 'a Parsetree.open_infos
    end
  module Incl :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs -> 'a -> 'a Parsetree.include_infos
    end
  module Vb :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        Parsetree.pattern -> Parsetree.expression -> Parsetree.value_binding
    end
  module Cty :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_type_desc -> Parsetree.class_type
      val attr :
        Parsetree.class_type -> Parsetree.attribute -> Parsetree.class_type
      val constr :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid -> Parsetree.core_type list -> Parsetree.class_type
      val signature :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_signature -> Parsetree.class_type
      val arrow :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.arg_label ->
        Parsetree.core_type -> Parsetree.class_type -> Parsetree.class_type
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.class_type
      val open_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.open_description ->
        Parsetree.class_type -> Parsetree.class_type
    end
  module Ctf :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        Parsetree.class_type_field_desc -> Parsetree.class_type_field
      val attr :
        Parsetree.class_type_field ->
        Parsetree.attribute -> Parsetree.class_type_field
      val inherit_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_type -> Parsetree.class_type_field
      val val_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str ->
        Asttypes.mutable_flag ->
        Asttypes.virtual_flag ->
        Parsetree.core_type -> Parsetree.class_type_field
      val method_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str ->
        Asttypes.private_flag ->
        Asttypes.virtual_flag ->
        Parsetree.core_type -> Parsetree.class_type_field
      val constraint_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.core_type ->
        Parsetree.core_type -> Parsetree.class_type_field
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.class_type_field
      val attribute :
        ?loc:Ast_helper.loc ->
        Parsetree.attribute -> Parsetree.class_type_field
      val text : Docstrings.text -> Parsetree.class_type_field list
    end
  module Cl :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_expr_desc -> Parsetree.class_expr
      val attr :
        Parsetree.class_expr -> Parsetree.attribute -> Parsetree.class_expr
      val constr :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.lid -> Parsetree.core_type list -> Parsetree.class_expr
      val structure :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_structure -> Parsetree.class_expr
      val fun_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.arg_label ->
        Parsetree.expression option ->
        Parsetree.pattern -> Parsetree.class_expr -> Parsetree.class_expr
      val apply :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_expr ->
        (Asttypes.arg_label * Parsetree.expression) list ->
        Parsetree.class_expr
      val let_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.rec_flag ->
        Parsetree.value_binding list ->
        Parsetree.class_expr -> Parsetree.class_expr
      val constraint_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.class_expr -> Parsetree.class_type -> Parsetree.class_expr
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.class_expr
      val open_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.open_description ->
        Parsetree.class_expr -> Parsetree.class_expr
    end
  module Cf :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        Parsetree.class_field_desc -> Parsetree.class_field
      val attr :
        Parsetree.class_field -> Parsetree.attribute -> Parsetree.class_field
      val inherit_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.override_flag ->
        Parsetree.class_expr ->
        Ast_helper.str option -> Parsetree.class_field
      val val_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str ->
        Asttypes.mutable_flag ->
        Parsetree.class_field_kind -> Parsetree.class_field
      val method_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Ast_helper.str ->
        Asttypes.private_flag ->
        Parsetree.class_field_kind -> Parsetree.class_field
      val constraint_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.core_type -> Parsetree.core_type -> Parsetree.class_field
      val initializer_ :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.expression -> Parsetree.class_field
      val extension :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.extension -> Parsetree.class_field
      val attribute :
        ?loc:Ast_helper.loc -> Parsetree.attribute -> Parsetree.class_field
      val text : Docstrings.text -> Parsetree.class_field list
      val virtual_ : Parsetree.core_type -> Parsetree.class_field_kind
      val concrete :
        Asttypes.override_flag ->
        Parsetree.expression -> Parsetree.class_field_kind
    end
  module Ci :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        ?docs:Docstrings.docs ->
        ?text:Docstrings.text ->
        ?virt:Asttypes.virtual_flag ->
        ?params:(Parsetree.core_type *
                 (Asttypes.variance * Asttypes.injectivity))
                list ->
        Ast_helper.str -> 'a -> 'a Parsetree.class_infos
    end
  module Csig :
    sig
      val mk :
        Parsetree.core_type ->
        Parsetree.class_type_field list -> Parsetree.class_signature
    end
  module Cstr :
    sig
      val mk :
        Parsetree.pattern ->
        Parsetree.class_field list -> Parsetree.class_structure
    end
  module Rf :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.row_field_desc -> Parsetree.row_field
      val tag :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.label Ast_helper.with_loc ->
        bool -> Parsetree.core_type list -> Parsetree.row_field
      val inherit_ :
        ?loc:Ast_helper.loc -> Parsetree.core_type -> Parsetree.row_field
    end
  module Of :
    sig
      val mk :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Parsetree.object_field_desc -> Parsetree.object_field
      val tag :
        ?loc:Ast_helper.loc ->
        ?attrs:Ast_helper.attrs ->
        Asttypes.label Ast_helper.with_loc ->
        Parsetree.core_type -> Parsetree.object_field
      val inherit_ :
        ?loc:Ast_helper.loc -> Parsetree.core_type -> Parsetree.object_field
    end
end