forked from rescript-lang/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathodoc_html.ml
2920 lines (2663 loc) · 105 KB
/
odoc_html.ml
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Maxence Guesdon, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 2001 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(** Generation of html documentation.*)
let print_DEBUG s = print_string s ; print_newline ()
open Odoc_info
open Value
open Type
open Extension
open Exception
open Class
open Module
let with_parameter_list = ref false
let css_style = ref None
let index_only = ref false
let colorize_code = ref false
let html_short_functors = ref false
let charset = ref "iso-8859-1"
(** The functions used for naming files and html marks.*)
module Naming =
struct
(** The prefix for modules marks. *)
let mark_module = "MODULE"
(** The prefix for module type marks. *)
let mark_module_type = "MODULETYPE"
(** The prefix for types marks. *)
let mark_type = "TYPE"
(** The prefix for types elements (record fields or constructors). *)
let mark_type_elt = "TYPEELT"
(** The prefix for functions marks. *)
let mark_function = "FUN"
(** The prefix for extensions marks. *)
let mark_extension = "EXTENSION"
(** The prefix for exceptions marks. *)
let mark_exception = "EXCEPTION"
(** The prefix for values marks. *)
let mark_value = "VAL"
(** The prefix for attributes marks. *)
let mark_attribute = "ATT"
(** The prefix for methods marks. *)
let mark_method = "METHOD"
(** The prefix for code files. *)
let code_prefix = "code_"
(** The prefix for type files. *)
let type_prefix = "type_"
(** Return the two html files names for the given module or class name.*)
let html_files name =
let qual =
try
let i = String.rindex name '.' in
match name.[i + 1] with
| 'A'..'Z' -> ""
| _ -> "-c"
with Not_found -> ""
in
let prefix = name^qual in
let html_file = prefix^".html" in
let html_frame_file = prefix^"-frame.html" in
(html_file, html_frame_file)
(** Return the target for the given prefix and simple name. *)
let target pref simple_name = pref^simple_name
(** Return the complete link target (file#target) for the given prefix string and complete name.*)
let complete_target pref complete_name =
let simple_name = Name.simple complete_name in
let module_name =
let s = Name.father complete_name in
if s = "" then simple_name else s
in
let (html_file, _) = html_files module_name in
html_file^"#"^(target pref simple_name)
(**return the link target for the given module. *)
let module_target m = target mark_module (Name.simple m.m_name)
(**return the link target for the given module type. *)
let module_type_target mt = target mark_module_type (Name.simple mt.mt_name)
(** Return the link target for the given type. *)
let type_target t = target mark_type (Name.simple t.ty_name)
(** Return the link target for the given variant constructor. *)
let const_target t f =
let name = Printf.sprintf "%s.%s" (Name.simple t.ty_name) f.vc_name in
target mark_type_elt name
(** Return the link target for the given record field. *)
let recfield_target t f = target mark_type_elt
(Printf.sprintf "%s.%s" (Name.simple t.ty_name) f.rf_name)
(** Return the link target for the given inline record field. *)
let inline_recfield_target t c f = target mark_type_elt
(Printf.sprintf "%s.%s.%s" t c f.rf_name)
(** Return the link target for the given object field. *)
let objfield_target t f = target mark_type_elt
(Printf.sprintf "%s.%s" (Name.simple t.ty_name) f.of_name)
(** Return the complete link target for the given type. *)
let complete_type_target t = complete_target mark_type t.ty_name
let complete_recfield_target name =
let typ = Name.father name in
let field = Name.simple name in
Printf.sprintf "%s.%s" (complete_target mark_type_elt typ) field
let complete_const_target = complete_recfield_target
(** Return the link target for the given extension. *)
let extension_target x = target mark_extension (Name.simple x.xt_name)
(** Return the complete link target for the given extension. *)
let complete_extension_target x = complete_target mark_extension x.xt_name
(** Return the link target for the given exception. *)
let exception_target e = target mark_exception (Name.simple e.ex_name)
(** Return the complete link target for the given exception. *)
let complete_exception_target e = complete_target mark_exception e.ex_name
(** Return the link target for the given value. *)
let value_target v = target mark_value (Name.simple v.val_name)
(** Return the given value name where symbols accepted in infix values
are replaced by strings, to avoid clashes with the filesystem.*)
let subst_infix_symbols name =
let len = String.length name in
let buf = Buffer.create len in
let ch c = Buffer.add_char buf c in
let st s = Buffer.add_string buf s in
for i = 0 to len - 1 do
match name.[i] with
| '|' -> st "_pipe_"
| '<' -> st "_lt_"
| '>' -> st "_gt_"
| '@' -> st "_at_"
| '^' -> st "_exp_"
| '&' -> st "_amp_"
| '+' -> st "_plus_"
| '-' -> st "_minus_"
| '*' -> st "_star_"
| '/' -> st "_slash_"
| '$' -> st "_dollar_"
| '%' -> st "_percent_"
| '=' -> st "_equal_"
| ':' -> st "_column_"
| '~' -> st "_tilde_"
| '!' -> st "_bang_"
| '?' -> st "_questionmark_"
| c -> ch c
done;
Buffer.contents buf
(** Return the complete link target for the given value. *)
let complete_value_target v = complete_target mark_value v.val_name
(** Return the complete filename for the code of the given value. *)
let file_code_value_complete_target v =
code_prefix^mark_value^(subst_infix_symbols v.val_name)^".html"
(** Return the link target for the given attribute. *)
let attribute_target a = target mark_attribute (Name.simple a.att_value.val_name)
(** Return the complete link target for the given attribute. *)
let complete_attribute_target a = complete_target mark_attribute a.att_value.val_name
(** Return the complete filename for the code of the given attribute. *)
let file_code_attribute_complete_target a =
code_prefix^mark_attribute^a.att_value.val_name^".html"
(** Return the link target for the given method. *)
let method_target m = target mark_method (Name.simple m.met_value.val_name)
(** Return the complete link target for the given method. *)
let complete_method_target m = complete_target mark_method m.met_value.val_name
(** Return the complete filename for the code of the given method. *)
let file_code_method_complete_target m =
code_prefix^mark_method^m.met_value.val_name^".html"
(** Return the link target for the given label section. *)
let label_target l = target "" l
(** Return the complete link target for the given section label. *)
let complete_label_target l = complete_target "" l
(** Return the complete filename for the code of the type of the
given module or module type name. *)
let file_type_module_complete_target name =
type_prefix^name^".html"
(** Return the complete filename for the code of the
given module name. *)
let file_code_module_complete_target name =
code_prefix^name^".html"
(** Return the complete filename for the code of the type of the
given class or class type name. *)
let file_type_class_complete_target name =
type_prefix^name^".html"
end
module StringSet = Set.Make (struct
type t = string
let compare (x:t) y = compare x y
end)
(** A class with a method to colorize a string which represents OCaml code. *)
class ocaml_code =
object
method html_of_code b ?(with_pre=true) code =
Odoc_ocamlhtml.html_of_code b ~with_pre: with_pre code
end
let new_buf () = Buffer.create 1024
let bp = Printf.bprintf
let bs = Buffer.add_string
(** Generation of html code from text structures. *)
class virtual text =
object (self)
(** We want to display colorized code. *)
inherit ocaml_code
(** Escape the strings which would clash with html syntax, and
make some replacements (double newlines replaced by <br>). *)
method escape s = Odoc_ocamlhtml.escape_base s
method keep_alpha_num s =
let len = String.length s in
let buf = Buffer.create len in
for i = 0 to len - 1 do
match s.[i] with
'a'..'z' | 'A'..'Z' | '0'..'9' -> Buffer.add_char buf s.[i]
| _ -> ()
done;
Buffer.contents buf
(** Return a label created from the first sentence of a text. *)
method label_of_text t=
let t2 = Odoc_info.first_sentence_of_text t in
let s = Odoc_info.string_of_text t2 in
self#keep_alpha_num s
(** Create a label for the associated title.
Return the label specified by the user or a label created
from the title level and the first sentence of the title. *)
method create_title_label (n,label_opt,t) =
match label_opt with
Some s -> s
| None -> Printf.sprintf "%d_%s" n (self#label_of_text t)
(** Print the html code corresponding to the [text] parameter. *)
method html_of_text ?(with_p=false) b t =
if not with_p then
List.iter (self#html_of_text_element b) t
else
self#html_of_text_with_p b t
method html_of_text_with_p b t =
(* In order to enclose the generated text in <p> </p>, we first
output the content inside a inner buffer b', and then generate
the whole paragraph, if the content is not empty,
either at the end of the text, at a Newline element or when
encountering an element that cannot be part of a paragraph element
*)
let b' = Buffer.create 17 (* paragraph buffer *) in
let flush b' =
(* trim the inner string to avoid outputting empty <p></p> *)
let s = String.trim @@ Buffer.contents b' in
if s <> "" then
begin
bp b "<p>";
bs b s;
bp b "</p>\n"
end;
Buffer.clear b' in
let rec iter txt =
match txt with
| [] ->
flush b' (* flush b' at the end of the text *)
| (List _ | Enum _ | Title _ | CodePre _ | Verbatim _ | Center _
| Left _ | Right _ | Newline | Index_list ) as a :: q
(* these elements cannot be part of <p> element *)
->
flush b'; (* stop the current paragraph *)
self#html_of_text_element b a; (*output [a] directly on [b] *)
iter q
| a :: q -> self#html_of_text_element b' a; iter q
in
iter t
(** Print the html code for the [text_element] in parameter. *)
method html_of_text_element b txt =
print_DEBUG "text::html_of_text_element";
match txt with
| Odoc_info.Raw s -> self#html_of_Raw b s
| Odoc_info.Code s -> self#html_of_Code b s
| Odoc_info.CodePre s -> self#html_of_CodePre b s
| Odoc_info.Verbatim s -> self#html_of_Verbatim b s
| Odoc_info.Bold t -> self#html_of_Bold b t
| Odoc_info.Italic t -> self#html_of_Italic b t
| Odoc_info.Emphasize t -> self#html_of_Emphasize b t
| Odoc_info.Center t -> self#html_of_Center b t
| Odoc_info.Left t -> self#html_of_Left b t
| Odoc_info.Right t -> self#html_of_Right b t
| Odoc_info.List tl -> self#html_of_List b tl
| Odoc_info.Enum tl -> self#html_of_Enum b tl
| Odoc_info.Newline -> self#html_of_Newline b
| Odoc_info.Block t -> self#html_of_Block b t
| Odoc_info.Title (n, l_opt, t) -> self#html_of_Title b n l_opt t
| Odoc_info.Latex s -> self#html_of_Latex b s
| Odoc_info.Link (s, t) -> self#html_of_Link b s t
| Odoc_info.Ref (name, ref_opt, text_opt) ->
self#html_of_Ref b name ref_opt text_opt
| Odoc_info.Superscript t -> self#html_of_Superscript b t
| Odoc_info.Subscript t -> self#html_of_Subscript b t
| Odoc_info.Module_list l -> self#html_of_Module_list b l
| Odoc_info.Index_list -> self#html_of_Index_list b
| Odoc_info.Custom (s,t) -> self#html_of_custom_text b s t
| Odoc_info.Target (target, code) -> self#html_of_Target b ~target ~code
method html_of_custom_text _ _ _ = ()
method html_of_Target b ~target ~code =
if String.lowercase_ascii target = "html" then bs b code else ()
method html_of_Raw b s = bs b (self#escape s)
method html_of_Code b s =
if !colorize_code then
self#html_of_code b ~with_pre: false s
else
(
bs b "<code class=\"";
bs b Odoc_ocamlhtml.code_class ;
bs b "\">";
bs b (self#escape s);
bs b "</code>"
)
method html_of_CodePre =
let remove_useless_newlines s =
let len = String.length s in
let rec iter_first n =
if n >= len then
None
else
match s.[n] with
| '\n' -> iter_first (n+1)
| _ -> Some n
in
match iter_first 0 with
None -> ""
| Some first ->
let rec iter_last n =
if n <= first then
None
else
match s.[n] with
'\t' -> iter_last (n-1)
| _ -> Some n
in
match iter_last (len-1) with
None -> String.sub s first 1
| Some last -> String.sub s first ((last-first)+1)
in
fun b s ->
if !colorize_code then
(
bs b "<pre class=\"codepre\">";
self#html_of_code b (remove_useless_newlines s);
bs b "</pre>"
)
else
(
bs b "<pre class=\"codepre\"><code class=\"";
bs b Odoc_ocamlhtml.code_class;
bs b "\">" ;
bs b (self#escape (remove_useless_newlines s));
bs b "</code></pre>"
)
method html_of_Verbatim b s =
bs b "<pre class=\"verbatim\">";
bs b (self#escape s);
bs b "</pre>"
method html_of_Bold b t =
bs b "<b>";
self#html_of_text b t;
bs b "</b>"
method html_of_Italic b t =
bs b "<i>" ;
self#html_of_text b t;
bs b "</i>"
method html_of_Emphasize b t =
bs b "<em>" ;
self#html_of_text b t ;
bs b "</em>"
method html_of_Center b t =
bs b "<center>";
self#html_of_text b t;
bs b "</center>"
method html_of_Left b t =
bs b "<div align=left>";
self#html_of_text b t;
bs b "</div>"
method html_of_Right b t =
bs b "<div align=right>";
self#html_of_text b t;
bs b "</div>"
method html_of_List b tl =
bs b "<ul>\n";
List.iter
(fun t -> bs b "<li>"; self#html_of_text b t; bs b "</li>\n")
tl;
bs b "</ul>\n"
method html_of_Enum b tl =
bs b "<OL>\n";
List.iter
(fun t -> bs b "<li>"; self#html_of_text b t; bs b"</li>\n")
tl;
bs b "</OL>\n"
method html_of_Newline b = bs b "\n"
method html_of_Block b t =
bs b "<blockquote>\n";
self#html_of_text b t;
bs b "</blockquote>\n"
method html_of_Title b n label_opt t =
let label1 = self#create_title_label (n, label_opt, t) in
let (tag_o, tag_c) =
if n > 6 then
(Printf.sprintf "div class=\"h%d\"" (n+1), "div")
else
let t = Printf.sprintf "h%d" (n+1) in (t, t)
in
bs b "<";
bp b "%s id=\"%s\"" tag_o (Naming.label_target label1);
bs b ">";
self#html_of_text b t;
bs b "</";
bs b tag_c;
bs b ">"
method html_of_Latex _ _ = ()
(* don't care about LaTeX stuff in HTML. *)
method html_of_Link b s t =
bs b "<a href=\"";
bs b (self#escape s);
bs b "\">";
self#html_of_text b t;
bs b "</a>"
method html_of_Ref b name ref_opt text_opt =
match ref_opt with
None ->
let text =
match text_opt with
None -> [Odoc_info.Code name]
| Some t -> t
in
self#html_of_text b text
| Some kind ->
let h name = Odoc_info.Code (Odoc_info.use_hidden_modules name) in
let (target, text) =
match kind with
Odoc_info.RK_module
| Odoc_info.RK_module_type
| Odoc_info.RK_class
| Odoc_info.RK_class_type ->
let (html_file, _) = Naming.html_files name in
(html_file, h name)
| Odoc_info.RK_value -> (Naming.complete_target Naming.mark_value name, h name)
| Odoc_info.RK_type -> (Naming.complete_target Naming.mark_type name, h name)
| Odoc_info.RK_extension -> (Naming.complete_target Naming.mark_extension name, h name)
| Odoc_info.RK_exception -> (Naming.complete_target Naming.mark_exception name, h name)
| Odoc_info.RK_attribute -> (Naming.complete_target Naming.mark_attribute name, h name)
| Odoc_info.RK_method -> (Naming.complete_target Naming.mark_method name, h name)
| Odoc_info.RK_section t -> (Naming.complete_label_target name,
Odoc_info.Italic [Raw (Odoc_info.string_of_text t)])
| Odoc_info.RK_recfield -> (Naming.complete_recfield_target name, h name)
| Odoc_info.RK_const -> (Naming.complete_const_target name, h name)
in
let text =
match text_opt with
None -> [text]
| Some text -> text
in
bs b ("<a href=\""^target^"\">");
self#html_of_text b text;
bs b "</a>"
method html_of_Superscript b t =
bs b "<sup class=\"superscript\">";
self#html_of_text b t;
bs b "</sup>"
method html_of_Subscript b t =
bs b "<sub class=\"subscript\">";
self#html_of_text b t;
bs b "</sub>"
method virtual html_of_info_first_sentence : _
method html_of_Module_list b l =
bs b "\n<table class=\"indextable module-list\">\n";
List.iter
(fun name ->
bs b "<tr><td class=\"module\">";
(
try
let m =
List.find (fun m -> m.m_name = name) self#list_modules
in
let (html, _) = Naming.html_files m.m_name in
bp b "<a href=\"%s\">%s</a></td>" html m.m_name;
bs b "<td>";
self#html_of_info_first_sentence b m.m_info;
with
Not_found ->
Odoc_global.pwarning (Odoc_messages.cross_module_not_found name);
bp b "%s</td><td>" name
);
bs b "</td></tr>\n"
)
l;
bs b "</table>\n"
method html_of_Index_list b =
let index_if_not_empty l url m =
match l with
[] -> ()
| _ -> bp b "<li><a href=\"%s\">%s</a></li>\n" url m
in
bp b "<ul class=\"indexlist\">\n";
index_if_not_empty self#list_types self#index_types Odoc_messages.index_of_types;
index_if_not_empty self#list_extensions self#index_extensions Odoc_messages.index_of_extensions;
index_if_not_empty self#list_exceptions self#index_exceptions Odoc_messages.index_of_exceptions;
index_if_not_empty self#list_values self#index_values Odoc_messages.index_of_values;
index_if_not_empty self#list_attributes self#index_attributes Odoc_messages.index_of_attributes;
index_if_not_empty self#list_methods self#index_methods Odoc_messages.index_of_methods;
index_if_not_empty self#list_classes self#index_classes Odoc_messages.index_of_classes;
index_if_not_empty self#list_class_types self#index_class_types Odoc_messages.index_of_class_types;
index_if_not_empty self#list_modules self#index_modules Odoc_messages.index_of_modules;
index_if_not_empty self#list_module_types self#index_module_types Odoc_messages.index_of_module_types;
bp b "</ul>\n"
method virtual list_types : Odoc_info.Type.t_type list
method virtual index_types : string
method virtual list_extensions : Odoc_info.Extension.t_extension_constructor list
method virtual index_extensions : string
method virtual list_exceptions : Odoc_info.Exception.t_exception list
method virtual index_exceptions : string
method virtual list_values : Odoc_info.Value.t_value list
method virtual index_values : string
method virtual list_attributes : Odoc_info.Value.t_attribute list
method virtual index_attributes : string
method virtual list_methods : Odoc_info.Value.t_method list
method virtual index_methods : string
method virtual list_classes : Odoc_info.Class.t_class list
method virtual index_classes : string
method virtual list_class_types : Odoc_info.Class.t_class_type list
method virtual index_class_types : string
method virtual list_modules : Odoc_info.Module.t_module list
method virtual index_modules : string
method virtual list_module_types : Odoc_info.Module.t_module_type list
method virtual index_module_types : string
end
(** A class used to generate html code for info structures. *)
class virtual info =
object (self)
(** The list of pairs [(tag, f)] where [f] is a function taking
the [text] associated to [tag] and returning html code.
Add a pair here to handle a tag.*)
val mutable tag_functions = ([] : (string * (Odoc_info.text -> string)) list)
(** The method used to get html code from a [text]. *)
method virtual html_of_text :
?with_p:bool -> Buffer.t -> Odoc_info.text -> unit
(** Print html for an author list. *)
method html_of_author_list b l =
match l with
[] -> ()
| _ ->
bp b "<li><b>%s:</b> " Odoc_messages.authors;
self#html_of_text b [Raw (String.concat ", " l)];
bs b "</li>\n"
(** Print html code for the given optional version information.*)
method html_of_version_opt b v_opt =
match v_opt with
None -> ()
| Some v ->
bp b "<li><b>%s:</b> " Odoc_messages.version;
self#html_of_text b [Raw v];
bs b "</li>\n"
(** Print html code for the given optional since information.*)
method html_of_since_opt b s_opt =
match s_opt with
None -> ()
| Some s ->
bp b "<li><b>%s</b> " Odoc_messages.since;
self#html_of_text b [Raw s];
bs b "</li>\n"
(** Print html code for the given "before" information.*)
method html_of_before b l =
let f (v, text) =
bp b "<li><b>%s " Odoc_messages.before;
self#html_of_text b [Raw v];
bs b " </b> ";
self#html_of_text b text;
bs b "</li>\n"
in
List.iter f l
(** Print html code for the given list of raised exceptions.*)
method html_of_raised_exceptions b l =
match l with
[] -> ()
| (s, t) :: [] ->
bp b "<li><b>%s</b> <code>%s</code> "
Odoc_messages.raises
s;
self#html_of_text b t;
bs b "</li>\n"
| _ ->
bp b "<li><b>%s</b><ul>" Odoc_messages.raises;
List.iter
(fun (ex, desc) ->
bp b "<li><code>%s</code> " ex ;
self#html_of_text b desc;
bs b "</li>\n"
)
l;
bs b "</ul></li>\n"
(** Print html code for the given "see also" reference. *)
method html_of_see b (see_ref, t) =
let t_ref =
match see_ref with
Odoc_info.See_url s -> [ Odoc_info.Link (s, t) ]
| Odoc_info.See_file s -> (Odoc_info.Code s) :: (Odoc_info.Raw " ") :: t
| Odoc_info.See_doc s -> (Odoc_info.Italic [Odoc_info.Raw s]) :: (Odoc_info.Raw " ") :: t
in
self#html_of_text b t_ref
(** Print html code for the given list of "see also" references.*)
method html_of_sees b l =
match l with
[] -> ()
| see :: [] ->
bp b "<li><b>%s</b> " Odoc_messages.see_also;
self#html_of_see b see;
bs b "</li>\n"
| _ ->
bp b "<li><b>%s</b><ul>" Odoc_messages.see_also;
List.iter
(fun see ->
bs b "<li>" ;
self#html_of_see b see;
bs b "</li>\n"
)
l;
bs b "</ul></li>\n"
(** Print html code for the given optional return information.*)
method html_of_return_opt b return_opt =
match return_opt with
None -> ()
| Some s ->
bp b "<li><b>%s</b> " Odoc_messages.returns;
self#html_of_text b s;
bs b "</li>\n"
(** Print html code for the given list of custom tagged texts. *)
method html_of_custom b l =
List.iter
(fun (tag, text) ->
try
let f = List.assoc tag tag_functions in
Buffer.add_string b (f text)
with
Not_found ->
Odoc_info.warning (Odoc_messages.tag_not_handled tag)
)
l
(** Print html code for a description, except for the [i_params] field.
@param indent can be specified not to use the style of info comments;
default is [true].
*)
method html_of_info ?(cls="") ?(indent=true) b info_opt =
match info_opt with
None ->
()
| Some info ->
let module M = Odoc_info in
if indent then bs b ("<div class=\"info "^cls^"\">\n");
(
match info.M.i_deprecated with
None -> ()
| Some d ->
bs b "<div class=\"info-deprecated\">\n";
bs b "<span class=\"warning\">";
bs b Odoc_messages.deprecated ;
bs b "</span>" ;
self#html_of_text b d;
bs b "</div>\n"
);
(
match info.M.i_desc with
None -> ()
| Some d when d = [Odoc_info.Raw ""] -> ()
| Some d ->
bs b "<div class=\"info-desc\">\n";
self#html_of_text ~with_p:true b d;
bs b "</div>\n"
);
let b' = Buffer.create 17 in
self#html_of_author_list b' info.M.i_authors;
self#html_of_version_opt b' info.M.i_version;
self#html_of_before b' info.M.i_before;
self#html_of_since_opt b' info.M.i_since;
self#html_of_raised_exceptions b' info.M.i_raised_exceptions;
self#html_of_return_opt b' info.M.i_return_value;
self#html_of_sees b' info.M.i_sees;
self#html_of_custom b' info.M.i_custom;
if Buffer.length b' > 0 then
begin
bs b "<ul class=\"info-attributes\">\n";
Buffer.add_buffer b b';
bs b "</ul>\n"
end;
if indent then bs b "</div>\n"
(** Print html code for the first sentence of a description.
The titles and lists in this first sentence has been removed.*)
method html_of_info_first_sentence b info_opt =
match info_opt with
None -> ()
| Some info ->
let module M = Odoc_info in
let dep = info.M.i_deprecated <> None in
bs b "<div class=\"info\">\n";
if dep then bs b "<span class=\"deprecated\">";
(
match info.M.i_desc with
None -> ()
| Some d when d = [Odoc_info.Raw ""] -> ()
| Some d ->
self#html_of_text ~with_p:true b
(Odoc_info.text_no_title_no_list
(Odoc_info.first_sentence_of_text d));
bs b "\n"
);
if dep then bs b "</span>";
bs b "</div>\n"
end
let opt = Odoc_info.apply_opt
let print_concat b sep f =
let rec iter = function
[] -> ()
| [c] -> f c
| c :: q ->
f c;
bs b sep;
iter q
in
iter
let newline_to_indented_br s =
let len = String.length s in
let b = Buffer.create len in
for i = 0 to len - 1 do
match s.[i] with
'\n' -> Buffer.add_string b "<br> "
| c -> Buffer.add_char b c
done;
Buffer.contents b
module Generator =
struct
(** This class is used to create objects which can generate a simple html documentation. *)
class html =
object (self)
inherit text
inherit info
val mutable doctype =
"<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 4.01 Transitional//EN\">\n"
method character_encoding b =
bp b
"<meta content=\"text/html; charset=%s\" http-equiv=\"Content-Type\">\n"
!charset
method meta b =
self#character_encoding b;
bs b "<meta name=\"viewport\" content=\"width=device-width, initial-scale=1\">\n"
(** The default style options. *)
val mutable default_style_options =
[ ".keyword { font-weight : bold ; color : Red }" ;
".keywordsign { color : #C04600 }" ;
".comment { color : Green }" ;
".constructor { color : Blue }" ;
".type { color : #5C6585 }" ;
".string { color : Maroon }" ;
".warning { color : Red ; font-weight : bold }" ;
".info { margin-left : 3em; margin-right: 3em }" ;
".param_info { margin-top: 4px; margin-left : 3em; margin-right : 3em }" ;
".code { color : #465F91 ; }" ;
".typetable { border-style : hidden }" ;
".paramstable { border-style : hidden ; padding: 5pt 5pt}" ;
"tr { background-color : White }" ;
"td.typefieldcomment { background-color : #FFFFFF ; font-size: smaller ;}" ;
"div.sig_block {margin-left: 2em}" ;
"*:target { background: yellow; }" ;
"body {font: 13px sans-serif; color: black; text-align: left; padding: 5px; margin: 0}";
"h1 { font-size : 20pt ; text-align: center; }" ;
"h2 { font-size : 20pt ; text-align: center; }" ;
"h3 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #90BDFF ;"^
"padding: 2px; }" ;
"h4 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #90DDFF ;"^
"padding: 2px; }" ;
"h5 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #90EDFF ;"^
"padding: 2px; }" ;
"h6 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #90FDFF ;"^
"padding: 2px; }" ;
"div.h7 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #90BDFF ; "^
"padding: 2px; }" ;
"div.h8 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #E0FFFF ; "^
"padding: 2px; }" ;
"div.h9 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #F0FFFF ; "^
"padding: 2px; }" ;
"div.h10 { font-size : 20pt ; border: 1px solid #000000; "^
"margin-top: 5px; margin-bottom: 2px;"^
"text-align: center; background-color: #FFFFFF ; "^
"padding: 2px; }" ;
"a {color: #416DFF; text-decoration: none}";
"a:hover {background-color: #ddd; text-decoration: underline}";
"pre { margin-bottom: 4px; font-family: monospace; }" ;
"pre.verbatim, pre.codepre { }";
".indextable {border: 1px #ddd solid; border-collapse: collapse}";
".indextable td, .indextable th {border: 1px #ddd solid; min-width: 80px}";
".indextable td.module {background-color: #eee ; padding-left: 2px; padding-right: 2px}";
".indextable td.module a {color: #4E6272; text-decoration: none; display: block; width: 100%}";
".indextable td.module a:hover {text-decoration: underline; background-color: transparent}";
".deprecated {color: #888; font-style: italic}" ;
".indextable tr td div.info { margin-left: 2px; margin-right: 2px }" ;
"ul.indexlist { margin-left: 0; padding-left: 0;}";
"ul.indexlist li { list-style-type: none ; margin-left: 0; padding-left: 0; }";
"ul.info-attributes {list-style: none; margin: 0; padding: 0; }";
"div.info > p:first-child { margin-top:0; }";
"div.info-desc > p:first-child { margin-top:0; margin-bottom:0; }"
]
(** The style file for all pages. *)
val mutable style_file = "style.css"
(** The code to import the style. Initialized in [init_style]. *)
val mutable style = ""
(** The known types names.
Used to know if we must create a link to a type
when printing a type. *)
val mutable known_types_names = StringSet.empty
(** The known class and class type names.
Used to know if we must create a link to a class
or class type or not when printing a type. *)
val mutable known_classes_names = StringSet.empty
(** The known modules and module types names.
Used to know if we must create a link to a type or not
when printing a module type. *)
val mutable known_modules_names = StringSet.empty
method index_prefix =
if !Odoc_global.out_file = Odoc_messages.default_out_file then
"index"
else
Filename.basename !Odoc_global.out_file
(** The main file. *)
method index =
let p = self#index_prefix in
Printf.sprintf "%s.html" p
(** The file for the index of values. *)
method index_values = Printf.sprintf "%s_values.html" self#index_prefix
(** The file for the index of types. *)
method index_types = Printf.sprintf "%s_types.html" self#index_prefix
(** The file for the index of extensions. *)
method index_extensions = Printf.sprintf "%s_extensions.html" self#index_prefix
(** The file for the index of exceptions. *)
method index_exceptions = Printf.sprintf "%s_exceptions.html" self#index_prefix
(** The file for the index of attributes. *)
method index_attributes = Printf.sprintf "%s_attributes.html" self#index_prefix
(** The file for the index of methods. *)
method index_methods = Printf.sprintf "%s_methods.html" self#index_prefix
(** The file for the index of classes. *)
method index_classes = Printf.sprintf "%s_classes.html" self#index_prefix
(** The file for the index of class types. *)
method index_class_types = Printf.sprintf "%s_class_types.html" self#index_prefix
(** The file for the index of modules. *)
method index_modules = Printf.sprintf "%s_modules.html" self#index_prefix
(** The file for the index of module types. *)
method index_module_types = Printf.sprintf "%s_module_types.html" self#index_prefix