Module Includemod

type mark =
| Mark_both(*

Mark definitions used from both arguments

*)
| Mark_positive(*

Mark definitions used from the positive (first) argument

*)
| Mark_negative(*

Mark definitions used from the negative (second) argument

*)
| Mark_neither(*

Do not mark definitions used from either argument

*)

Type describing which arguments of an inclusion to consider as used for the usage warnings. Mark_both is the default.

val strengthened_module_decl : loc:Location.t -> aliasable:bool -> Env.t -> mark:mark -> Types.module_declaration -> Path.t -> Types.module_declaration -> Typedtree.module_coercion
val check_modtype_inclusion : loc:Location.t -> Env.t -> Types.module_type -> Path.t -> Types.module_type -> unit

check_modtype_inclusion ~loc env mty1 path1 mty2 checks that the functor application F(M) is well typed, where mty2 is the type of the argument of F and path1/mty1 is the path/unstrenghened type of M.

val compunit : Env.t -> mark:mark -> string -> Types.signature -> string -> Types.signature -> Typedtree.module_coercion
val type_declarations : loc:Location.t -> Env.t -> mark:mark -> Ident.t -> Types.type_declaration -> Types.type_declaration -> unit
val print_coercion : Format.formatter -> Typedtree.module_coercion -> unit
type symptom =
| Missing_field of Ident.t * Location.t * string
| Value_descriptions of Ident.t * Types.value_description * Types.value_description
| Type_declarations of Ident.t * Types.type_declaration * Types.type_declaration * Includecore.type_mismatch
| Extension_constructors of Ident.t * Types.extension_constructor * Types.extension_constructor * Includecore.extension_constructor_mismatch
| Module_types of Types.module_type * Types.module_type
| Modtype_infos of Ident.t * Types.modtype_declaration * Types.modtype_declaration
| Modtype_permutation of Types.module_type * Typedtree.module_coercion
| Interface_mismatch of string * string
| Class_type_declarations of Ident.t * Types.class_type_declaration * Types.class_type_declaration * Ctype.class_match_failure list
| Class_declarations of Ident.t * Types.class_declaration * Types.class_declaration * Ctype.class_match_failure list
| Unbound_modtype_path of Path.t
| Unbound_module_path of Path.t
| Invalid_module_alias of Path.t
type pos =
| Module of Ident.t
| Modtype of Ident.t
| Arg of Types.functor_parameter
| Body of Types.functor_parameter
type error = pos list * Env.t * symptom
exception Error of error list
val report_error : Format.formatter -> error list -> unit
val expand_module_alias : Env.t -> pos list -> Path.t -> Types.module_type