Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 4 additions & 0 deletions src/loader/cmi.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,10 @@ module Paths = Odoc_model.Paths

module Compat = struct
#if OCAML_VERSION >= (4, 14, 0)
#if OCAML_VERSION >= (5, 3, 0)
let newty2 = Btype.newty2
#endif

(** this is the type on which physical equality is meaningful *)
type repr_type_node = Types.transient_expr

Expand Down
4 changes: 3 additions & 1 deletion src/loader/doc_attr.ml
Original file line number Diff line number Diff line change
Expand Up @@ -39,8 +39,10 @@ let load_constant_string = function
Pexp_constant (Const_string (text, _))
#elif OCAML_VERSION < (4,11,0)
Pexp_constant (Pconst_string (text, _))
#else
#elif OCAML_VERSION < (5,3,0)
Pexp_constant (Pconst_string (text, _, _))
#else
Pexp_constant {pconst_desc= Pconst_string (text, _, _); _}
#endif
; pexp_loc = loc; _} ->
Some (text , loc)
Expand Down
6 changes: 6 additions & 0 deletions src/syntax_highlighter/syntax_highlighter.ml
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,12 @@ let tag_of_token (tok : Parser.token) =
| ANDOP _ -> "ANDOP"
| LETOP _ -> "LETOP"
#endif
#if OCAML_VERSION >= (5,3,0)
| METAOCAML_ESCAPE -> "METAOCAML_ESCAPE"
| METAOCAML_BRACKET_OPEN -> "METAOCAML_BRACKET_OPEN"
| METAOCAML_BRACKET_CLOSE -> "METAOCAML_BRACKET_CLOSE"
| EFFECT -> "EFFECT"
#endif

let syntax_highlighting_locs src =
let lexbuf = Lexing.from_string
Expand Down
2 changes: 1 addition & 1 deletion src/xref2/shape_tools.cppo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ module MkId = Identifier.Mk
let unit_of_uid uid =
match uid with
| Shape.Uid.Compilation_unit s -> Some s
| Item { comp_unit; id = _ } -> Some comp_unit
| Item { comp_unit; _ } -> Some comp_unit
| Predef _ -> None
| Internal -> None

Expand Down
4 changes: 3 additions & 1 deletion test/xref2/lib/common.cppo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,10 @@ let cmt_of_string s =
let p = Parse.implementation l in
#if OCAML_VERSION < (5,2,0)
Typemod.type_implementation "" "" "" env p
#else
#elif OCAML_VERSION < (5,3,0)
Typemod.type_implementation (Unit_info.make ~source_file:"" "") env p
#else
Typemod.type_implementation Unit_info.(make ~source_file:"" Impl "") env p
#endif

let parent = Odoc_model.Paths.Identifier.Mk.page (None, Odoc_model.Names.PageName.make_std "None")
Expand Down
2 changes: 1 addition & 1 deletion test/xref2/module_preamble.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered
$ ocamlc -bin-annot -o a__b.cmo -c b.ml
$ ocamlc -bin-annot -o a.cmi -c a.mli
$ ocamlc -bin-annot -o a.cmo -c a.ml
$ ocamlc -bin-annot -a -o a.cma a.cmo a__b.cmo
$ ocamlc -bin-annot -a -o a.cma a__b.cmo a.cmo

$ odoc compile --pkg test -o a__b.odoc -I . a__b.cmti
$ odoc compile --pkg test -o a.odoc -I . a.cmti
Expand Down
Loading