Skip to content

Commit f0aa658

Browse files
committed
Consistent output file names in all backends
The latex and man backends were prefixing names differently than the HTML backend. This can create naming conflicts. This removes code that was hard to maintain.
1 parent a45c770 commit f0aa658

File tree

115 files changed

+1009
-1030
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

115 files changed

+1009
-1030
lines changed

src/document/url.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -115,6 +115,10 @@ module Path = struct
115115

116116
let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind)
117117

118+
let pp_kind_prefix_for_output fmt = function
119+
| `Module | `Page | `LeafPage | `File | `SourcePage -> ()
120+
| kind -> Format.fprintf fmt "%s-" (string_of_kind kind)
121+
118122
type t = { kind : kind; parent : t option; name : string }
119123

120124
let mk ?parent kind name = { kind; parent; name }

src/document/url.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,9 @@ module Path : sig
2727

2828
val string_of_kind : kind -> string
2929

30+
val pp_kind_prefix_for_output : Format.formatter -> kind -> unit
31+
(** Print the ["kind-"] prefix used in output files. *)
32+
3033
type t = { kind : kind; parent : t option; name : string }
3134

3235
type any_pv =

src/html/link.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,9 +5,7 @@ module Path = struct
55
let for_printing url = List.map snd @@ Url.Path.to_list url
66

77
let segment_to_string (kind, name) =
8-
match kind with
9-
| `Module | `Page | `File | `SourcePage -> name
10-
| _ -> Format.asprintf "%a-%s" Url.Path.pp_kind kind name
8+
Format.asprintf "%a%s" Url.Path.pp_kind_prefix_for_output kind name
119

1210
let is_leaf_page url = url.Url.Path.kind = `LeafPage
1311

src/latex/generator.ml

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,16 @@
11
open Odoc_document.Types
22
open Types
33
module Doctree = Odoc_document.Doctree
4+
module Url = Odoc_document.Url
45

56
module Link = struct
67
let rec flatten_path ppf (x : Odoc_document.Url.Path.t) =
7-
match x.parent with
8-
| Some p ->
9-
Fmt.pf ppf "%a-%a-%s" flatten_path p Odoc_document.Url.Path.pp_kind
10-
x.kind x.name
11-
| None -> Fmt.pf ppf "%a-%s" Odoc_document.Url.Path.pp_kind x.kind x.name
8+
let pp_parent ppf = function
9+
| Some p -> Format.fprintf ppf "%a-" flatten_path p
10+
| None -> ()
11+
in
12+
Format.fprintf ppf "%a%a%s" pp_parent x.parent
13+
Url.Path.pp_kind_prefix_for_output x.kind x.name
1214

1315
let page p = Format.asprintf "%a" flatten_path p
1416

src/manpage/link.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,7 @@ open Odoc_document
33
let for_printing url = List.map snd @@ Url.Path.to_list url
44

55
let segment_to_string (kind, name) =
6-
match kind with
7-
| `Module | `Page | `LeafPage | `Class -> name
8-
| _ -> Format.asprintf "%a-%s" Odoc_document.Url.Path.pp_kind kind name
6+
Format.asprintf "%a%s" Url.Path.pp_kind_prefix_for_output kind name
97

108
let as_filename ?(add_ext = true) (url : Url.Path.t) =
119
let components = Url.Path.to_list url in

