Source file pb_parsing.ml
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
module Loc = Pb_location
module Parsing_util = Pb_parsing_util
module Pt = Pb_parsing_parse_tree
let string_of_token =
let open Pb_parsing_parser in
function
| T_required -> "required"
| T_optional -> "optional"
| T_repeated -> "repeated"
| T_one_of _ -> "oneof"
| T_message -> "message"
| T_enum -> "enum"
| T_package -> "package"
| T_import _ -> "import"
| T_public -> "public"
| T_option -> "option"
| T_extensions -> "extensions"
| T_extend -> "extend"
| T_reserved -> "reserved"
| T_returns -> "returns"
| T_rpc -> "rpc"
| T_service -> "service"
| T_stream -> "stream"
| T_syntax -> "syntax"
| T_to -> "to"
| T_max -> "max"
| T_map -> "map"
| T_rbrace -> "}"
| T_lbrace -> "{"
| T_rbracket -> "]"
| T_lbracket -> "["
| T_rparen -> ")"
| T_lparen -> "("
| T_greater -> ">"
| T_less -> "<"
| T_equal -> "="
| T_semi -> ";"
| T_colon -> ":"
| T_comma -> ","
| T_string s -> Printf.sprintf "%S" s
| T_int i -> string_of_int i
| T_float f -> string_of_float f
| T_ident (_, s) -> s
| T_eof -> "<EOF>"
let custom_lexer_with_buffer buf_size =
let token_buffer = Queue.create () in
let next_token lexbuf =
let token = Pb_parsing_lexer.lexer lexbuf in
Queue.add token token_buffer;
if Queue.length token_buffer > buf_size then
Queue.take token_buffer |> ignore;
token
in
let error_context_tokens () =
let context =
Queue.fold (fun acc tok -> tok :: acc) [] token_buffer
|> List.rev |> List.map string_of_token |> String.concat " "
in
Printf.sprintf "%s <<< HERE" context
in
next_token, error_context_tokens
let parse_single_file (file_name, file_content) =
let lexbuf = Lexing.from_string file_content in
let pos = lexbuf.Lexing.lex_curr_p in
lexbuf.Lexing.lex_curr_p <- Lexing.{ pos with pos_fname = file_name };
let buffer_size =
5
in
let next_token, error_context_tokens = custom_lexer_with_buffer buffer_size in
let proto =
try Pb_parsing_parser.proto_ next_token lexbuf with
| Parsing.Parse_error ->
Pb_exception.ocamlyacc_parsing_error (Loc.from_lexbuf lexbuf)
(error_context_tokens ())
| Pb_exception.Compilation_error e ->
Pb_exception.protoc_parsing_error e (Loc.from_lexbuf lexbuf)
(error_context_tokens ())
| exn ->
let msg = Printexc.to_string exn in
Pb_exception.unknown_parsing_error ~msg ~context:(error_context_tokens ())
(Loc.from_lexbuf lexbuf)
in
let proto = { proto with Pt.proto_file_name = Some file_name } in
Parsing_util.finalize_proto_value proto
type file_loader = string -> string * string
let parse_file file_loader file_name =
let rec aux protos = function
| [] -> protos
| { Pt.file_name; _ } :: imports ->
let proto = parse_single_file (file_loader file_name) in
let protos = aux (proto :: protos) proto.Pt.imports in
aux protos imports
in
let proto = parse_single_file (file_loader file_name) in
List.rev @@ aux [ proto ] proto.Pt.imports