diff --git a/src/loader/cmi.ml b/src/loader/cmi.ml index 52a35269e3..db4454f34a 100644 --- a/src/loader/cmi.ml +++ b/src/loader/cmi.ml @@ -215,9 +215,18 @@ let mark_type ty = List.iter (fun t -> add_alias t) tyl; loop visited ty | Tunivar name -> reserve_name name +#if OCAML_VERSION>=(4,13,0) + | Tpackage(_,tyl) -> + List.iter (fun (_,x) -> loop visited x) tyl +#else | Tpackage(_, _, tyl) -> List.iter (loop visited) tyl +#endif +#if OCAML_VERSION<(4,13,0) | Tsubst ty -> loop visited ty +#else + | Tsubst (ty,_) -> loop visited ty +#endif | Tlink _ -> assert false in loop [] ty @@ -240,12 +249,20 @@ let mark_type_parameter param = mark_type param; if aliasable param then use_alias (Btype.proxy param) +#if OCAML_VERSION<(4,13,0) +let tsubst x = Tsubst x +let tvar_none ty = ty.desc <- Tvar None +#else +let tsubst x = Tsubst(x,None) +let tvar_none ty = Types.Private_type_expr.set_desc ty (Tvar None) +#endif + let prepare_type_parameters params manifest = let params = List.fold_left (fun params param -> let param = Btype.repr param in - if List.memq param params then Btype.newgenty (Tsubst param) :: params + if List.memq param params then Btype.newgenty (tsubst param) :: params else param :: params) [] params in @@ -255,7 +272,7 @@ let prepare_type_parameters params manifest = let vars = Ctype.free_variables ty in List.iter (function {desc = Tvar (Some "_"); _} as ty -> - if List.memq ty vars then ty.desc <- Tvar None + if List.memq ty vars then tvar_none ty | _ -> ()) params | None -> () @@ -274,7 +291,11 @@ let mark_constructor_args = let mark_type_kind = function | Type_abstract -> () +#if OCAML_VERSION >= (4,13,0) + | Type_variant (cds,_) -> +#else | Type_variant cds -> +#endif List.iter (fun cd -> mark_constructor_args cd.cd_args; @@ -393,19 +414,28 @@ let rec read_type_expr env typ = remove_names tyl; Poly(vars, typ) | Tunivar _ -> Var (name_of_type typ) +#if OCAML_VERSION>=(4,13,0) + | Tpackage(p,eqs) -> +#else | Tpackage(p, frags, tyl) -> + let eqs = List.combine frags tyl in +#endif let open TypeExpr.Package in let path = Env.Path.read_module_type env p in let substitutions = - List.map2 - (fun frag typ -> + List.map + (fun (frag,typ) -> let frag = Env.Fragment.read_type frag in let typ = read_type_expr env typ in (frag, typ)) - frags tyl + eqs in - Package {path; substitutions} + Package {path; substitutions} +#if OCAML_VERSION<(4,13,0) | Tsubst typ -> read_type_expr env typ +#else + | Tsubst (typ,_) -> read_type_expr env typ +#endif | Tlink _ -> assert false in match alias with @@ -572,7 +602,11 @@ let read_constructor_declaration env parent cd = let read_type_kind env parent = let open TypeDecl.Representation in function | Type_abstract -> None - | Type_variant cstrs -> +#if OCAML_VERSION >= (4,13,0) + | Type_variant (cstrs,_) -> +#else + | Type_variant cstrs -> +#endif let cstrs = List.map (read_constructor_declaration env parent) cstrs in @@ -634,7 +668,11 @@ let read_type_declaration env parent id decl = decl.type_manifest = None || decl.type_private = Private | Type_record _ -> decl.type_private = Private - | Type_variant tll -> +#if OCAML_VERSION >= (4,13,0) + | Type_variant (tll,_) -> +#else + | Type_variant tll -> +#endif decl.type_private = Private || List.exists (fun cd -> cd.cd_res <> None) tll | Type_open -> diff --git a/src/loader/cmt.ml b/src/loader/cmt.ml index d331ddaebe..dede18b460 100644 --- a/src/loader/cmt.ml +++ b/src/loader/cmt.ml @@ -62,7 +62,11 @@ let rec read_pattern env parent doc pat = | Tpat_constant _ -> [] | Tpat_tuple pats -> List.concat (List.map (read_pattern env parent doc) pats) +#if OCAML_VERSION < (4, 13, 0) | Tpat_construct(_, _, pats) -> +#else + | Tpat_construct(_,_,pats,_) -> +#endif List.concat (List.map (read_pattern env parent doc) pats) | Tpat_variant(_, None, _) -> [] | Tpat_variant(_, Some pat, _) -> diff --git a/src/loader/cmti.ml b/src/loader/cmti.ml index 4090e70fec..7fe0e0ee90 100644 --- a/src/loader/cmti.ml +++ b/src/loader/cmti.ml @@ -485,6 +485,10 @@ let rec read_with_constraint env parent (_, frag, constr) = let frag = Env.Fragment.read_module frag.Location.txt in let p = Env.Path.read_module env p in ModuleSubst(frag, p) +#if OCAML_VERSION >= (4,13,0) + | Twith_modtype _ -> failwith "with module type is only supported by odoc 2.0 and later" + | Twith_modtypesubst _ -> failwith "with module type is only supported by odoc 2.0 and later" +#endif and read_module_type env parent label_parent pos mty = let open ModuleType in @@ -701,6 +705,10 @@ and read_signature_item env parent item = read_type_substitutions env parent tst | Tsig_modsubst mst -> [ModuleSubstitution (read_module_substitution env parent mst)] +#if OCAML_VERSION >= (4,13,0) + | Tsig_modtypesubst _ -> failwith "local module type substitution is only supported by odoc 2.0 and later" +#endif + and read_module_substitution env parent ms = let open ModuleSubstitution in diff --git a/src/model/ident_env.cppo.ml b/src/model/ident_env.cppo.ml index 0d2530181f..fff19a0b0b 100644 --- a/src/model/ident_env.cppo.ml +++ b/src/model/ident_env.cppo.ml @@ -243,6 +243,10 @@ let add_signature_tree_item parent item env = List.fold_right (fun decl env -> add_type parent decl.typ_id (TypeName.of_ident decl.typ_id) env) ts env +#endif +#if OCAML_VERSION >= (4,13,0) + | Tsig_modtypesubst mtd -> + add_module_type parent mtd.mtd_id (ModuleTypeName.of_ident mtd.mtd_id) env #endif | Tsig_value _ | Tsig_typext _ | Tsig_exception _ | Tsig_open _