Skip to content

Commit b7f7bbc

Browse files
committed
Parser: Ensure parser can be called concurrently
1 parent 409b10e commit b7f7bbc

File tree

3 files changed

+18
-11
lines changed

3 files changed

+18
-11
lines changed

src/parser/lexer.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ type input = {
55
offset_to_location : int -> Loc.point;
66
warnings : Warning.t list ref;
77
lexbuf : Lexing.lexbuf;
8+
string_buffer : Buffer.t;
89
}
910

1011
val token : input -> Lexing.lexbuf -> Token.t Loc.with_location

src/parser/lexer.mll

Lines changed: 9 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -41,10 +41,9 @@ type input = {
4141
offset_to_location : int -> Loc.point;
4242
warnings : Warning.t list ref;
4343
lexbuf : Lexing.lexbuf;
44+
string_buffer : Buffer.t;
4445
}
4546

46-
let string_buffer = Buffer.create 256
47-
4847
let with_location_adjustments
4948
k input ?start_offset ?adjust_start_by ?end_offset ?adjust_end_by value =
5049

@@ -728,13 +727,13 @@ and bad_markup_recovery start_offset input = parse
728727
if necessary. Using the missing cases will cause a warning *)
729728
and string input = parse
730729
| '\"'
731-
{ let result = Buffer.contents string_buffer in
732-
Buffer.clear string_buffer;
730+
{ let result = Buffer.contents input.string_buffer in
731+
Buffer.clear input.string_buffer;
733732
result }
734733
| '\\' newline [' ' '\t']*
735734
{ string input lexbuf }
736735
| '\\' (['\\' '\'' '\"' 'n' 't' 'b' 'r' ' '] as c)
737-
{ Buffer.add_char string_buffer
736+
{ Buffer.add_char input.string_buffer
738737
(match c with
739738
| '\\' -> '\\'
740739
| '\'' -> '\''
@@ -747,24 +746,24 @@ and string input = parse
747746
| _ -> assert false);
748747
string input lexbuf }
749748
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9']
750-
{ Buffer.add_char string_buffer (char_for_decimal_code input lexbuf 1);
749+
{ Buffer.add_char input.string_buffer (char_for_decimal_code input lexbuf 1);
751750
string input lexbuf }
752751
| '\\' (_ as c)
753752
{ warning input (Parse_error.should_not_be_escaped c);
754-
Buffer.add_char string_buffer c;
753+
Buffer.add_char input.string_buffer c;
755754
string input lexbuf }
756755
| eof
757756
{ warning input Parse_error.truncated_string;
758-
Buffer.contents string_buffer }
757+
Buffer.contents input.string_buffer }
759758
| (_ as c)
760-
{ Buffer.add_char string_buffer c;
759+
{ Buffer.add_char input.string_buffer c;
761760
string input lexbuf }
762761
763762
and code_block_metadata_atom input = parse
764763
| '"'
765764
{
766765
let start_offset = Lexing.lexeme_start input.lexbuf in
767-
Buffer.clear string_buffer;
766+
Buffer.clear input.string_buffer;
768767
let s = string input lexbuf in
769768
with_location_adjustments ~start_offset (fun _ -> Loc.at) input s }
770769
| (tag_unquoted_atom as value)

src/parser/odoc_parser.ml

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -103,13 +103,20 @@ let position_of_point : t -> Loc.point -> Lexing.position =
103103
let parse_comment ~location ~text =
104104
let warnings = ref [] in
105105
let reversed_newlines = reversed_newlines ~input:text in
106+
let string_buffer = Buffer.create 256 in
106107
let token_stream =
107108
let lexbuf = Lexing.from_string text in
108109
let offset_to_location =
109110
offset_to_location ~reversed_newlines ~comment_location:location
110111
in
111112
let input : Lexer.input =
112-
{ file = location.Lexing.pos_fname; offset_to_location; warnings; lexbuf }
113+
{
114+
file = location.Lexing.pos_fname;
115+
offset_to_location;
116+
warnings;
117+
lexbuf;
118+
string_buffer;
119+
}
113120
in
114121
Stream.from (fun _token_index -> Some (Lexer.token input lexbuf))
115122
in

0 commit comments

Comments
 (0)