Skip to content

Commit 1677caa

Browse files
committed
Compatibility
1 parent 35ad0aa commit 1677caa

File tree

5 files changed

+52
-51
lines changed

5 files changed

+52
-51
lines changed

src/document/sidebar.ml

Lines changed: 16 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -2,12 +2,16 @@ open Odoc_utils
22
open Types
33

44
let sidebar_toc_entry id content =
5-
let href =
6-
(id :> Odoc_model.Paths.Identifier.t)
7-
|> Url.from_identifier ~stop_before:false
8-
|> Result.get_ok
5+
let target =
6+
match
7+
(id :> Odoc_model.Paths.Identifier.t)
8+
|> Url.from_identifier ~stop_before:false
9+
with
10+
| Ok href -> Target.Resolved href
11+
| Error _ -> Target.Unresolved
12+
(* This error case should never happen since [stop_before] is false *)
913
in
10-
let target = Target.Internal (Resolved href) in
14+
let target = Target.Internal target in
1115
inline @@ Inline.Link { target; content; tooltip = None }
1216

1317
module Toc : sig
@@ -30,8 +34,12 @@ end = struct
3034
| None -> None
3135
| Some (index_id, title) ->
3236
let path =
33-
Url.from_identifier ~stop_before:false (index_id :> Id.t)
34-
|> Result.get_ok
37+
match
38+
Url.from_identifier ~stop_before:false (index_id :> Id.t)
39+
with
40+
| Ok r -> r
41+
| Error _ -> assert false
42+
(* This error case should never happen since [stop_before] is false, and even less since it's a page id *)
3543
in
3644
let content = Comment.link_content title in
3745
Some (path, sidebar_toc_entry index_id content)
@@ -59,7 +67,7 @@ end = struct
5967
root. So we apply the filter_map starting from the first children. *)
6068
let convert ((url : Url.t), b) =
6169
let link =
62-
if url.page = current_url && String.equal url.anchor "" then
70+
if url.page = current_url && Astring.String.equal url.anchor "" then
6371
{ b with Inline.attr = [ "current_unit" ] }
6472
else b
6573
in

src/document/url.ml

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -448,18 +448,10 @@ let from_path page =
448448
{ Anchor.page; anchor = ""; kind = (page.kind :> Anchor.kind) }
449449

450450
let from_identifier ~stop_before x =
451-
if Identifier.is_hidden x then
452-
Ok
453-
{
454-
Anchor.page = { parent = None; kind = `Module; name = "blooooooo" };
455-
anchor = "bliiiiiiii";
456-
kind = `Module;
457-
}
458-
else
459-
match x with
460-
| { Identifier.iv = #Path.any_pv; _ } as p when not stop_before ->
461-
Ok (from_path @@ Path.from_identifier p)
462-
| p -> Anchor.from_identifier p
451+
match x with
452+
| { Identifier.iv = #Path.any_pv; _ } as p when not stop_before ->
453+
Ok (from_path @@ Path.from_identifier p)
454+
| p -> Anchor.from_identifier p
463455

464456
let from_asset_identifier p = from_path @@ Path.from_identifier p
465457

src/utils/odoc_list.ml

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
include List
2+
3+
let rec concat_map ?sep ~f = function
4+
| [] -> []
5+
| [ x ] -> f x
6+
| x :: xs -> (
7+
let hd = f x in
8+
let tl = concat_map ?sep ~f xs in
9+
match sep with None -> hd @ tl | Some sep -> hd @ (sep :: tl))
10+
11+
let rec filter_map acc f = function
12+
| hd :: tl ->
13+
let acc = match f hd with Some x -> x :: acc | None -> acc in
14+
filter_map acc f tl
15+
| [] -> List.rev acc
16+
17+
let filter_map f x = filter_map [] f x
18+
19+
(** @raise [Failure] if the list is empty. *)
20+
let rec last = function
21+
| [] -> failwith "Odoc_utils.List.last"
22+
| [ x ] -> x
23+
| _ :: tl -> last tl
24+
25+
(* From ocaml/ocaml *)
26+
let rec find_map f = function
27+
| [] -> None
28+
| x :: l -> (
29+
match f x with Some _ as result -> result | None -> find_map f l)

src/utils/odoc_utils.ml

Lines changed: 1 addition & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -45,37 +45,7 @@ module EitherMonad = struct
4545
let of_result = function Result.Ok x -> Right x | Error y -> Left y
4646
end
4747

48-
module List = struct
49-
include List
50-
51-
let rec concat_map ?sep ~f = function
52-
| [] -> []
53-
| [ x ] -> f x
54-
| x :: xs -> (
55-
let hd = f x in
56-
let tl = concat_map ?sep ~f xs in
57-
match sep with None -> hd @ tl | Some sep -> hd @ (sep :: tl))
58-
59-
let rec filter_map acc f = function
60-
| hd :: tl ->
61-
let acc = match f hd with Some x -> x :: acc | None -> acc in
62-
filter_map acc f tl
63-
| [] -> List.rev acc
64-
65-
let filter_map f x = filter_map [] f x
66-
67-
(** @raise [Failure] if the list is empty. *)
68-
let rec last = function
69-
| [] -> failwith "Odoc_utils.List.last"
70-
| [ x ] -> x
71-
| _ :: tl -> last tl
72-
73-
(* From ocaml/ocaml *)
74-
let rec find_map f = function
75-
| [] -> None
76-
| x :: l -> (
77-
match f x with Some _ as result -> result | None -> find_map f l)
78-
end
48+
module List = Odoc_list
7949

8050
module Option = struct
8151
let map f = function None -> None | Some x -> Some (f x)

src/utils/tree.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
module List = Odoc_list
2+
13
type 'a t = { node : 'a; children : 'a forest }
24
and 'a forest = 'a t list
35

0 commit comments

Comments
 (0)