test/generators/latex/Alerts.tex

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,41 +1,41 @@
1-
\section{Module \ocamlinlinecode{Alerts}}\label{module-Alerts}%
2-
\label{module-Alerts-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : int}\begin{ocamlindent}\begin{description}\kern-\topsep
1+
\section{Module \ocamlinlinecode{Alerts}}\label{Alerts}%
2+
\label{Alerts-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : int}\begin{ocamlindent}\begin{description}\kern-\topsep
33
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
44
\item[{deprecated}]{a}\end{description}%
55
\end{ocamlindent}%
66
\medbreak
7-
\label{module-Alerts-val-b}\ocamlcodefragment{\ocamltag{keyword}{val} b : int}\begin{ocamlindent}\begin{description}\kern-\topsep
7+
\label{Alerts-val-b}\ocamlcodefragment{\ocamltag{keyword}{val} b : int}\begin{ocamlindent}\begin{description}\kern-\topsep
88
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
99
\item[{deprecated}]{b.}\end{description}%
1010
\end{ocamlindent}%
1111
\medbreak
12-
\label{module-Alerts-val-c}\ocamlcodefragment{\ocamltag{keyword}{val} c : int}\begin{ocamlindent}\begin{description}\kern-\topsep
12+
\label{Alerts-val-c}\ocamlcodefragment{\ocamltag{keyword}{val} c : int}\begin{ocamlindent}\begin{description}\kern-\topsep
1313
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
1414
\item[{deprecated}]{}\end{description}%
1515
\end{ocamlindent}%
1616
\medbreak
17-
\label{module-Alerts-module-Top1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Alerts-module-Top1]{\ocamlinlinecode{Top1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
17+
\label{Alerts-module-Top1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Alerts-Top1]{\ocamlinlinecode{Top1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
1818
\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment.\end{ocamlindent}%
1919
\medbreak
20-
\label{module-Alerts-module-Top2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Alerts-module-Top2]{\ocamlinlinecode{Top2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
20+
\label{Alerts-module-Top2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Alerts-Top2]{\ocamlinlinecode{Top2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
2121
\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment.\end{ocamlindent}%
2222
\medbreak
23-
\label{module-Alerts-val-d}\ocamlcodefragment{\ocamltag{keyword}{val} d : int}\begin{ocamlindent}\begin{description}\kern-\topsep
23+
\label{Alerts-val-d}\ocamlcodefragment{\ocamltag{keyword}{val} d : int}\begin{ocamlindent}\begin{description}\kern-\topsep
2424
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
2525
\item[{deprecated}]{A deprecated alert d}\end{description}%
2626
\end{ocamlindent}%
2727
\medbreak
28-
\label{module-Alerts-val-d2}\ocamlcodefragment{\ocamltag{keyword}{val} d2 : int}\begin{ocamlindent}\begin{description}\kern-\topsep
28+
\label{Alerts-val-d2}\ocamlcodefragment{\ocamltag{keyword}{val} d2 : int}\begin{ocamlindent}\begin{description}\kern-\topsep
2929
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
3030
\item[{deprecated}]{}\end{description}%
3131
\end{ocamlindent}%
3232
\medbreak
33-
\label{module-Alerts-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : int}\begin{ocamlindent}\begin{description}\kern-\topsep
33+
\label{Alerts-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : int}\begin{ocamlindent}\begin{description}\kern-\topsep
3434
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
3535
\item[{alert}]{e an alert}\end{description}%
3636
\end{ocamlindent}%
3737
\medbreak
38-
\label{module-Alerts-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : int}\begin{ocamlindent}\begin{description}\kern-\topsep
38+
\label{Alerts-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : int}\begin{ocamlindent}\begin{description}\kern-\topsep
3939
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
4040
\item[{alert}]{f}\end{description}%
4141
\end{ocamlindent}%

test/generators/latex/Alias.X.tex

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
\section{Module \ocamlinlinecode{Alias.\allowbreak{}X}}\label{module-Alias-module-X}%
2-
\label{module-Alias-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}%
1+
\section{Module \ocamlinlinecode{Alias.\allowbreak{}X}}\label{Alias-X}%
2+
\label{Alias-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}%
33
\medbreak
44

55

test/generators/latex/Alias.tex

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
\section{Module \ocamlinlinecode{Alias}}\label{module-Alias}%
2-
\label{module-Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Alias-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
1+
\section{Module \ocamlinlinecode{Alias}}\label{Alias}%
2+
\label{Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Alias-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
33

44
\input{Alias.X.tex}

test/generators/latex/Bugs.tex

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
1-
\section{Module \ocamlinlinecode{Bugs}}\label{module-Bugs}%
2-
\label{module-Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\
3-
\label{module-Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : \ocamltag{optlabel}{?bar}:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}%
1+
\section{Module \ocamlinlinecode{Bugs}}\label{Bugs}%
2+
\label{Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\
3+
\label{Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : \ocamltag{optlabel}{?bar}:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}%
44
\medbreak
5-
\label{module-Bugs-val-repeat}\ocamlcodefragment{\ocamltag{keyword}{val} repeat : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} * \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b}}\begin{ocamlindent}Renders as \ocamlinlinecode{val repeat : 'a -> 'b -> 'c * 'd * 'e * 'f} before https://github.com/ocaml/odoc/pull/1173\end{ocamlindent}%
5+
\label{Bugs-val-repeat}\ocamlcodefragment{\ocamltag{keyword}{val} repeat : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} * \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b}}\begin{ocamlindent}Renders as \ocamlinlinecode{val repeat : 'a -> 'b -> 'c * 'd * 'e * 'f} before https://github.com/ocaml/odoc/pull/1173\end{ocamlindent}%
66
\medbreak
77

88

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
1-
\section{Class \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406.\allowbreak{}let\_\allowbreak{}open'}}\label{module-Bugs_post_406-class-let_open'}%
1+
\section{Class \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406.\allowbreak{}let\_\allowbreak{}open'}}\label{Bugs_post_406-class-let_open'}%
22

33

0 commit comments

Comments
 (0)