Skip to content

Commit 41d293f

Browse files
panglesdjonludlam
authored andcommitted
Improve namings for code block content parsing
1 parent f92fe52 commit 41d293f

File tree

1 file changed

+18
-17
lines changed

1 file changed

+18
-17
lines changed

src/parser/lexer.mll

Lines changed: 18 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,9 @@ let reference_token media start target input lexbuf =
109109
let content = media token_descr (Buffer.create 1024) 0 (Lexing.lexeme_start lexbuf) input lexbuf in
110110
`Media_with_replacement_text (target, kind, content)
111111

112-
let require_whitespace_first input start_offset text =
112+
(** Verbatims' content must be separated from their delimiters: [{v content v}]
113+
and not [{vcontentv}]. Such leading space is not part of the content. *)
114+
let verbatim_whitespace_first input start_offset text =
113115
match text.[0] with
114116
| ' ' -> String.sub text 1 (String.length text - 1)
115117
| '\t' | '\r' | '\n' -> text
@@ -122,17 +124,20 @@ let require_whitespace_first input start_offset text =
122124
Parse_error.no_leading_whitespace_in_verbatim;
123125
text
124126

125-
let strip_whitespace_last text =
127+
(** Verbatims' content must be separated from their delimiters: [{v content v}]
128+
and not [{vcontentv}]. Such leading space is not part of the content. *)
129+
let verbatim_whitespace_last text =
126130
match text.[String.length text - 1] with
127131
| ' ' -> String.sub text 0 (String.length text - 1)
128132
| '\t' | '\r' | '\n' -> text
129133
| exception Invalid_argument _ -> ""
130134
| _ -> text
131135

132-
(** [trim_leading_whitespace ~offset c] "unindents" [c] by the [offset] amount.
133-
If that is not possible (eg there is a non-whitespace line starting with
134-
less than [offset] whitespaces), it unindents as much as possible and raises
135-
a warning. *)
136+
(** [deindent ~what input ~start_offset s] "deindents" [s] by an offset computed
137+
from [start_offset] and [input], corresponding to the begining of a code
138+
block or verbatim. If that is not possible (eg there is a non-whitespace
139+
line starting with less than [offset] whitespaces), it unindents as much as
140+
possible and raises a warning. *)
136141
let deindent : what:string -> _ -> start_offset:_ -> string -> string =
137142
fun ~what input ~start_offset s ->
138143
let start_location = input.offset_to_location start_offset in
@@ -176,13 +181,9 @@ let deindent : what:string -> _ -> start_offset:_ -> string -> string =
176181
let lines = List.map (drop least_amount_of_whitespace) lines in
177182
String.concat "\n" lines
178183

179-
(** Removes at most one leading whitespace line, and at most one trailing empty
180-
line. This is in order to have the opening token and the first line of the
181-
content not on the same line.
182-
183-
If the leading line is not whitespace, indent this line as much as the
184-
opening token (to account for the offset to the left margin). *)
185-
let sanitize_code_block input ~what ~start_offset s =
184+
(** Implements the rules for code block as specified in [odoc_for_authors],
185+
section on code blocks and indentation. *)
186+
let code_block_content input ~what ~start_offset s =
186187
let start_location = input.offset_to_location start_offset in
187188
let indent = start_location.column in
188189
let rec handle_first_newline index =
@@ -212,9 +213,9 @@ let sanitize_code_block input ~what ~start_offset s =
212213

213214
let emit_verbatim input start_offset buffer =
214215
let t = Buffer.contents buffer in
215-
let t = require_whitespace_first input start_offset t in
216-
let t = strip_whitespace_last t in
217-
let t = sanitize_code_block input ~what:"verbatim" ~start_offset t in
216+
let t = verbatim_whitespace_first input start_offset t in
217+
let t = verbatim_whitespace_last t in
218+
let t = code_block_content input ~what:"verbatim" ~start_offset t in
218219
emit input (`Verbatim t) ~start_offset
219220

220221
(* The locations have to be treated carefully in this function. We need to ensure that
@@ -228,7 +229,7 @@ let emit_code_block ~start_offset content_offset input metadata delim terminator
228229
let c = Buffer.contents c in
229230
(* We first handle the case wehere there is no line at the beginning, then
230231
remove trailing, leading lines and deindent *)
231-
let c = sanitize_code_block input ~what:"code block" ~start_offset c in
232+
let c = code_block_content input ~what:"code block" ~start_offset c in
232233
let c =
233234
with_location_adjustments ~adjust_end_by:terminator
234235
~start_offset:content_offset

0 commit comments

Comments
 (0)