@@ -188,17 +188,16 @@ type surrounding =
188188 * Odoc_parser.Ast .inline_element Location_ .with_location list ]
189189
190190let rec non_link_inline_element :
191- status ->
192191 surrounding :surrounding ->
193192 Odoc_parser.Ast. inline_element with_location ->
194193 Comment. non_link_inline_element with_location =
195- fun status ~surrounding element ->
194+ fun ~surrounding element ->
196195 match element with
197196 | { value = #ast_leaf_inline_element ; _ } as element ->
198197 (leaf_inline_element element
199198 :> Comment. non_link_inline_element with_location)
200199 | { value = `Styled (style , content ); _ } ->
201- `Styled (style, non_link_inline_elements status ~surrounding content)
200+ `Styled (style, non_link_inline_elements ~surrounding content)
202201 |> Location. same element
203202 | ( { value = `Reference (_, _, content); _ }
204203 | { value = `Link (_ , content ); _ } ) as element ->
@@ -208,29 +207,26 @@ let rec non_link_inline_element :
208207 element.location
209208 |> Error. raise_warning;
210209
211- `Styled (`Emphasis , non_link_inline_elements status ~surrounding content)
210+ `Styled (`Emphasis , non_link_inline_elements ~surrounding content)
212211 |> Location. same element
213212
214- and non_link_inline_elements status ~surrounding elements =
215- List. map (non_link_inline_element status ~surrounding ) elements
213+ and non_link_inline_elements ~surrounding elements =
214+ List. map (non_link_inline_element ~surrounding ) elements
216215
217216let rec inline_element :
218- status ->
219217 Odoc_parser.Ast. inline_element with_location ->
220218 Comment. inline_element with_location =
221- fun status element ->
219+ fun element ->
222220 match element with
223221 | { value = #ast_leaf_inline_element ; _ } as element ->
224222 (leaf_inline_element element :> Comment.inline_element with_location )
225223 | { value = `Styled (style , content ); location } ->
226- `Styled (style, inline_elements status content) |> Location. at location
224+ `Styled (style, inline_elements content) |> Location. at location
227225 | { value = `Reference (kind , target , content ) as value ; location } -> (
228226 let { Location. value = target; location = target_location } = target in
229227 match Error. raise_warnings (Reference. parse target_location target) with
230228 | Result. Ok target ->
231- let content =
232- non_link_inline_elements status ~surrounding: value content
233- in
229+ let content = non_link_inline_elements ~surrounding: value content in
234230 Location. at location (`Reference (target, content))
235231 | Result. Error error ->
236232 Error. raise_warning error;
@@ -239,21 +235,20 @@ let rec inline_element :
239235 | `Simple -> `Code_span target
240236 | `With_text -> `Styled (`Emphasis , content)
241237 in
242- inline_element status (Location. at location placeholder))
238+ inline_element (Location. at location placeholder))
243239 | { value = `Link (target , content ) as value ; location } ->
244- `Link (target, non_link_inline_elements status ~surrounding: value content)
240+ `Link (target, non_link_inline_elements ~surrounding: value content)
245241 |> Location. at location
246242
247- and inline_elements status elements = List. map ( inline_element status) elements
243+ and inline_elements elements = List. map inline_element elements
248244
249245let rec nestable_block_element :
250- status ->
251246 Odoc_parser.Ast. nestable_block_element with_location ->
252247 Comment. nestable_block_element with_location =
253- fun status element ->
248+ fun element ->
254249 match element with
255250 | { value = `Paragraph content ; location } ->
256- Location. at location (`Paragraph (inline_elements status content))
251+ Location. at location (`Paragraph (inline_elements content))
257252 | { value = `Code_block { meta; delimiter = _; content; output }; location }
258253 ->
259254 let lang_tag =
@@ -264,7 +259,7 @@ let rec nestable_block_element :
264259 let outputs =
265260 match output with
266261 | None -> None
267- | Some l -> Some (List. map ( nestable_block_element status) l)
262+ | Some l -> Some (List. map nestable_block_element l)
268263 in
269264 Location. at location (`Code_block (lang_tag, content, outputs))
270265 | { value = `Math_block s ; location } -> Location. at location (`Math_block s)
@@ -286,13 +281,13 @@ let rec nestable_block_element :
286281 in
287282 Location. at location (`Modules modules)
288283 | { value = `List (kind , _syntax , items ); location } ->
289- `List (kind, List. map ( nestable_block_elements status) items)
284+ `List (kind, List. map nestable_block_elements items)
290285 |> Location. at location
291286 | { value = `Table ((grid , align ), (`Heavy | `Light )); location } ->
292287 let data =
293288 List. map
294289 (List. map (fun (cell , cell_type ) ->
295- (nestable_block_elements status cell, cell_type)))
290+ (nestable_block_elements cell, cell_type)))
296291 grid
297292 in
298293 `Table { Comment. data; align } |> Location. at location
@@ -312,17 +307,15 @@ let rec nestable_block_element :
312307 | `With_text ->
313308 `Styled (`Emphasis , [ `Word content |> Location. at location ])
314309 in
315- `Paragraph
316- (inline_elements status [ placeholder |> Location. at location ])
310+ `Paragraph (inline_elements [ placeholder |> Location. at location ])
317311 |> Location. at location
318312 in
319313 match Error. raise_warnings (Reference. parse_asset href_location href) with
320314 | Result. Ok target ->
321315 `Media (`Reference target, m, content) |> Location. at location
322316 | Result. Error error -> fallback error)
323317
324- and nestable_block_elements status elements =
325- List. map (nestable_block_element status) elements
318+ and nestable_block_elements elements = List. map nestable_block_element elements
326319
327320let tag :
328321 location :Location. span ->
@@ -339,26 +332,23 @@ let tag :
339332 let ok t = Result. Ok (Location. at location (`Tag t)) in
340333 match tag with
341334 | (`Author _ | `Since _ | `Version _ ) as tag -> ok tag
342- | `Deprecated content ->
343- ok (`Deprecated (nestable_block_elements status content))
335+ | `Deprecated content -> ok (`Deprecated (nestable_block_elements content))
344336 | `Param (name , content ) ->
345- ok (`Param (name, nestable_block_elements status content))
337+ ok (`Param (name, nestable_block_elements content))
346338 | `Raise (name , content ) -> (
347339 match Error. raise_warnings (Reference. parse location name) with
348340 (* TODO: location for just name * )
349341 | Result. Ok target ->
350- ok
351- (`Raise
352- (`Reference (target, [] ), nestable_block_elements status content))
342+ ok (`Raise (`Reference (target, [] ), nestable_block_elements content))
353343 | Result. Error error ->
354344 Error. raise_warning error;
355345 let placeholder = `Code_span name in
356- ok (`Raise (placeholder, nestable_block_elements status content)))
357- | `Return content -> ok (`Return (nestable_block_elements status content))
346+ ok (`Raise (placeholder, nestable_block_elements content)))
347+ | `Return content -> ok (`Return (nestable_block_elements content))
358348 | `See (kind , target , content ) ->
359- ok (`See (kind, target, nestable_block_elements status content))
349+ ok (`See (kind, target, nestable_block_elements content))
360350 | `Before (version , content ) ->
361- ok (`Before (version, nestable_block_elements status content))
351+ ok (`Before (version, nestable_block_elements content))
362352
363353(* When the user does not give a section heading a label (anchor), we generate
364354 one from the text in the heading. This is the common case. This involves
@@ -423,7 +413,7 @@ let section_heading :
423413 fun status ~top_heading_level location heading ->
424414 let (`Heading (level, label, content)) = heading in
425415
426- let text = inline_elements status content in
416+ let text = inline_elements content in
427417
428418 let heading_label_explicit, label =
429419 match label with
@@ -491,7 +481,7 @@ let top_level_block_elements status ast_elements =
491481
492482 match ast_element with
493483 | { value = #Odoc_parser.Ast. nestable_block_element ; _ } as element ->
494- let element = nestable_block_element status element in
484+ let element = nestable_block_element element in
495485 let element = (element :> Comment.block_element with_location ) in
496486 traverse ~top_heading_level
497487 (element :: comment_elements_acc)
0 commit comments