@@ -18,7 +18,7 @@ module Html = Tyxml.Html
18
18
19
19
let html_of_toc toc =
20
20
let open Types in
21
- let rec section section =
21
+ let rec section ( section : toc ) =
22
22
let link = Html. a ~a: [ Html. a_href section.href ] section.title in
23
23
match section.children with [] -> [ link ] | cs -> [ link; sections cs ]
24
24
and sections the_sections =
@@ -30,13 +30,54 @@ let html_of_toc toc =
30
30
| [] -> []
31
31
| _ -> [ Html. nav ~a: [ Html. a_class [ " odoc-toc" ] ] [ sections toc ] ]
32
32
33
- let page_creator ~config ~url ~uses_katex name header toc content =
33
+ let html_of_breadcrumbs (breadcrumbs : Types.breadcrumb list ) =
34
+ let make_navigation ~up_url rest =
35
+ [
36
+ Html. nav
37
+ ~a: [ Html. a_class [ " odoc-nav" ] ]
38
+ ([ Html. a ~a: [ Html. a_href up_url ] [ Html. txt " Up" ]; Html. txt " – " ]
39
+ @ rest);
40
+ ]
41
+ in
42
+ match List. rev breadcrumbs with
43
+ | [] -> [] (* Can't happen - there's always the current page's breadcrumb. *)
44
+ | [ _ ] -> [] (* No parents *)
45
+ | [ { name = " index" ; _ }; x ] ->
46
+ (* Special case leaf pages called 'index' with one parent. This is for files called
47
+ index.mld that would otherwise clash with their parent. In particular,
48
+ dune and odig both cause this situation right now. *)
49
+ let up_url = " ../index.html" in
50
+ let parent_name = x.name in
51
+ make_navigation ~up_url [ Html. txt parent_name ]
52
+ | current :: up :: bs ->
53
+ let space = Html. txt " " in
54
+ let sep = [ space; Html. entity " #x00BB" ; space ] in
55
+ let html =
56
+ (* Create breadcrumbs *)
57
+ Utils. list_concat_map ?sep:(Some sep)
58
+ ~f: (fun (breadcrumb : Types.breadcrumb ) ->
59
+ [
60
+ [
61
+ Html. a
62
+ ~a: [ Html. a_href breadcrumb.href ]
63
+ [ Html. txt breadcrumb.name ];
64
+ ];
65
+ ])
66
+ (up :: bs)
67
+ |> List. flatten
68
+ in
69
+ make_navigation ~up_url: up.href
70
+ (List. rev html @ sep @ [ Html. txt current.name ])
71
+
72
+ let page_creator ~config ~url ~uses_katex header breadcrumbs toc content =
34
73
let theme_uri = Config. theme_uri config in
35
74
let support_uri = Config. support_uri config in
36
75
let path = Link.Path. for_printing url in
37
76
38
77
let head : Html_types.head Html.elt =
39
- let title_string = Printf. sprintf " %s (%s)" name (String. concat " ." path) in
78
+ let title_string =
79
+ Printf. sprintf " %s (%s)" url.name (String. concat " ." path)
80
+ in
40
81
41
82
let file_uri base file =
42
83
match base with
@@ -99,89 +140,20 @@ let page_creator ~config ~url ~uses_katex name header toc content =
99
140
Html. head (Html. title (Html. txt title_string)) meta_elements
100
141
in
101
142
102
- let gen_breadcrumbs () =
103
- let rec get_parents x =
104
- match x with
105
- | [] -> []
106
- | x :: xs -> (
107
- match Odoc_document.Url.Path. of_list (List. rev (x :: xs)) with
108
- | Some x -> x :: get_parents xs
109
- | None -> get_parents xs)
110
- in
111
- let parents =
112
- get_parents (List. rev (Odoc_document.Url.Path. to_list url)) |> List. rev
113
- in
114
- let href page =
115
- Link. href ~resolve: (Current url) (Odoc_document.Url. from_path page)
116
- in
117
- let make_navigation ~up_url breadcrumbs =
118
- [
119
- Html. nav
120
- ~a: [ Html. a_class [ " odoc-nav" ] ]
121
- ([
122
- Html. a ~a: [ Html. a_href up_url ] [ Html. txt " Up" ]; Html. txt " – " ;
123
- ]
124
- @ breadcrumbs);
125
- ]
126
- in
127
- match parents with
128
- | [] -> [] (* Can't happen - Url.Path.to_list returns a non-empty list *)
129
- | [ _ ] -> [] (* No parents *)
130
- | [ x; { name = " index" ; _ } ] ->
131
- (* Special case leaf pages called 'index' with one parent. This is for files called
132
- index.mld that would otherwise clash with their parent. In particular,
133
- dune and odig both cause this situation right now. *)
134
- let up_url = " ../index.html" in
135
- let parent_name = x.name in
136
- make_navigation ~up_url [ Html. txt parent_name ]
137
- | _ ->
138
- let up_url = href ~config (List. hd (List. tl (List. rev parents))) in
139
- let l =
140
- (* Create breadcrumbs *)
141
- let space = Html. txt " " in
142
- parents
143
- |> Utils. list_concat_map
144
- ?sep:(Some [ space; Html.entity "#x00BB"; space ] )
145
- ~f: (fun url' ->
146
- [
147
- [
148
- (if url = url' then Html. txt url.name
149
- else
150
- Html. a
151
- ~a: [ Html. a_href (href ~config url') ]
152
- [ Html. txt url'.name ]);
153
- ];
154
- ])
155
- |> List. flatten
156
- in
157
- make_navigation ~up_url l
158
- in
159
-
160
- let breadcrumbs =
161
- if Config. omit_breadcrumbs config then [] else gen_breadcrumbs ()
162
- in
163
- let toc = if Config. omit_toc config then [] else html_of_toc toc in
164
143
let body =
165
- breadcrumbs
144
+ html_of_breadcrumbs breadcrumbs
166
145
@ [ Html. header ~a: [ Html. a_class [ " odoc-preamble" ] ] header ]
167
- @ toc
146
+ @ html_of_toc toc
168
147
@ [ Html. div ~a: [ Html. a_class [ " odoc-content" ] ] content ]
169
148
in
170
- let htmlpp_elt = Html. pp_elt ~indent: (Config. indent config) () in
171
149
let htmlpp = Html. pp ~indent: (Config. indent config) () in
172
- if Config. content_only config then
173
- let content ppf =
174
- htmlpp_elt ppf (Html. div ~a: [ Html. a_class [ " odoc" ] ] body)
175
- in
176
- content
177
- else
178
- let html = Html. html head (Html. body ~a: [ Html. a_class [ " odoc" ] ] body) in
179
- let content ppf = htmlpp ppf html in
180
- content
150
+ let html = Html. html head (Html. body ~a: [ Html. a_class [ " odoc" ] ] body) in
151
+ let content ppf = htmlpp ppf html in
152
+ content
181
153
182
- let make ~config ~url ~header ~toc ~uses_katex title content children =
154
+ let make ~config ~url ~header ~breadcrumbs ~ toc ~uses_katex content children =
183
155
let filename = Link.Path. as_filename ~is_flat: (Config. flat config) url in
184
156
let content =
185
- page_creator ~config ~url ~uses_katex title header toc content
157
+ page_creator ~config ~url ~uses_katex header breadcrumbs toc content
186
158
in
187
159
[ { Odoc_document.Renderer. filename; content; children } ]
0 commit comments