File tree Expand file tree Collapse file tree 6 files changed +37
-11
lines changed
test/generators/html_opts.t Expand file tree Collapse file tree 6 files changed +37
-11
lines changed Original file line number Diff line number Diff line change @@ -9,10 +9,11 @@ type t = {
9
9
open_details : bool ;
10
10
omit_breadcrumbs : bool ;
11
11
omit_toc : bool ;
12
+ content_only : bool ;
12
13
}
13
14
14
- let v ?theme_uri ?support_uri ~semantic_uris ~indent ~flat ~open_details ~omit_breadcrumbs ~omit_toc () =
15
- { theme_uri; support_uri; semantic_uris; indent; flat; open_details; omit_breadcrumbs; omit_toc }
15
+ let v ?theme_uri ?support_uri ~semantic_uris ~indent ~flat ~open_details ~omit_breadcrumbs ~omit_toc ~ content_only () =
16
+ { theme_uri; support_uri; semantic_uris; indent; flat; open_details; omit_breadcrumbs; omit_toc; content_only }
16
17
17
18
let theme_uri config =
18
19
match config.theme_uri with None -> Types. Relative None | Some uri -> uri
@@ -30,4 +31,6 @@ let open_details config = config.open_details
30
31
31
32
let omit_breadcrumbs config = config.omit_breadcrumbs
32
33
33
- let omit_toc config = config.omit_toc
34
+ let omit_toc config = config.omit_toc
35
+
36
+ let content_only config = config.content_only
Original file line number Diff line number Diff line change @@ -11,6 +11,7 @@ val v :
11
11
open_details :bool ->
12
12
omit_breadcrumbs :bool ->
13
13
omit_toc :bool ->
14
+ content_only :bool ->
14
15
unit ->
15
16
t
16
17
@@ -28,4 +29,6 @@ val open_details : t -> bool
28
29
29
30
val omit_breadcrumbs : t -> bool
30
31
31
- val omit_toc : t -> bool
32
+ val omit_toc : t -> bool
33
+
34
+ val content_only : t -> bool
Original file line number Diff line number Diff line change @@ -138,10 +138,19 @@ let page_creator ~config ~url name header toc content =
138
138
@ toc
139
139
@ [ Html. div ~a: [ Html. a_class [ " odoc-content" ] ] content ]
140
140
in
141
- Html. html head (Html. body ~a: [ Html. a_class [ " odoc" ] ] body)
141
+ let htmlpp_elt = Html. pp_elt ~indent: (Config. indent config) () in
142
+ let htmlpp = Html. pp ~indent: (Config. indent config) () in
143
+ if Config. content_only config
144
+ then begin
145
+ let content ppf = htmlpp_elt ppf (Html. div ~a: [ Html. a_class [ " odoc" ] ] body) in
146
+ content
147
+ end else begin
148
+ let html = Html. html head (Html. body ~a: [ Html. a_class [ " odoc" ] ] body) in
149
+ let content ppf = htmlpp ppf html in
150
+ content
151
+ end
142
152
143
153
let make ~config ~url ~header ~toc title content children =
144
154
let filename = Link.Path. as_filename ~is_flat: (Config. flat config) url in
145
- let html = page_creator ~config ~url title header toc content in
146
- let content ppf = (Html. pp ~indent: (Config. indent config) () ) ppf html in
155
+ let content = page_creator ~config ~url title header toc content in
147
156
[ { Odoc_document.Renderer. filename; content; children } ]
Original file line number Diff line number Diff line change @@ -527,16 +527,22 @@ module Odoc_html_args = struct
527
527
" Don't emit the table of contents div"
528
528
in
529
529
Arg. (value & flag & info ~docs ~doc [ " omit-toc" ])
530
+
531
+ let content_only =
532
+ let doc =
533
+ " Only emit the content of the page, not the html, head and body elements"
534
+ in
535
+ Arg. (value & flag & info ~docs ~doc [ " content-only" ])
530
536
531
537
let extra_args =
532
- let config semantic_uris closed_details indent theme_uri support_uri flat omit_breadcrumbs omit_toc =
538
+ let config semantic_uris closed_details indent theme_uri support_uri flat omit_breadcrumbs omit_toc content_only =
533
539
let open_details = not closed_details in
534
540
Odoc_html.Config. v ~theme_uri ~support_uri ~semantic_uris ~indent ~flat
535
- ~open_details ~omit_breadcrumbs ~omit_toc ()
541
+ ~open_details ~omit_breadcrumbs ~omit_toc ~content_only ()
536
542
in
537
543
Term. (
538
544
const config $ semantic_uris $ closed_details $ indent $ theme_uri
539
- $ support_uri $ flat $ omit_breadcrumbs $ omit_toc)
545
+ $ support_uri $ flat $ omit_breadcrumbs $ omit_toc $ content_only )
540
546
end
541
547
542
548
module Odoc_html = Make_renderer (Odoc_html_args )
Original file line number Diff line number Diff line change @@ -26,7 +26,7 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input =
26
26
let page = Odoc_document.Comment. to_ir resolved.content in
27
27
let config =
28
28
Odoc_html.Config. v ~semantic_uris: false ~indent: false ~flat: false
29
- ~open_details: false ~omit_breadcrumbs: false ~omit_toc: false ()
29
+ ~open_details: false ~omit_breadcrumbs: false ~omit_toc: false ~content_only: false ()
30
30
in
31
31
let html = Odoc_html.Generator. doc ~config ~xref_base_uri page in
32
32
let oc = open_out (Fs.File. to_string output) in
Original file line number Diff line number Diff line change @@ -40,4 +40,9 @@ Check omission of toc:
40
40
$ grep odoc-toc html/ test/ Test / index . html
41
41
[1 ]
42
42
43
+ Check content-only output:
44
+ $ odoc html-generate test. odocl -o html -- indent -- content-only
45
+ $ head -n 1 html/ test/ Test / index . html
46
+ <div class="odoc" >
47
+
43
48
You can’t perform that action at this time.
0 commit comments