Skip to content

Commit 0e6e3ae

Browse files
committed
Handle language tag on code blocks
Pass the language tag through the model and to highlightjs in the html generator. The value is ignored in other backends.
1 parent e8e3b81 commit 0e6e3ae

File tree

11 files changed

+55
-35
lines changed

11 files changed

+55
-35
lines changed

odoc.opam

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ delimited with `(** ... *)`, and outputs HTML.
2525
"""
2626

2727
depends: [
28-
"odoc-parser" {>= "0.9.0"}
28+
"odoc-parser" {>= "1.0.0"}
2929
"astring"
3030
"cmdliner" {>= "1.0.0"}
3131
"cppo" {build & >= "1.1.0"}

src/document/codefmt.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -222,7 +222,7 @@ let code ?attr f = [ inline ?attr @@ Inline.Source (render f) ]
222222

223223
let documentedSrc f = [ DocumentedSrc.Code (render f) ]
224224

225-
let codeblock ?attr f = [ block ?attr @@ Block.Source (render f) ]
225+
let codeblock ?attr f = [ block ?attr @@ Block.Source (None, render f) ]
226226

227227
let keyword keyword ppf = pf ppf "@{<keyword>%s@}" keyword
228228

src/document/comment.ml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -196,8 +196,9 @@ let rec nestable_block_element : Comment.nestable_block_element -> Block.one =
196196
fun content ->
197197
match content with
198198
| `Paragraph p -> paragraph p
199-
| `Code_block code ->
200-
block @@ Source (source_of_code (Odoc_model.Location_.value code))
199+
| `Code_block (lang_tag, code) ->
200+
block
201+
@@ Source (lang_tag, source_of_code (Odoc_model.Location_.value code))
201202
| `Verbatim s -> block @@ Verbatim s
202203
| `Modules ms -> module_references ms
203204
| `List (kind, items) ->

src/document/types.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -64,6 +64,8 @@ end =
6464
Heading
6565

6666
and Block : sig
67+
type lang_tag = string option
68+
6769
type t = one list
6870

6971
and one = { attr : Class.t; desc : desc }
@@ -73,7 +75,7 @@ and Block : sig
7375
| Paragraph of Inline.t
7476
| List of list_type * t list
7577
| Description of Description.t
76-
| Source of Source.t
78+
| Source of lang_tag * Source.t
7779
| Verbatim of string
7880
| Raw_markup of Raw_markup.t
7981

src/html/generator.ml

Lines changed: 25 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -165,32 +165,37 @@ let heading ~resolve (h : Heading.t) =
165165
let rec block ~resolve (l : Block.t) : flow Html.elt list =
166166
let as_flow x = (x : phrasing Html.elt list :> flow Html.elt list) in
167167
let one (t : Block.one) =
168-
let a = class_ t.attr in
168+
let mk_block ?(extra_class = []) mk content =
169+
let a = Some (class_ (extra_class @ t.attr)) in
170+
[ mk ?a content ]
171+
in
169172
match t.desc with
170173
| Inline i ->
171-
if a = [] then as_flow @@ inline ~resolve i
172-
else [ Html.span ~a (inline ~resolve i) ]
173-
| Paragraph i -> [ Html.p ~a (inline ~resolve i) ]
174+
if t.attr = [] then as_flow @@ inline ~resolve i
175+
else mk_block Html.span (inline ~resolve i)
176+
| Paragraph i -> mk_block Html.p (inline ~resolve i)
174177
| List (typ, l) ->
175178
let mk = match typ with Ordered -> Html.ol | Unordered -> Html.ul in
176-
[ mk ~a (List.map (fun x -> Html.li (block ~resolve x)) l) ]
179+
mk_block mk (List.map (fun x -> Html.li (block ~resolve x)) l)
177180
| Description l ->
178-
[
179-
(let item i =
180-
let a = class_ i.Description.attr in
181-
let term =
182-
(inline ~resolve i.Description.key
183-
: phrasing Html.elt list
184-
:> flow Html.elt list)
185-
in
186-
let def = block ~resolve i.Description.definition in
187-
Html.li ~a (term @ (Html.txt " " :: def))
188-
in
189-
Html.ul ~a (List.map item l));
190-
]
181+
let item i =
182+
let a = class_ i.Description.attr in
183+
let term =
184+
(inline ~resolve i.Description.key
185+
: phrasing Html.elt list
186+
:> flow Html.elt list)
187+
in
188+
let def = block ~resolve i.Description.definition in
189+
Html.li ~a (term @ (Html.txt " " :: def))
190+
in
191+
mk_block Html.ul (List.map item l)
191192
| Raw_markup r -> raw_markup r
192-
| Verbatim s -> [ Html.pre ~a [ Html.txt s ] ]
193-
| Source c -> [ Html.pre ~a (source (inline ~resolve) c) ]
193+
| Verbatim s -> mk_block Html.pre [ Html.txt s ]
194+
| Source (lang_tag, c) ->
195+
let extra_class =
196+
match lang_tag with None -> [] | Some lang -> [ "language-" ^ lang ]
197+
in
198+
mk_block ~extra_class Html.pre (source (inline ~resolve) c)
194199
in
195200
Utils.list_concat_map l ~f:one
196201

src/latex/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -308,7 +308,7 @@ let rec block ~in_source (l : Block.t) =
308308
]
309309
| Raw_markup r -> raw_markup r
310310
| Verbatim s -> [ Verbatim s ]
311-
| Source c -> non_empty_block_code c
311+
| Source (_, c) -> non_empty_block_code c
312312
in
313313
list_concat_map l ~f:one
314314

src/manpage/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -331,7 +331,7 @@ let rec block (l : Block.t) =
331331
indent 2 (str "@" ++ key ++ str ":" ++ sp ++ def)
332332
in
333333
list ~sep:break (List.map f descrs) ++ continue rest
334-
| Source content ->
334+
| Source (_, content) ->
335335
env "EX" "EE" "" (source_code content) ++ continue rest
336336
| Verbatim content -> env "EX" "EE" "" (str "%s" content) ++ continue rest
337337
| Raw_markup t -> raw_markup t ++ continue rest)

src/model/comment.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ type module_reference = {
4040

4141
type nestable_block_element =
4242
[ `Paragraph of paragraph
43-
| `Code_block of string with_location
43+
| `Code_block of string option * string with_location
4444
| `Verbatim of string
4545
| `Modules of module_reference list
4646
| `List of

src/model/semantics.ml

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -227,8 +227,13 @@ let rec nestable_block_element :
227227
match element with
228228
| { value = `Paragraph content; location } ->
229229
Location.at location (`Paragraph (inline_elements status content))
230-
| { value = `Code_block (_, code); _ } ->
231-
Location.same element (`Code_block code)
230+
| { value = `Code_block (metadata, code); location } ->
231+
let lang_tag =
232+
match metadata with
233+
| Some ({ Location.value; _ }, _) -> Some value
234+
| None -> None
235+
in
236+
Location.at location (`Code_block (lang_tag, code))
232237
| { value = `Verbatim _; _ } as element -> element
233238
| { value = `Modules modules; location } ->
234239
let modules =

src/model_desc/comment_desc.ml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ and general_link_content = general_inline_element with_location list
1818

1919
type general_block_element =
2020
[ `Paragraph of general_link_content
21-
| `Code_block of string with_location
21+
| `Code_block of string option * string with_location
2222
| `Verbatim of string
2323
| `Modules of Comment.module_reference list
2424
| `List of
@@ -100,7 +100,8 @@ let rec block_element : general_block_element t =
100100
Variant
101101
(function
102102
| `Paragraph x -> C ("`Paragraph", x, link_content)
103-
| `Code_block x -> C ("`Code_block", ignore_loc x, string)
103+
| `Code_block (x1, x2) ->
104+
C ("`Code_block", (x1, ignore_loc x2), Pair (Option string, string))
104105
| `Verbatim x -> C ("`Verbatim", x, string)
105106
| `Modules x -> C ("`Modules", x, List module_reference)
106107
| `List (x1, x2) ->

0 commit comments

Comments
 (0)