Skip to content

Commit

Permalink
Breadcrumb: rename escape-breadcrumb to home-breadcrumb
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd authored and jonludlam committed Dec 11, 2024
1 parent 85b32c2 commit 7fa3d8b
Show file tree
Hide file tree
Showing 4 changed files with 12 additions and 12 deletions.
8 changes: 4 additions & 4 deletions src/html/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,12 @@ type t = {
flat : bool;
open_details : bool;
as_json : bool;
escape_breadcrumb : bool;
home_breadcrumb : bool;
}

let v ?(search_result = false) ?theme_uri ?support_uri ?(search_uris = [])
~semantic_uris ~indent ~flat ~open_details ~as_json ~remap
?(escape_breadcrumb = true) () =
?(home_breadcrumb = true) () =
{
semantic_uris;
indent;
Expand All @@ -29,7 +29,7 @@ let v ?(search_result = false) ?theme_uri ?support_uri ?(search_uris = [])
as_json;
search_result;
remap;
escape_breadcrumb;
home_breadcrumb;
}

let theme_uri config : Types.uri =
Expand All @@ -54,4 +54,4 @@ let search_result config = config.search_result

let remap config = config.remap

let escape_breadcrumb config = config.escape_breadcrumb
let home_breadcrumb config = config.home_breadcrumb
4 changes: 2 additions & 2 deletions src/html/config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ val v :
open_details:bool ->
as_json:bool ->
remap:(string * string) list ->
?escape_breadcrumb:bool ->
?home_breadcrumb:bool ->
unit ->
t
(** [search_result] indicates whether this is a summary for a search result. In
Expand All @@ -39,4 +39,4 @@ val search_result : t -> bool

val remap : t -> (string * string) list

val escape_breadcrumb : t -> bool
val home_breadcrumb : t -> bool
2 changes: 1 addition & 1 deletion src/html/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -614,7 +614,7 @@ module Breadcrumbs = struct
{ Types.current; parents; up_url }
in
let escape =
match (Config.escape_breadcrumb config, find_parent sidebar) with
match (Config.home_breadcrumb config, find_parent sidebar) with
| true, Some { node; _ } -> (
match page_parent node.url.page with
| None -> []
Expand Down
10 changes: 5 additions & 5 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1132,12 +1132,12 @@ module Odoc_html_args = struct
(parser, printer)
end

let escape_breadcrumb =
let home_breadcrumb =
let doc =
"Wether to add a 'Home' breadcrumb to go up the root of the given \
sidebar."
in
Arg.(value & flag & info ~docv:"escape" ~doc [ "escape-breadcrumb" ])
Arg.(value & flag & info ~docv:"escape" ~doc [ "home-breadcrumb" ])

let theme_uri =
let doc =
Expand Down Expand Up @@ -1207,7 +1207,7 @@ module Odoc_html_args = struct

let extra_args =
let config semantic_uris closed_details indent theme_uri support_uri
search_uris flat as_json remap remap_file escape_breadcrumb =
search_uris flat as_json remap remap_file home_breadcrumb =
let open_details = not closed_details in
let remap =
match remap_file with
Expand All @@ -1228,14 +1228,14 @@ module Odoc_html_args = struct
in
let html_config =
Odoc_html.Config.v ~theme_uri ~support_uri ~search_uris ~semantic_uris
~indent ~flat ~open_details ~as_json ~remap ~escape_breadcrumb ()
~indent ~flat ~open_details ~as_json ~remap ~home_breadcrumb ()
in
{ Html_page.html_config }
in
Term.(
const config $ semantic_uris $ closed_details $ indent $ theme_uri
$ support_uri $ search_uri $ flat $ as_json $ remap $ remap_file
$ escape_breadcrumb)
$ home_breadcrumb)
end

module Odoc_html = Make_renderer (Odoc_html_args)
Expand Down

0 comments on commit 7fa3d8b

Please sign in to comment.