Skip to content

Commit

Permalink
Html: Fix stack overflow computing source code spans
Browse files Browse the repository at this point in the history
  • Loading branch information
Julow authored and jonludlam committed Jan 16, 2025
1 parent f83e69a commit f4b81ef
Showing 1 changed file with 3 additions and 4 deletions.
7 changes: 3 additions & 4 deletions src/html/html_source.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
open Odoc_utils
module HLink = Link
open Odoc_document.Types
open Tyxml
Expand All @@ -23,7 +24,7 @@ let html_of_doc ~config ~resolve docs =
| Source_page.Plain_code s -> [ txt s ]
| Tagged_code (info, docs) -> (
let is_in_a = match info with Link _ -> true | _ -> is_in_a in
let children = List.concat @@ (List.rev_map (doc_to_html ~is_in_a) docs |> List.rev) in
let children = List.concat_map (doc_to_html ~is_in_a) docs in
match info with
| Syntax tok -> [ span ~a:[ a_class [ tok ] ] children ]
(* Currently, we do not render links to documentation *)
Expand All @@ -33,9 +34,7 @@ let html_of_doc ~config ~resolve docs =
[ a ~a:[ a_href href ] children ]
| Anchor lbl -> [ span ~a:[ a_id lbl ] children ])
in
let span_content_l = List.rev_map (doc_to_html ~is_in_a:false) docs |> List.rev in
(* This is List.concat, tail recursive version *)
let span_content = List.fold_left (fun acc x -> List.rev_append x acc) [] span_content_l |> List.rev in
let span_content = List.concat_map (doc_to_html ~is_in_a:false) docs in
span ~a:[] span_content

let count_lines_in_string s =
Expand Down

0 comments on commit f4b81ef

Please sign in to comment.