Skip to content

Commit

Permalink
Compatibility
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Oct 18, 2024
1 parent 35ad0aa commit 1677caa
Show file tree
Hide file tree
Showing 5 changed files with 52 additions and 51 deletions.
24 changes: 16 additions & 8 deletions src/document/sidebar.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,12 +2,16 @@ open Odoc_utils
open Types

let sidebar_toc_entry id content =
let href =
(id :> Odoc_model.Paths.Identifier.t)
|> Url.from_identifier ~stop_before:false
|> Result.get_ok
let target =
match
(id :> Odoc_model.Paths.Identifier.t)
|> Url.from_identifier ~stop_before:false
with
| Ok href -> Target.Resolved href
| Error _ -> Target.Unresolved
(* This error case should never happen since [stop_before] is false *)
in
let target = Target.Internal (Resolved href) in
let target = Target.Internal target in
inline @@ Inline.Link { target; content; tooltip = None }

module Toc : sig
Expand All @@ -30,8 +34,12 @@ end = struct
| None -> None
| Some (index_id, title) ->
let path =
Url.from_identifier ~stop_before:false (index_id :> Id.t)
|> Result.get_ok
match
Url.from_identifier ~stop_before:false (index_id :> Id.t)
with
| Ok r -> r
| Error _ -> assert false
(* This error case should never happen since [stop_before] is false, and even less since it's a page id *)
in
let content = Comment.link_content title in
Some (path, sidebar_toc_entry index_id content)
Expand Down Expand Up @@ -59,7 +67,7 @@ end = struct
root. So we apply the filter_map starting from the first children. *)
let convert ((url : Url.t), b) =
let link =
if url.page = current_url && String.equal url.anchor "" then
if url.page = current_url && Astring.String.equal url.anchor "" then
{ b with Inline.attr = [ "current_unit" ] }
else b
in
Expand Down
16 changes: 4 additions & 12 deletions src/document/url.ml
Original file line number Diff line number Diff line change
Expand Up @@ -448,18 +448,10 @@ let from_path page =
{ Anchor.page; anchor = ""; kind = (page.kind :> Anchor.kind) }

let from_identifier ~stop_before x =
if Identifier.is_hidden x then
Ok
{
Anchor.page = { parent = None; kind = `Module; name = "blooooooo" };
anchor = "bliiiiiiii";
kind = `Module;
}
else
match x with
| { Identifier.iv = #Path.any_pv; _ } as p when not stop_before ->
Ok (from_path @@ Path.from_identifier p)
| p -> Anchor.from_identifier p
match x with
| { Identifier.iv = #Path.any_pv; _ } as p when not stop_before ->
Ok (from_path @@ Path.from_identifier p)
| p -> Anchor.from_identifier p

let from_asset_identifier p = from_path @@ Path.from_identifier p

Expand Down
29 changes: 29 additions & 0 deletions src/utils/odoc_list.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
include List

let rec concat_map ?sep ~f = function
| [] -> []
| [ x ] -> f x
| x :: xs -> (
let hd = f x in
let tl = concat_map ?sep ~f xs in
match sep with None -> hd @ tl | Some sep -> hd @ (sep :: tl))

let rec filter_map acc f = function
| hd :: tl ->
let acc = match f hd with Some x -> x :: acc | None -> acc in
filter_map acc f tl
| [] -> List.rev acc

let filter_map f x = filter_map [] f x

(** @raise [Failure] if the list is empty. *)
let rec last = function
| [] -> failwith "Odoc_utils.List.last"
| [ x ] -> x
| _ :: tl -> last tl

(* From ocaml/ocaml *)
let rec find_map f = function
| [] -> None
| x :: l -> (
match f x with Some _ as result -> result | None -> find_map f l)
32 changes: 1 addition & 31 deletions src/utils/odoc_utils.ml
Original file line number Diff line number Diff line change
Expand Up @@ -45,37 +45,7 @@ module EitherMonad = struct
let of_result = function Result.Ok x -> Right x | Error y -> Left y
end

module List = struct
include List

let rec concat_map ?sep ~f = function
| [] -> []
| [ x ] -> f x
| x :: xs -> (
let hd = f x in
let tl = concat_map ?sep ~f xs in
match sep with None -> hd @ tl | Some sep -> hd @ (sep :: tl))

let rec filter_map acc f = function
| hd :: tl ->
let acc = match f hd with Some x -> x :: acc | None -> acc in
filter_map acc f tl
| [] -> List.rev acc

let filter_map f x = filter_map [] f x

(** @raise [Failure] if the list is empty. *)
let rec last = function
| [] -> failwith "Odoc_utils.List.last"
| [ x ] -> x
| _ :: tl -> last tl

(* From ocaml/ocaml *)
let rec find_map f = function
| [] -> None
| x :: l -> (
match f x with Some _ as result -> result | None -> find_map f l)
end
module List = Odoc_list

module Option = struct
let map f = function None -> None | Some x -> Some (f x)
Expand Down
2 changes: 2 additions & 0 deletions src/utils/tree.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
module List = Odoc_list

type 'a t = { node : 'a; children : 'a forest }
and 'a forest = 'a t list

Expand Down

0 comments on commit 1677caa

Please sign in to comment.