Skip to content

Commit 53e3971

Browse files
Julowjonludlam
authored andcommitted
Compat with OCaml 5.3.0~alpha1
1 parent d8980ff commit 53e3971

File tree

7 files changed

+22
-26
lines changed

7 files changed

+22
-26
lines changed

src/loader/cmi.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,10 @@ module Paths = Odoc_model.Paths
2727

2828
module Compat = struct
2929
#if OCAML_VERSION >= (4, 14, 0)
30+
#if OCAML_VERSION >= (5, 3, 0)
31+
let newty2 = Btype.newty2
32+
#endif
33+
3034
(** this is the type on which physical equality is meaningful *)
3135
type repr_type_node = Types.transient_expr
3236

src/loader/doc_attr.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,8 +39,10 @@ let load_constant_string = function
3939
Pexp_constant (Const_string (text, _))
4040
#elif OCAML_VERSION < (4,11,0)
4141
Pexp_constant (Pconst_string (text, _))
42-
#else
42+
#elif OCAML_VERSION < (5,3,0)
4343
Pexp_constant (Pconst_string (text, _, _))
44+
#else
45+
Pexp_constant {pconst_desc= Pconst_string (text, _, _); _}
4446
#endif
4547
; pexp_loc = loc; _} ->
4648
Some (text , loc)

src/syntax_highlighter/syntax_highlighter.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,6 +145,12 @@ let tag_of_token (tok : Parser.token) =
145145
| ANDOP _ -> "ANDOP"
146146
| LETOP _ -> "LETOP"
147147
#endif
148+
#if OCAML_VERSION >= (5,3,0)
149+
| METAOCAML_ESCAPE -> "METAOCAML_ESCAPE"
150+
| METAOCAML_BRACKET_OPEN -> "METAOCAML_BRACKET_OPEN"
151+
| METAOCAML_BRACKET_CLOSE -> "METAOCAML_BRACKET_CLOSE"
152+
| EFFECT -> "EFFECT"
153+
#endif
148154

149155
let syntax_highlighting_locs src =
150156
let lexbuf = Lexing.from_string

src/xref2/shape_tools.cppo.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ module MkId = Identifier.Mk
115115
let unit_of_uid uid =
116116
match uid with
117117
| Shape.Uid.Compilation_unit s -> Some s
118-
| Item { comp_unit; id = _ } -> Some comp_unit
118+
| Item { comp_unit; _ } -> Some comp_unit
119119
| Predef _ -> None
120120
| Internal -> None
121121

test/xref2/lib/common.cppo.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,8 +35,10 @@ let cmt_of_string s =
3535
let p = Parse.implementation l in
3636
#if OCAML_VERSION < (5,2,0)
3737
Typemod.type_implementation "" "" "" env p
38-
#else
38+
#elif OCAML_VERSION < (5,3,0)
3939
Typemod.type_implementation (Unit_info.make ~source_file:"" "") env p
40+
#else
41+
Typemod.type_implementation Unit_info.(make ~source_file:"" Impl "") env p
4042
#endif
4143

4244
let parent = Odoc_model.Paths.Identifier.Mk.page (None, PageName.make_std "None")

test/xref2/module_preamble.t/run.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered
99
$ ocamlc -bin-annot -o a__b.cmo -c b.ml
1010
$ ocamlc -bin-annot -o a.cmi -c a.mli
1111
$ ocamlc -bin-annot -o a.cmo -c a.ml
12-
$ ocamlc -bin-annot -a -o a.cma a.cmo a__b.cmo
12+
$ ocamlc -bin-annot -a -o a.cma a__b.cmo a.cmo
1313

1414
$ odoc compile --pkg test -o a__b.odoc -I . a__b.cmti
1515
$ odoc compile --pkg test -o a.odoc -I . a.cmti

test/xref2/module_type_of_extra.t/run.t

Lines changed: 4 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -37,28 +37,10 @@ More advanced uses of `module type of`, including using functors.
3737

3838
$ ocamlc -c -bin-annot a.mli
3939
$ ocamlc -c -bin-annot b.mli
40-
$ ocamlc -i b.mli
41-
module X : sig type t end
42-
module type X1 = sig type t end
43-
module type X2 = sig module X : sig type t end end
44-
module type X3 = sig type t end
45-
module Y : functor (A : sig type t end) -> sig type t end
46-
module type Foo =
47-
sig
48-
module X : sig type t end
49-
module Y : functor (A : sig type t end) -> sig module Z = X end
50-
module type Z = functor (A : sig type t end) -> sig module Z = X end
51-
module X' : sig type t = X.t end
52-
end
53-
module type X4 = functor (A : sig type t end) -> sig type t end
54-
module SubX : sig type t type u end
55-
module type X5 =
56-
sig
57-
module Y : functor (A : sig type t end) -> sig module Z = SubX end
58-
module type Z = functor (A : sig type t end) -> sig module Z = SubX end
59-
module X' : sig type t = SubX.t end
60-
end
61-
module type X6 = sig type t end
40+
41+
Omitted for stability:
42+
$ ocamlc -i b.mli
43+
6244
$ odoc compile a.cmti
6345
$ odoc compile -I . b.cmti
6446
$ odoc link -I . a.odoc

0 commit comments

Comments
 (0)