Skip to content

Commit e5cb05f

Browse files
author
Guillaume Petiot
authored
Add support for tables (#893)
1 parent 72ac2cf commit e5cb05f

23 files changed

+642
-33
lines changed

CHANGES.md

+1
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ UNRELEASED
33

44
Additions
55
- Source code rendering (@Julow, @panglesd, #909)
6+
- Handle tables markup (@panglesd, @gpetiot, #893)
67

78
Bugfixes
89
- Fix `--hidden` not always taken into account (@panglesd, #940)

doc/ocamldoc_differences.mld

+2-1
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ can be seen rendered by [odoc] {{!Odoc_examples.Markup.Foo}here}.
1313
The following describes the changes between what [odoc] understands and what’s in the OCaml manual.
1414

1515
- Heading levels are more restrictive. In the manual, it suggests any whole number is acceptable. In [odoc],
16-
we follow the HTML spec in allowing headings from 1-6, and we also allow heading level [0] for the title
16+
similarly to the HTML spec, we allow headings from 1-5, and heading level [0] for the title
1717
of [.mld] files. [odoc] emits a warning for heading levels outside this range and caps them.
1818

1919
{3 Omissions}
@@ -29,6 +29,7 @@ The following describes the changes between what [odoc] understands and what’s
2929
An other difference is that documentation starting with a heading or something that is not a paragraph won't have a synopsis ({{:https://github.com/ocaml/odoc/pull/643}github issue}).
3030

3131
{3 Improvements}
32+
- [odoc] supports writing mathematics and tables with a specific syntax.
3233
- [odoc] has a better mechanism for disambiguating references in comments. See 'reference syntax' later in this document.
3334
- Built-in support for standalone [.mld] files. These are documents using the OCamldoc markup, but they’re rendered as distinct pages.
3435
- Structured output: [odoc] can produce output in a structured directory tree rather a set of files.

doc/odoc_for_authors.mld

+68
Original file line numberDiff line numberDiff line change
@@ -542,6 +542,74 @@ in block form this becomes:
542542
See the {{:https://katex.org/docs/supported.html}KaTeX documentation} for the
543543
HTML mode LaTeX support status.
544544

545+
{2 Tables}
546+
547+
Odoc 2.3 introduced new markup for tables. This markup comes in two flavors: the light syntax, and the heavy syntax.
548+
549+
The heavy syntax uses several markup: [{table ...}] to define a table, [{tr ...}] to define a row, and [{th ...}] and [{td ...}] to respectively define a header cell and a data cell.
550+
Direct children of tables have to be rows, and direct children of rows have to be cells. Similarly, rows have to be direct children of tables, and cells direct children of row. Cells can contain any markup.
551+
552+
For instance, the following table:
553+
554+
{[
555+
{table
556+
{tr
557+
{th Header 1}
558+
{th Header 2}
559+
{th Header 3}
560+
}
561+
{tr
562+
{td Cell 1}
563+
{td Cell with {e emphasized content}}
564+
{td {v a block v} }
565+
}
566+
}
567+
]}
568+
569+
would render as
570+
571+
{table
572+
{tr
573+
{th Header 1}
574+
{th Header 2}
575+
{th Header 3}
576+
}
577+
{tr
578+
{td Cell 1}
579+
{td Cell with {e emphasized content}}
580+
{td {v a block v} }
581+
}
582+
}
583+
584+
585+
The light syntax has the advantages of being simple to read, even as plain text. It is very similar to the {{:https://github.github.com/gfm/#tables-extension-}GFM Markdown syntax}, with the exception that it has to be enclosed in [{t ...}], and that the inline markup is the ocamldoc one. It supports alignment for columns using the [:] notation, from the GFM syntax: [---] is the default alignment, [:--] left-aligned, [--:] right-aligned and [:---:] is centered.
586+
587+
The following table, in light syntax:
588+
589+
{[
590+
{t
591+
| Header 1 | Header 2 | Header 3 | Header 4|
592+
| :------: | --------:|:---------|---------|
593+
| centered | right | left | default |
594+
omitted | bar at | start and| finish
595+
| {e emph} | and | unaligned | bars |
596+
}
597+
]}
598+
599+
would render as
600+
601+
{t
602+
| Header 1 | Header 2 | Header 3 | Header 4|
603+
| :------: | --------:|:---------|---------|
604+
| centered | right | left | default |
605+
omitted | bar at | start and| finish
606+
| {e emph} | and | unaligned | bars |
607+
}
608+
609+
The light syntax has the advantages of being arguably more readable for small tables, when viewing the source file directly. However, its content is restricted (for instance, no new line is allowed).
610+
The heavy syntax is easier to write, can be more readable for big tables, and supports having any kind of content inside. It does not support alignment (yet).
611+
612+
545613
{2 Stop Comments}
546614

547615
The special comment:

odoc.opam

+4
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,10 @@ Odoc is a documentation generator for OCaml. It reads doc comments,
2424
delimited with `(** ... *)`, and outputs HTML.
2525
"""
2626

27+
pin-depends: [
28+
["odoc-parser.dev" "git+https://github.com/ocaml-doc/odoc-parser.git#f98cfe3"]
29+
]
30+
2731
depends: [
2832
"odoc-parser" {>= "2.0.0"}
2933
"astring"

src/document/comment.ml

+33
Original file line numberDiff line numberDiff line change
@@ -258,6 +258,39 @@ let rec nestable_block_element : Comment.nestable_block_element -> Block.one =
258258
in
259259
let items = List.map f items in
260260
block @@ Block.List (kind, items)
261+
| `Table { data; align } ->
262+
let data =
263+
List.map
264+
(List.map (fun (cell, cell_type) ->
265+
(nestable_block_element_list cell, cell_type)))
266+
data
267+
in
268+
let generate_align data =
269+
let max (a : int) b = if a < b then b else a in
270+
(* Length of the longest line of the table *)
271+
let max_length =
272+
List.fold_left (fun m l -> max m (List.length l)) 0 data
273+
in
274+
let rec list_init i =
275+
if i <= 0 then [] else Table.Default :: list_init (i - 1)
276+
in
277+
list_init max_length
278+
in
279+
let align =
280+
match align with
281+
| None -> generate_align data
282+
| Some align ->
283+
List.map
284+
(function
285+
| None -> Table.Default
286+
| Some `Right -> Right
287+
| Some `Left -> Left
288+
| Some `Center -> Center)
289+
align
290+
(* We should also check wellness of number of table cells vs alignment,
291+
and raise warnings *)
292+
in
293+
block @@ Table { data; align }
261294

262295
and paragraph : Comment.paragraph -> Block.one = function
263296
| [ { value = `Raw_markup (target, s); _ } ] ->

src/document/doctree.ml

+2
Original file line numberDiff line numberDiff line change
@@ -384,6 +384,8 @@ end = struct
384384
| Inline x -> inline x
385385
| Paragraph x -> inline x
386386
| List (_, x) -> List.exists block x
387+
| Table { data; align = _ } ->
388+
List.exists (List.exists (fun (cell, _) -> block cell)) data
387389
| Description x -> description x
388390
| Math _ -> true
389391
| Source _ | Verbatim _ | Raw_markup _ -> false

src/document/types.ml

+11
Original file line numberDiff line numberDiff line change
@@ -89,11 +89,22 @@ and Block : sig
8989
| Math of Math.t
9090
| Verbatim of string
9191
| Raw_markup of Raw_markup.t
92+
| Table of t Table.t
9293

9394
and list_type = Ordered | Unordered
9495
end =
9596
Block
9697

98+
and Table : sig
99+
type alignment = Left | Center | Right | Default
100+
101+
type 'a t = {
102+
data : ('a * [ `Header | `Data ]) list list;
103+
align : alignment list;
104+
}
105+
end =
106+
Table
107+
97108
and DocumentedSrc : sig
98109
type 'a documented = {
99110
attrs : Class.t;

src/html/generator.ml

+35
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,14 @@ let heading ~config ~resolve (h : Heading.t) =
177177
in
178178
mk ~a (anchor @ content @ source_link)
179179

180+
let text_align = function
181+
| Table.Left -> [ Html.a_style "text-align:left" ]
182+
| Center -> [ Html.a_style "text-align:center" ]
183+
| Right -> [ Html.a_style "text-align:right" ]
184+
| Default -> []
185+
186+
let cell_kind = function `Header -> Html.th | `Data -> Html.td
187+
180188
let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
181189
let as_flow x = (x : phrasing Html.elt list :> flow Html.elt list) in
182190
let one (t : Block.one) =
@@ -192,6 +200,10 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
192200
| List (typ, l) ->
193201
let mk = match typ with Ordered -> Html.ol | Unordered -> Html.ul in
194202
mk_block mk (List.map (fun x -> Html.li (block ~config ~resolve x)) l)
203+
| Table t ->
204+
mk_block ~extra_class:[ "odoc-table" ]
205+
(fun ?a x -> Html.table ?a x)
206+
(mk_rows ~config ~resolve t)
195207
| Description l ->
196208
let item i =
197209
let a = class_ i.Description.attr in
@@ -213,6 +225,29 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
213225
in
214226
Utils.list_concat_map l ~f:one
215227

228+
and mk_rows ~config ~resolve { align; data } =
229+
let mk_row row =
230+
let mk_cell ~align (x, h) =
231+
let a = text_align align in
232+
cell_kind ~a h (block ~config ~resolve x)
233+
in
234+
let alignment align =
235+
match align with align :: q -> (align, q) | [] -> (Table.Default, [])
236+
(* Second case is for recovering from a too short alignment list. A
237+
warning should have been raised when loading the doc-comment. *)
238+
in
239+
let acc, _align =
240+
List.fold_left
241+
(fun (acc, aligns) (x, h) ->
242+
let align, aligns = alignment aligns in
243+
let cell = mk_cell ~align (x, h) in
244+
(cell :: acc, aligns))
245+
([], align) row
246+
in
247+
Html.tr (List.rev acc)
248+
in
249+
List.map mk_row data
250+
216251
(* This coercion is actually sound, but is not currently accepted by Tyxml.
217252
See https://github.com/ocsigen/tyxml/pull/265 for details
218253
Can be replaced by a simple type coercion once this is fixed

src/html_support_files/odoc.css

+16
Original file line numberDiff line numberDiff line change
@@ -701,6 +701,22 @@ td.def-doc *:first-child {
701701
padding-left: 12px;
702702
}
703703

704+
/* Tables */
705+
706+
.odoc-table {
707+
margin: 1em;
708+
}
709+
710+
.odoc-table td, .odoc-table th {
711+
padding-left: 0.5em;
712+
padding-right: 0.5em;
713+
border: 1px solid black;
714+
}
715+
716+
.odoc-table th {
717+
font-weight: bold;
718+
}
719+
704720
/* Mobile adjustements. */
705721

706722
@media only screen and (max-width: 110ex) {

0 commit comments

Comments
 (0)