1%% This line tells emacs to use -*- erlang -*- mode for this file
2
3%%% Copyright (C) 2010-2013  Tomas Abrahamsson
4%%%
5%%% Author: Tomas Abrahamsson <tab@lysator.liu.se>
6%%%
7%%% This library is free software; you can redistribute it and/or
8%%% modify it under the terms of the GNU Lesser General Public
9%%% License as published by the Free Software Foundation; either
10%%% version 2.1 of the License, or (at your option) any later version.
11%%%
12%%% This library is distributed in the hope that it will be useful,
13%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
14%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15%%% Lesser General Public License for more details.
16%%%
17%%% You should have received a copy of the GNU Lesser General Public
18%%% License along with this library; if not, write to the Free Software
19%%% Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston,
20%%% MA  02110-1301  USA
21
22Nonterminals
23        proto
24        syntax_def
25        elements element
26        enum_def enum_fields enum_field
27        opt_enum_opts enum_opts enum_opt
28        message_def msg_elems msg_elem
29        opt_field_opts field_opts field_opt occurrence type
30        map_type map_key_type
31        package_def
32        import_def
33        identifiers
34        option_name_ident
35        extend_def extensions_def exts ext
36        reserved_def res_numbers res_number res_names
37        oneof_def oneof_elems oneof_elem
38        option_def
39        group_def
40        service_def rpc_defs rpc_def rpc_arg rpc_ret m_opts
41        name
42        option_name
43        constant
44        integer
45        string_expr
46        fidentifier
47        .
48
49Terminals
50        package
51        message enum
52        required optional repeated
53        double float int32 int64 uint32
54        uint64 sint32 sint64 fixed32 fixed64
55        sfixed32 sfixed64 bool string bytes map
56        identifier str_lit dec_lit oct_lit hex_lit float_lit bool_lit
57        default
58        import
59        option
60        extensions extend max to reserved
61        oneof
62        group
63        service rpc returns stream
64        packed deprecated
65        syntax
66        '.' ';' '(' ')' '{' '}' '[' ']' '=' ',' '<' '>'
67        .
68
69Rootsymbol
70        proto.
71
72Endsymbol
73        '$end'.
74
75
76%% TODO: implement verification of references
77%% TODO: implement (custom) options: allowed everywhere
78
79proto -> elements:                      '$1'.
80proto -> syntax_def elements:           ['$1' | '$2'].
81
82syntax_def -> syntax '=' str_lit ';':   verify_syntax('$3').
83
84elements -> element elements:           ['$1' | '$2'].
85elements -> ';' elements:               '$2'.
86elements -> '$empty':                   [].
87
88element -> package_def:                 '$1'.
89element -> import_def:                  '$1'.
90element -> enum_def:                    '$1'.
91element -> message_def:                 '$1'.
92element -> extend_def:                  '$1'.
93element -> option_def:                  '$1'.
94element -> service_def:                 '$1'.
95
96package_def -> package name ';':        {package, '$2'}.
97
98name -> '.' identifiers:                ['.' | '$2'].
99name -> identifiers:                    '$1'.
100
101option_name_ident -> identifier:        [identifier_name('$1')].
102option_name_ident -> '(' name ')':      '$2'.
103
104option_name -> option_name_ident:           '$1'.
105option_name -> option_name_ident '.' name:  '$1' ++ '$3'.
106
107identifiers -> identifier '.' identifiers:      [identifier_name('$1'), '.'
108                                                 | '$3'].
109identifiers -> identifier:                      [identifier_name('$1')].
110
111import_def -> import str_lit ';':       {import, literal_value('$2')}.
112
113option_def -> option option_name '=' constant: {option, '$2', '$4'}.
114
115enum_def -> enum fidentifier '{' enum_fields '}':
116                                        {{enum,identifier_name('$2')},'$4'}.
117
118enum_fields -> enum_field enum_fields:  ['$1' | '$2'].
119enum_fields -> option_def enum_fields:  ['$1' | '$2'].
120enum_fields -> ';' enum_fields:         '$2'.
121enum_fields -> '$empty':                [].
122
123enum_field -> fidentifier '=' integer ';':
124                                        {identifier_name('$1'), '$3'}.
125enum_field -> fidentifier '=' integer '[' opt_enum_opts ']' ';':
126                                        {identifier_name('$1'), '$3'}.
127
128opt_enum_opts -> enum_opts:             '$1'.
129opt_enum_opts -> '$empty':              [].
130
131enum_opts -> enum_opt ',' enum_opts:    ['$1' | '$2'].
132enum_opts -> enum_opt:                  ['$1'].
133
134enum_opt -> name '=' constant:          {'$1', '$3'}.
135
136
137message_def -> message fidentifier '{' msg_elems '}':
138                                        {{msg,identifier_name('$2')},'$4'}.
139
140msg_elems -> msg_elem msg_elems:        ['$1' | '$2'].
141msg_elems -> ';' msg_elems:             '$2'.
142msg_elems -> '$empty':                  [].
143
144msg_elem -> occurrence type fidentifier '=' dec_lit ';':
145                                        #?gpb_field{occurrence='$1',
146                                                    type='$2',
147                                                    name=identifier_name('$3'),
148                                                    fnum=literal_value('$5'),
149                                                    opts=[]}.
150msg_elem -> occurrence type fidentifier '=' dec_lit '[' opt_field_opts ']' ';':
151                                        #?gpb_field{occurrence='$1',
152                                                    type='$2',
153                                                    name=identifier_name('$3'),
154                                                    fnum=literal_value('$5'),
155                                                    opts='$7'}.
156msg_elem -> type fidentifier '=' dec_lit ';': % proto3
157                                        #?gpb_field{occurrence=optional,
158                                                    type='$1',
159                                                    name=identifier_name('$2'),
160                                                    fnum=literal_value('$4'),
161                                                    opts=[]}.
162msg_elem -> type fidentifier '=' dec_lit '[' opt_field_opts ']' ';': % proto3
163                                        #?gpb_field{occurrence=optional,
164                                                    type='$1',
165                                                    name=identifier_name('$2'),
166                                                    fnum=literal_value('$4'),
167                                                    opts='$6'}.
168msg_elem -> map_type fidentifier '=' dec_lit ';':
169                                        #?gpb_field{occurrence=repeated,
170                                                    type='$1',
171                                                    name=identifier_name('$2'),
172                                                    fnum=literal_value('$4')}.
173msg_elem -> map_type fidentifier '=' dec_lit '[' opt_field_opts ']' ';':
174                                        #?gpb_field{occurrence=repeated,
175                                                    type='$1',
176                                                    name=identifier_name('$2'),
177                                                    fnum=literal_value('$4'),
178                                                    opts='$6'}.
179
180msg_elem -> message_def:                '$1'.
181msg_elem -> enum_def:                   '$1'.
182msg_elem -> extensions_def:             {extensions,lists:sort('$1')}.
183msg_elem -> oneof_def:                  '$1'.
184msg_elem -> extend_def:                 '$1'.
185msg_elem -> reserved_def:               '$1'.
186msg_elem -> group_def:                  '$1'.
187msg_elem -> option_def:                 '$1'.
188
189fidentifier -> identifier:              '$1'.
190fidentifier -> package:                 kw_to_identifier('$1').
191fidentifier -> service:                 kw_to_identifier('$1').
192fidentifier -> enum:                    kw_to_identifier('$1').
193fidentifier -> message:                 kw_to_identifier('$1').
194fidentifier -> required:                kw_to_identifier('$1').
195fidentifier -> optional:                kw_to_identifier('$1').
196fidentifier -> repeated:                kw_to_identifier('$1').
197fidentifier -> double:                  kw_to_identifier('$1').
198fidentifier -> 'float':                 kw_to_identifier('$1').
199fidentifier -> int32:                   kw_to_identifier('$1').
200fidentifier -> int64:                   kw_to_identifier('$1').
201fidentifier -> uint32:                  kw_to_identifier('$1').
202fidentifier -> uint64:                  kw_to_identifier('$1').
203fidentifier -> sint32:                  kw_to_identifier('$1').
204fidentifier -> sint64:                  kw_to_identifier('$1').
205fidentifier -> fixed32:                 kw_to_identifier('$1').
206fidentifier -> fixed64:                 kw_to_identifier('$1').
207fidentifier -> sfixed32:                kw_to_identifier('$1').
208fidentifier -> sfixed64:                kw_to_identifier('$1').
209fidentifier -> bool:                    kw_to_identifier('$1').
210fidentifier -> string:                  kw_to_identifier('$1').
211fidentifier -> bytes:                   kw_to_identifier('$1').
212fidentifier -> bool_lit:                kw_to_identifier(literal_value('$1')).
213fidentifier -> default:                 kw_to_identifier('$1').
214fidentifier -> import:                  kw_to_identifier('$1').
215fidentifier -> option:                  kw_to_identifier('$1').
216fidentifier -> extensions:              kw_to_identifier('$1').
217fidentifier -> extend:                  kw_to_identifier('$1').
218fidentifier -> max:                     kw_to_identifier('$1').
219fidentifier -> to:                      kw_to_identifier('$1').
220fidentifier -> rpc:                     kw_to_identifier('$1').
221fidentifier -> returns:                 kw_to_identifier('$1').
222fidentifier -> stream:                  kw_to_identifier('$1').
223fidentifier -> packed:                  kw_to_identifier('$1').
224fidentifier -> deprecated:              kw_to_identifier('$1').
225fidentifier -> syntax:                  kw_to_identifier('$1').
226fidentifier -> map:                     kw_to_identifier('$1').
227fidentifier -> reserved:                kw_to_identifier('$1').
228fidentifier -> group:                   kw_to_identifier('$1').
229
230opt_field_opts -> field_opts:           '$1'.
231opt_field_opts -> '$empty':             [].
232
233
234field_opts -> field_opt ',' field_opts: ['$1' | '$3'].
235field_opts -> field_opt:                ['$1'].
236
237
238field_opt -> default '=' constant:      {default, '$3'}.
239field_opt -> packed:                    {packed, true}.
240field_opt -> packed '=' bool_lit:       {packed, literal_value('$3')}.
241field_opt -> deprecated:                {deprecated, true}.
242field_opt -> deprecated '=' bool_lit:   {deprecated, literal_value('$3')}.
243field_opt -> option_name:               {'$1', true}.
244field_opt -> option_name '=' constant:  {'$1', '$3'}.
245
246occurrence -> required:                 required.
247occurrence -> optional:                 optional.
248occurrence -> repeated:                 repeated.
249
250type -> double:                         double.
251type -> float:                          float.
252type -> int32:                          int32.
253type -> int64:                          int64.
254type -> uint32:                         uint32.
255type -> uint64:                         uint64.
256type -> sint32:                         sint32.
257type -> sint64:                         sint64.
258type -> fixed32:                        fixed32.
259type -> fixed64:                        fixed64.
260type -> sfixed32:                       sfixed32.
261type -> sfixed64:                       sfixed64.
262type -> bool:                           bool.
263type -> string:                         string.
264type -> bytes:                          bytes.
265type -> name:                           {ref, '$1'}.
266
267map_type -> map '<' map_key_type ',' type '>': {map,'$3','$5'}.
268
269map_key_type -> int32:                  int32.
270map_key_type -> int64:                  int64.
271map_key_type -> uint32:                 uint32.
272map_key_type -> uint64:                 uint64.
273map_key_type -> sint32:                 sint32.
274map_key_type -> sint64:                 sint64.
275map_key_type -> fixed32:                fixed32.
276map_key_type -> fixed64:                fixed64.
277map_key_type -> sfixed32:               sfixed32.
278map_key_type -> sfixed64:               sfixed64.
279map_key_type -> bool:                   bool.
280map_key_type -> string:                 string.
281%% missing from type: double | float | bytes | message name | enum name
282
283group_def -> occurrence group fidentifier '=' dec_lit '{' msg_elems '}':
284                 begin
285                     TmpGName = identifier_name('$3'),
286                     {group1,TmpGName,'$7',
287                      #?gpb_field{occurrence='$1',
288                                  type={ref,['...expanded-later']},
289                                  name=identifier_name('$3'),
290                                  fnum=literal_value('$5'),
291                                  opts=[]}}
292                 end.
293
294constant -> identifier:                 identifier_name('$1').
295constant -> integer:                    '$1'.
296constant -> float_lit:                  literal_value('$1').
297constant -> string_expr:                '$1'.
298constant -> bool_lit:                   literal_value('$1').
299
300integer -> dec_lit:                     literal_value('$1').
301integer -> oct_lit:                     literal_value('$1').
302integer -> hex_lit:                     literal_value('$1').
303
304%% the protoc parser sports a c[++] style string concatenation feature
305string_expr -> str_lit string_expr:     literal_value('$1') ++ '$2'.
306string_expr -> str_lit:                 literal_value('$1').
307
308extensions_def -> extensions exts ';':  '$2'.
309
310exts -> ext ',' exts:                   ['$1' | '$3'].
311exts -> ext:                            ['$1'].
312
313ext -> integer:                         {'$1','$1'}.
314ext -> integer to integer:              {'$1','$3'}.
315ext -> integer to max:                  {'$1',max}.
316
317reserved_def -> reserved res_numbers:   {reserved_numbers,'$2'}.
318reserved_def -> reserved res_names:     {reserved_names,'$2'}.
319
320res_numbers -> res_number ',' res_numbers: ['$1' | '$3'].
321res_numbers -> res_number:                 ['$1'].
322
323res_number -> integer:                  '$1'.
324res_number -> integer to integer:       {'$1','$3'}.
325
326res_names -> string_expr ',' res_names: ['$1' | '$3'].
327res_names -> string_expr:               ['$1'].
328
329oneof_def -> 'oneof' fidentifier '{' oneof_elems '}':
330                                        #gpb_oneof{name=identifier_name('$2'),
331                                                   fields='$4'}.
332
333oneof_elems -> oneof_elem oneof_elems:  ['$1' | '$2'].
334oneof_elems -> oneof_elem:              ['$1'].
335
336oneof_elem -> type fidentifier '=' dec_lit ';':
337                                        #?gpb_field{occurrence=optional,
338                                                    type='$1',
339                                                    name=identifier_name('$2'),
340                                                    fnum=literal_value('$4'),
341                                                    opts=[]}.
342oneof_elem -> type fidentifier '=' dec_lit '[' opt_field_opts ']' ';':
343                                        #?gpb_field{occurrence=optional,
344                                                    type='$1',
345                                                    name=identifier_name('$2'),
346                                                    fnum=literal_value('$4'),
347                                                    opts='$6'}.
348
349extend_def -> extend name '{' msg_elems '}':
350                                        {{extend,{eref1,'$2'}},'$4'}.
351
352
353service_def -> service fidentifier '{' rpc_defs '}':
354                                        {{service,identifier_name('$2')},'$4'}.
355
356rpc_defs -> rpc_def rpc_defs:           ['$1' | '$2'].
357rpc_defs -> ';' rpc_defs:               '$2'.
358rpc_defs -> '$empty':                   [].
359
360rpc_def -> rpc fidentifier rpc_arg returns rpc_ret ';':
361                                        {identifier_name('$2'), '$3','$5',[]}.
362rpc_def -> rpc fidentifier rpc_arg returns rpc_ret '{' m_opts '}':
363                                        {identifier_name('$2'), '$3','$5','$7'}.
364
365rpc_arg -> '(' name ')':                {'$2', false}.
366rpc_arg -> '(' stream name ')':         {'$3', true}.
367
368rpc_ret -> '(' name ')':                {'$2', false}.
369rpc_ret -> '(' stream name ')':         {'$3', true}.
370
371m_opts -> option_def ';' m_opts:        ['$1' | '$3'].
372m_opts -> ';' m_opts:                   '$2'.
373m_opts -> '$empty':                     [].
374
375
376
377Header
378"%%% @doc The yecc grammar for the protobuf language,"
379"%%% both for syntax = proto2 and for proto3."
380"%%% @private"
381"".
382
383Erlang code.
384
385-include("../include/gpb.hrl").
386
387-export([post_process_one_file/3]).
388-export([post_process_all_files/2]).
389-export([format_post_process_error/1]).
390-export([fetch_imports/1]).
391
392-type defs() :: [def()].
393-type def() :: {{msg, Name::atom()}, [field()]} |
394               {{group, Name::atom()}, [field()]} |
395               {{enum, Name::atom()}, [{Sym::atom(), Value::integer()}]} |
396               {{service, Name::atom()}, [#?gpb_rpc{}]} |
397               {package, Name::atom()} |
398               {syntax, string()} | % "proto2" | "proto3"
399               {{extensions, MsgName::atom()}, [field_number_extension()]} |
400               {{extend, MsgName::atom()}, MoreFields::[field()]} |
401               {proto3_msgs, [MsgName::atom()]} |
402               {{reserved_numbers, MsgName::atom()}, [integer()]} |
403               {{reserved_names, MsgName::atom()}, [FieldName::atom()]} |
404               {import, ProtoFile::string()} |
405               {{msg_options, MsgName::atom()}, [msg_option()]} |
406               {{msg_containment, ProtoName::string()}, [MsgName::atom()]} |
407               {{pkg_containment, ProtoName::string()}, PkgName::atom()} |
408               {{service_containment, ProtoName::string()},
409                [ServiceName::atom()]} |
410               {{rpc_containment, ProtoName::string()}, [RpcName::atom()]}.
411-type field() :: #?gpb_field{} | #gpb_oneof{}.
412-type field_number_extension() :: {Lower::integer(), Upper::integer() | max}.
413-type msg_option() :: {[NameComponent::atom()], OptionValue::term()}.
414
415-export_type([defs/0, def/0]).
416-export_type([field/0]).
417
418
419verify_syntax({str_lit, _Line, "proto2"}) ->
420    {syntax, "proto2"};
421verify_syntax({str_lit, _Line, "proto3"}) ->
422    {syntax, "proto3"};
423verify_syntax({str_lit, Line, "proto"++_ = Unsupported}) ->
424    return_error(Line, "Unsupported proto version: " ++ Unsupported);
425verify_syntax({str_lit, Line, Unsupported}) ->
426    return_error(Line, "Unsupported proto syntax: " ++ Unsupported).
427
428identifier_name({identifier, _Line, Name}) -> list_to_atom(Name).
429
430kw_to_identifier({Kw, Line}) ->
431    {identifier, Line, atom_to_list(Kw)}.
432
433literal_value({_TokenType, _Line, Value}) -> Value.
434
435post_process_one_file(FileName, Defs, Opts) ->
436    case find_package_def(Defs, Opts) of
437        {ok, Package} ->
438            Defs1 = handle_proto_syntax_version_one_file(
439                      join_any_msg_options(
440                        convert_default_values(
441                          flatten_qualify_defnames(Defs, Package)))),
442            FileExt = filename:extension(FileName),
443            ProtoName = filename:basename(FileName, FileExt),
444            MetaInfo = mk_meta_info(ProtoName, Defs1, Opts),
445            {ok, MetaInfo ++ Defs1};
446        {error, Reasons} ->
447            {error, Reasons}
448    end.
449
450post_process_all_files(Defs, _Opts) ->
451    case resolve_names(Defs) of
452        {ok, Defs2} ->
453            {ok, normalize_msg_field_options(
454                   handle_proto_syntax_version_all_files(
455                     enumerate_msg_fields(
456                       reformat_names(
457                         extend_msgs(Defs2)))))};
458        {error, Reasons} ->
459            {error, Reasons}
460    end.
461
462%% -> {ok, Defs} | {error, [Reason]}
463resolve_names(Defs) ->
464    case resolve_refs(Defs) of
465        {ok, RDefs} ->
466            case verify_defs(RDefs) of
467                ok ->
468                    {ok, RDefs};
469                {error, Reasons} ->
470                    {error, Reasons}
471            end;
472        {error, Reasons} ->
473            {error, Reasons}
474    end.
475
476%% Find any package specifier. At most one such package specifier
477%% may exist, and it can exist anywhere (top-level) in the proto file,
478%% yet it still applies to the whole file.
479find_package_def(Defs, Opts) ->
480    case proplists:get_bool(use_packages, Opts) of
481        true ->
482            case [Pkg || {package, Pkg} <- Defs] of
483                [] ->
484                    {ok, empty_pkg_root()};
485                [Pkg] ->
486                    {ok, ['.' | Pkg]};
487                Pkgs when length(Pkgs) >= 2 ->
488                    PrettyPkgs = [reformat_name(Pkg) || Pkg <- Pkgs],
489                    {error, [{multiple_pkg_specifiers, PrettyPkgs}]}
490            end;
491        false ->
492            {ok, empty_pkg_root()}
493    end.
494
495empty_pkg_root() ->
496    ['.'].
497
498%% For nested message definitions such as
499%% ```
500%%    message m1 {
501%%      required uint32 f1 = 1;
502%%      message m2 { ... }
503%%      enum e2 { ... }
504%%    };",
505%% '''
506%% the parser will produce a nested structure, such as:
507%% ```
508%%   [{{msg,M1},[#field{},
509%%               {{msg,M2}, [...]},
510%%               {{enum,E2}, [...]}]}]
511%% '''
512%% Flattening means to lift the nested m2 and e2 definition to the top-level,
513%% so the above turns into:
514%% ```
515%%   [{{msg,M1},[#field{}]},
516%%    {{msg,M2}, [...]},
517%%    {{enum,E2}, [...]}]
518%% '''
519%%
520%% During this process, the message and enum names and similar get
521%% fully qualified into absolute rooted name-paths. In the example
522%% above, this applies to m1, m2 and e2. Note that at this stage,
523%% nothing is done to resolve reference to names, such as message
524%% types for fields. A name-path is a list of path components,
525%% separated by the dot-atom, '.', and an absolute rooted name-path is
526%% a path that begins with the dot-atom, '.', much like a slash or a
527%% backslash in a file name path.
528flatten_qualify_defnames(Defs, Root) ->
529    lists:reverse(
530      lists:foldl(
531        fun({{msg,Name}, FieldsOrDefs}, Acc) ->
532                FullName = prepend_path(Root, Name),
533                {Fields2, Defs2} = flatten_fields(FieldsOrDefs, FullName),
534                [{{msg,FullName},Fields2} | Defs2] ++ Acc;
535           ({{group,FullName}, FieldsOrDefs}, Acc) ->
536                {Fields2, Defs2} = flatten_fields(FieldsOrDefs, FullName),
537                [{{group,FullName},Fields2} | Defs2] ++ Acc;
538           ({{enum,Name}, ENs}, Acc) ->
539                FullName = prepend_path(Root, Name),
540                [{{enum,FullName}, ENs} | Acc];
541           ({extensions,Exts}, Acc) ->
542                [{{extensions,Root},Exts} | Acc];
543           ({{extend,{eref1,Name}}, FieldsOrDefs}, Acc) ->
544                FullNameCandidates =
545                    rootward_names(Root, Name) ++
546                    rootward_names(empty_pkg_root(), Name),
547                {Fields2, Defs2} = flatten_fields(FieldsOrDefs, Root),
548                [{{extend,{eref2,Root,FullNameCandidates}},Fields2} | Defs2] ++
549                    Acc;
550           ({{service, Name}, RPCs}, Acc) ->
551                FullName = prepend_path(Root, Name),
552                [{{service,FullName}, RPCs} | Acc];
553           (OtherElem, Acc) ->
554                [OtherElem | Acc]
555        end,
556        [],
557        Defs)).
558
559flatten_fields(FieldsOrDefs, FullName) ->
560    {RFields2, Defs2} =
561        lists:foldl(
562          fun(#?gpb_field{}=F, {Fs,Ds}) ->
563                  {[F | Fs], Ds};
564             (#gpb_oneof{}=O, {Fs,Ds}) ->
565                  {[O | Fs], Ds};
566             ({group1,TmpGName,GFields,MField}, {Fs,Ds}) ->
567                  FullGroupName = prepend_path(FullName, TmpGName),
568                  Group0 = {{group,FullGroupName}, GFields},
569                  QDefs = flatten_qualify_defnames([Group0], FullGroupName),
570                  MField1 = MField#?gpb_field{type={ref,FullGroupName}},
571                  {[MField1 | Fs], QDefs++Ds};
572             ({{extend, _Ref},_}=Def, {Fs,Ds}) ->
573                  QDefs = flatten_qualify_defnames([Def], FullName),
574                  {Fs, QDefs ++ Ds};
575             ({reserved_numbers, Ns}, {Fs,Ds}) ->
576                  Def = {{reserved_numbers,FullName}, Ns},
577                  {Fs, [Def | Ds]};
578             ({reserved_names, Ns}, {Fs,Ds}) ->
579                  Def = {{reserved_names,FullName}, Ns},
580                  {Fs, [Def | Ds]};
581             ({option,OptName,OptValue}, {Fs,Ds}) ->
582                  {Fs, [{{msg_option,FullName},{OptName,OptValue}} | Ds]};
583             (Def, {Fs,Ds}) ->
584                  QDefs = flatten_qualify_defnames([Def], FullName),
585                  {Fs, QDefs++Ds}
586          end,
587          {[],[]},
588          FieldsOrDefs),
589    {lists:reverse(RFields2), Defs2}.
590
591%% Resolve any refs
592resolve_refs(Defs) ->
593    Root = ['.'],
594    {ResolvedRefs, Reasons} =
595        lists:mapfoldl(
596          fun({{msg,FullName}, Fields}, Acc) ->
597                  {NewFields, Acc2} =
598                      resolve_field_refs(Fields, Defs, Root, FullName, Acc),
599                  {{{msg,FullName}, NewFields}, Acc2};
600             ({{group,FullName}, Fields}, Acc) ->
601                  {NewFields, Acc2} =
602                      resolve_field_refs(Fields, Defs, Root, FullName, Acc),
603                  {{{group,FullName}, NewFields}, Acc2};
604             ({{service,FullName}, Rpcs}, Acc) ->
605                  {NewRPCs, Acc2} =
606                      resolve_rpc_refs(Rpcs, Defs, Root, FullName, Acc),
607                  {{{service,FullName}, NewRPCs}, Acc2};
608             ({{extend,ExtendeeCandidates}, Fields}, Acc) ->
609                  {Extendee, NewFields, Acc2} =
610                      resolve_extend_refs(ExtendeeCandidates, Fields, Defs,
611                                          Root, Acc),
612                  {{{extend,Extendee}, NewFields}, Acc2};
613             (OtherElem, Acc) ->
614                  {OtherElem, Acc}
615          end,
616          [],
617          Defs),
618    if Reasons == [] -> {ok, ResolvedRefs};
619       Reasons /= [] -> {error, lists:reverse(Reasons)}
620    end.
621
622
623
624resolve_field_refs(Fields, Defs, Root, FullName, Reasons) ->
625    lists:mapfoldl(
626      fun(#?gpb_field{name=FName, type={ref,Ref}}=Field, Acc) ->
627              case resolve_ref(Defs, Ref, Root, FullName) of
628                  {found, TypeName} ->
629                      {Field#?gpb_field{type=TypeName}, Acc};
630                  not_found ->
631                      Reason = {ref_to_undefined_msg_or_enum,
632                                {{FullName, FName}, Ref}},
633                      {Field, [Reason | Acc]}
634              end;
635         (#?gpb_field{name=FName, type={map,KeyType,{ref,Ref}}}=Field, Acc) ->
636              case resolve_ref(Defs, Ref, Root, FullName) of
637                  {found, TypeName} ->
638                      {Field#?gpb_field{type={map,KeyType,TypeName}}, Acc};
639                  not_found ->
640                      Reason = {ref_to_undefined_msg_or_enum,
641                                {{FullName, FName}, Ref}},
642                      {Field, [Reason | Acc]}
643              end;
644         (#?gpb_field{}=Field, Acc) ->
645              {Field, Acc};
646         (#gpb_oneof{fields=OFields1}=Oneof, Acc) ->
647              {OFields2, Acc2} =
648                  resolve_field_refs(OFields1, Defs, Root, FullName, Acc),
649              {Oneof#gpb_oneof{fields=OFields2}, Acc2}
650      end,
651      Reasons,
652      Fields).
653
654resolve_rpc_refs(Rpcs, Defs, Root, FullName, Reasons) ->
655    lists:mapfoldl(
656      fun({RpcName, {Arg, ArgIsStream}, {Return, ReturnIsStream}, Opts}=Rpc,
657          Acc) ->
658              case resolve_ref(Defs, Arg, Root, FullName) of
659                  {found, {msg, MArg}} ->
660                      case resolve_ref(Defs, Return, Root, FullName) of
661                          {found, {msg, MReturn}} ->
662                              NewOpts = [{reformat_name(Name), Value}
663                                         || {option,Name,Value} <- Opts],
664                              NewRpc = #?gpb_rpc{name=RpcName,
665                                                 input=MArg,
666                                                 input_stream=ArgIsStream,
667                                                 output=MReturn,
668                                                 output_stream=ReturnIsStream,
669                                                 opts=NewOpts},
670                              {NewRpc, Acc};
671                          {found, {BadType, MReturn}} ->
672                              Reason = {rpc_return_ref_to_non_msg,
673                                        {{FullName, RpcName, Return},
674                                         BadType, MReturn}},
675                              {Rpc, [Reason | Acc]};
676                          not_found ->
677                              Reason = {rpc_return_ref_to_undefined_msg,
678                                        {{FullName, RpcName}, Return}},
679                              {Rpc, [Reason | Acc]}
680                      end;
681                  {found, {BadType, MArg}} ->
682                      Reason = {rpc_arg_ref_to_non_msg,
683                                {{FullName, RpcName, Arg}, BadType, MArg}},
684                      {Rpc, [Reason | Acc]};
685                  not_found ->
686                      Reason = {rpc_arg_ref_to_undefined_msg,
687                                {{FullName, RpcName}, Arg}},
688                      {Rpc, [Reason | Acc]}
689              end
690      end,
691      Reasons,
692      Rpcs).
693
694resolve_extend_refs({eref2, Ctxt, ExtendeeCandidates}, Fields, Defs,
695                    Root, Acc) ->
696    case resolve_ref_candidates(Defs, ExtendeeCandidates) of
697        {found, {msg,NewToBeExtended}} ->
698            {NewFields, Acc2} =
699                resolve_field_refs(Fields, Defs, Root, Ctxt, Acc),
700            {NewToBeExtended, NewFields, Acc2};
701        not_found ->
702            Reason = {extend_ref_to_undefined_msg, hd(ExtendeeCandidates)},
703            {hd(ExtendeeCandidates), Fields, [Reason | Acc]}
704    end.
705
706%% -> {found, {msg,FullName}|{enum,FullName}} | not_found
707resolve_ref(Defs, Ref, Root, FullName) ->
708    case is_absolute_ref(Ref) of
709        true  ->
710            FullRef = ensure_path_prepended(Root, Ref),
711            find_typename(FullRef, Defs);
712        false ->
713            PossibleRoots = compute_roots(FullName),
714            find_ref_rootwards(PossibleRoots, Ref, Defs)
715    end.
716
717resolve_ref_candidates(Defs, [Cand1 | Rest]) ->
718    case find_typename(Cand1, Defs) of
719        {found, TypeName} -> {found, TypeName};
720        not_found -> resolve_ref_candidates(Defs, Rest)
721    end;
722resolve_ref_candidates(_Defs, []) ->
723    not_found.
724
725find_ref_rootwards([PossibleRoot | Rest], Ref, Defs) ->
726    FullRef = ensure_path_prepended(PossibleRoot, Ref),
727    case find_typename(FullRef, Defs) of
728        {found, TypeName} -> {found, TypeName};
729        not_found -> find_ref_rootwards(Rest, Ref, Defs)
730    end;
731find_ref_rootwards([], _Ref, _Defs) ->
732    not_found.
733
734is_absolute_ref(['.' | _]) -> true;
735is_absolute_ref(_Other)    -> false.
736
737find_typename(Name, [{{enum,Name}, _Values} | _])  -> {found, {enum,Name}};
738find_typename(Name, [{{msg,Name}, _SubElems} | _]) -> {found, {msg,Name}};
739find_typename(Name, [{{group,Name}, _Elems} | _])  -> {found, {group,Name}};
740find_typename(Name, [_ | Rest])                    -> find_typename(Name, Rest);
741find_typename(_Name,[])                            -> not_found.
742
743%% Similar to compute_roots/1, but always keep `Name' last.
744%% Example: rootward_names(['.',m1,'.',m2],  x) ->
745%%            [['.',m1,'.',m2,'.',x],
746%%             ['.',m1,'.',x]
747%%             ['.',x]]
748rootward_names(Path, Name) ->
749    [prepend_path(R, Name) || R <- compute_roots(Path)].
750
751%% Turn ['.',m1,'.',m2,'.',m3]
752%% into [['.',m1,'.',m2,'.',m3],
753%%       ['.',m1,'.',m2],
754%%       ['.',m1],
755%%       ['.']]
756compute_roots(['.']) -> [['.']];
757compute_roots(DeeperPath) ->
758    [DeeperPath | compute_roots(drop_last_level(DeeperPath))].
759
760drop_last_level(['.']) -> ['.'];
761drop_last_level(['.', X]) when is_atom(X) -> ['.'];
762drop_last_level(DeeperPath) when length(DeeperPath) >= 3 ->
763    [_X, '.' | RestReversed] = lists:reverse(DeeperPath),
764    lists:reverse(RestReversed).
765
766prepend_path(['.'], Id) when is_atom(Id)           -> ['.', Id];
767prepend_path(['.'], SubPath) when is_list(SubPath) -> ['.' | SubPath];
768prepend_path(Path,  Id) when is_atom(Id)           -> Path ++ ['.', Id];
769prepend_path(Path,  SubPath) when is_list(SubPath) -> Path ++ ['.' | SubPath].
770
771ensure_path_prepended(Pkg, Path)   ->
772    case lists:prefix(Pkg, Path) of
773        false -> prepend_path(Pkg, Path);
774        true ->  Path
775    end.
776
777convert_default_values(Defs) ->
778    lists:map(
779      fun({{msg,Name},Fields}) ->
780              Fields2 = lists:map(fun convert_default_values_field/1, Fields),
781              {{msg,Name},Fields2};
782         ({{group,Name},Fields}) ->
783              Fields2 = lists:map(fun convert_default_values_field/1, Fields),
784              {{group,Name},Fields2};
785         (Other) ->
786              Other
787      end,
788      Defs).
789
790convert_default_values_field(#?gpb_field{type=Type, opts=Opts}=Field) ->
791    case {Type, lists:keyfind(default, 1, Opts)} of
792        {bytes, {default, Default}} when is_list(Default) ->
793            %% Default values for type bytes are written as a string
794            Default2 = list_to_binary(Default),
795            Opts2 = lists:keyreplace(default, 1, Opts, {default, Default2}),
796            Field#?gpb_field{opts=Opts2};
797        _ ->
798            Field
799    end;
800convert_default_values_field(#gpb_oneof{fields=OFs}=Field) ->
801    OFs2 = lists:map(fun convert_default_values_field/1, OFs),
802    Field#gpb_oneof{fields=OFs2}.
803
804join_any_msg_options(Defs) ->
805    {NonMsgOptDefs, MsgOptsDict} =
806        lists:foldl(
807          fun({{msg_option,MsgName},Opt}, {Ds,MsgOptsDict}) ->
808                  {Ds, dict:append(MsgName, Opt, MsgOptsDict)};
809             (OtherDef, {Ds, MsgOptsDict}) ->
810                  {[OtherDef | Ds], MsgOptsDict}
811          end,
812          {[], dict:new()},
813          Defs),
814    MsgOpts = [{{msg_options, MsgName}, MsgOpts}
815               || {MsgName, MsgOpts} <- dict:to_list(MsgOptsDict)],
816    lists:reverse(NonMsgOptDefs, MsgOpts).
817
818handle_proto_syntax_version_one_file(Defs) ->
819    case proplists:get_value(syntax, Defs) of
820        undefined -> handle_proto2_1(Defs);
821        "proto2"  -> handle_proto2_1(Defs);
822        "proto3"  -> handle_proto3_1(Defs)
823    end.
824
825handle_proto2_1(Defs) ->
826    Defs.
827
828handle_proto3_1(Defs) ->
829    %% FIXME: Verify no 'extensions' or 'extend'
830    %% FIXME: Verify no 'required' occurrences
831    %% FIXME: Verify enums start with 0
832
833    %% Remember which msgs were defined using proto3 syntax,
834    %% so we can treat them differently later on.
835    anno_msgs_proto3_origin(Defs).
836
837anno_msgs_proto3_origin(Defs) ->
838    anno_msgs_proto3_origin_2(Defs, []).
839
840anno_msgs_proto3_origin_2([{{msg,Msg},_Fields}=Def | Rest], P3Msgs) ->
841    [Def | anno_msgs_proto3_origin_2(Rest, [Msg | P3Msgs])];
842anno_msgs_proto3_origin_2([Def | Rest], Acc) ->
843    [Def | anno_msgs_proto3_origin_2(Rest, Acc)];
844anno_msgs_proto3_origin_2([], Acc) ->
845    [{proto3_msgs,lists:reverse(Acc)}].
846
847handle_proto_syntax_version_all_files(Defs) ->
848    P3Items = [X || {proto3_msgs,_}=X <- Defs],
849    if P3Items == [] ->
850            Defs;
851       P3Items /= [] ->
852            Proto3Msgs = lists:append([Msgs || {proto3_msgs,Msgs} <- P3Items]),
853            Defs1 = Defs -- P3Items,
854            Defs2 = Defs1 ++ [{proto3_msgs, lists:sort(Proto3Msgs)}],
855
856            %% The protobuf language guide for proto3 says: "In proto3,
857            %% repeated fields of scalar numeric types use packed encoding by
858            %% default."
859            default_repeated_to_packed(Defs2, Proto3Msgs)
860    end.
861
862default_repeated_to_packed(Defs, P3Msgs) ->
863    lists:map(
864      fun({{msg,MsgName},Fields}=MsgDef) ->
865              case lists:member(MsgName, P3Msgs) of
866                  true ->
867                      Fields1 = default_repeated_fields_to_packed(Fields),
868                      {{msg,MsgName}, Fields1};
869                  false ->
870                      MsgDef
871              end;
872         (Other) ->
873              Other
874      end,
875      Defs).
876
877default_repeated_fields_to_packed(Fields) ->
878    lists:map(
879      fun(#?gpb_field{occurrence=repeated, opts=Opts, type=Type}=F) ->
880              case {proplists:get_value(packed, Opts),
881                    is_scalar_numeric(Type)} of
882                  {undefined, true} ->
883                      NewOpts = [{packed, true} | Opts],
884                      F#?gpb_field{opts=NewOpts};
885                  _ ->
886                      F
887              end;
888         (F) ->
889              F
890      end,
891      Fields).
892
893is_scalar_numeric(int32)    -> true;
894is_scalar_numeric(int64)    -> true;
895is_scalar_numeric(uint32)   -> true;
896is_scalar_numeric(uint64)   -> true;
897is_scalar_numeric(sint32)   -> true;
898is_scalar_numeric(sint64)   -> true;
899is_scalar_numeric(fixed32)  -> true;
900is_scalar_numeric(fixed64)  -> true;
901is_scalar_numeric(sfixed32) -> true;
902is_scalar_numeric(sfixed64) -> true;
903is_scalar_numeric(bool)     -> true;
904is_scalar_numeric(float)    -> true;
905is_scalar_numeric(double)   -> true;
906is_scalar_numeric({enum,_}) -> true;
907is_scalar_numeric(_)        -> false. % not: string | bytes | msg | map
908
909%% Find inconsistencies
910%%
911%% Prerequisites:
912%% `Defs' is expected to be flattened and may or may not be reformatted.
913verify_defs(Defs) ->
914    collect_errors(Defs,
915                   [{msg,     [fun verify_field_defaults/2]},
916                    {group,   [fun verify_field_defaults/2]},
917                    {extend,  [fun verify_extend/2]},
918                    {service, [fun verify_service/2]},
919                    {'_',     [fun(_Def, _AllDefs) -> ok end]}]).
920
921collect_errors(Defs, VerifiersList) ->
922    collect_errors(Defs, Defs, VerifiersList, ok).
923
924collect_errors([{{ElemType,_},_}=Def | Rest], AllDefs, VerifiersList, Acc) ->
925    Result = lists:foldl(
926               fun(Verifier, A) -> add_acc(A, Verifier(Def, AllDefs)) end,
927               Acc,
928               find_verifiers(ElemType, VerifiersList)),
929    collect_errors(Rest, AllDefs, VerifiersList, Result);
930collect_errors([_OtherDef | Rest], AllDefs, VerifiersList, Acc) ->
931    %% Example: import, package, ...
932    collect_errors(Rest, AllDefs, VerifiersList, Acc);
933collect_errors([], _AllRefs, _VerifiersList, Acc) ->
934    case Acc of
935        ok                       -> ok;
936        {error, ReasonsReversed} -> {error, lists:reverse(ReasonsReversed)}
937    end.
938
939add_acc(AnyPreviousResult, ok)         -> AnyPreviousResult;
940add_acc(ok,                {error, R}) -> {error, add_reason([], R)};
941add_acc({error, Reasons},  {error, R}) -> {error, add_reason(Reasons, R)}.
942
943add_reason(Reasons, Reason) when not is_list(Reason) ->
944    [Reason | Reasons];
945add_reason(Reasons, MoreReasons) when is_list(MoreReasons) ->
946    lists:reverse(MoreReasons, Reasons).
947
948find_verifiers(Type,  [{Type, Verifiers} | _]) -> Verifiers;
949find_verifiers(_Type, [{'_', Verifiers} | _])  -> Verifiers;
950find_verifiers(Type,  [_Other | Rest])         -> find_verifiers(Type, Rest).
951
952verify_field_defaults({{msg,M}, Fields}, AllDefs) ->
953    lists:foldl(fun(#?gpb_field{name=Name, type=Type, opts=FOpts}, Acc) ->
954                        Res = case lists:keysearch(default, 1, FOpts) of
955                                  {value, {default, Default}} ->
956                                      verify_scalar_default_if_present(
957                                        M, Name, Type, Default, AllDefs);
958                                  false ->
959                                      ok
960                              end,
961                        add_acc(Acc, Res);
962                   (#gpb_oneof{fields=OFields}, Acc) ->
963                        Res = verify_field_defaults({{msg,M},OFields}, AllDefs),
964                        add_acc(Acc, Res)
965                end,
966                ok,
967                Fields);
968verify_field_defaults({{group,G}, Fields}, AllDefs) ->
969    verify_field_defaults({{msg,G}, Fields}, AllDefs).
970
971
972verify_scalar_default_if_present(MsgName, FieldName, Type, Default, AllDefs) ->
973    case Type of
974        {enum,Ref} ->
975            case lists:keysearch({enum, Ref}, 1, AllDefs) of
976                {value, {{enum,Ref}, Enumerators}} ->
977                    case lists:keysearch(Default, 1, Enumerators) of
978                        {value, {Default, _Value}} ->
979                            ok;
980                        false ->
981                            {error,
982                             {{invalid_default_enum_value, Default},
983                              {name_to_dstr(MsgName), atom_to_list(FieldName)}}}
984                    end;
985                false ->
986                    ok %% caught by another verification step
987            end;
988        ScalarType when is_atom(ScalarType) ->
989            case gpb:check_scalar(Default, ScalarType) of
990                ok ->
991                    ok;
992                {error, Reason} ->
993                    {error, {Reason, {name_to_dstr(MsgName),
994                                      atom_to_list(FieldName)}}}
995            end
996    end.
997
998verify_extend(_, _AllDefs) ->
999    %% FIXME
1000    ok.
1001
1002verify_service(_, _AllDefs) ->
1003    %% FIXME
1004    ok.
1005
1006name_to_absdstr(['.' | Name]) -> "." ++ name_to_dstr(Name);
1007name_to_absdstr(Name) -> name_to_dstr(Name).
1008
1009name_to_dstr(Name) when is_list(Name) ->
1010    gpb_lib:dot_join([atom_to_list(P) || P <- Name, P /= '.']);
1011name_to_dstr(Name) when is_atom(Name) ->
1012    atom_to_list(Name).
1013
1014format_post_process_error({error, Reasons}) ->
1015    lists:flatten([[fmt_err(Reason),"\n"] || Reason <- Reasons]).
1016
1017-define(f(F, A), io_lib:format(F, A)).
1018
1019fmt_err({multiple_pkg_specifiers, Pkgs}) ->
1020    ?f("package specified more than once: ~s~n",
1021       [gpb_lib:comma_join([atom_to_list(Pkg) || Pkg <- Pkgs])]);
1022fmt_err({ref_to_undefined_msg_or_enum, {{Msg, Field}, To}}) ->
1023    ?f("in msg ~s, field ~s: undefined reference  ~s",
1024       [name_to_dstr(Msg), name_to_dstr(Field), name_to_absdstr(To)]);
1025fmt_err({extend_ref_to_undefined_msg, Msg}) ->
1026    ?f("extend of unknown message ~s", [name_to_absdstr(Msg)]);
1027fmt_err({rpc_return_ref_to_non_msg,
1028         {{FullName, RpcName, Return}, BadType, MReturn}}) ->
1029    ?f("in service ~s, rpc ~s, the return type, ~s, refers to "
1030       " a ~p, ~s, instead of to a message",
1031       [name_to_dstr(FullName), name_to_dstr(RpcName), name_to_absdstr(Return),
1032        BadType, name_to_dstr(MReturn)]);
1033fmt_err({rpc_return_ref_to_undefined_msg, {{FullName, RpcName}, Ret}}) ->
1034    ?f("in service ~s, rpc ~s, return: undefined reference ~s",
1035       [name_to_dstr(FullName), name_to_dstr(RpcName), name_to_absdstr(Ret)]);
1036fmt_err({rpc_arg_ref_to_non_msg, {{FullName, RpcName, Arg}, BadType, MArg}}) ->
1037    ?f("in service ~s, rpc ~s, the arg type, ~s, refers to "
1038       " a ~p, ~s, instead of to a message",
1039       [name_to_dstr(FullName), name_to_dstr(RpcName), name_to_absdstr(Arg),
1040        BadType, name_to_dstr(MArg)]);
1041fmt_err({rpc_arg_ref_to_undefined_msg, {{FullName, RpcName}, Arg}}) ->
1042    ?f("in service ~s, rpc ~s, arg: undefined reference ~s",
1043       [name_to_dstr(FullName), name_to_dstr(RpcName), name_to_absdstr(Arg)]);
1044fmt_err({{invalid_default_enum_value, Default}, {Msg, Field}}) ->
1045    ?f("in msg ~s, field ~s: undefined enumerator in default value ~s",
1046       [Msg, Field, Default]);
1047fmt_err({{{value_out_of_range, Signedness, Bits}, Default}, {Msg, Field}}) ->
1048    ?f("in msg ~s, field ~s: default value ~p out of range for ~p ~p bit int",
1049       [Msg, Field, Default, Signedness, Bits]);
1050fmt_err({{{bad_integer_value, Signedness, Bits}, Default}, {Msg, Field}}) ->
1051    ?f("in msg ~s, field ~s: bad default value ~p for ~p ~p bit int",
1052       [Msg, Field, Default, Signedness, Bits]);
1053fmt_err({{bad_floating_point_value, Default}, {Msg, Field}}) ->
1054    ?f("in msg ~s, field ~s: bad floating point default value ~p",
1055       [Msg, Field, Default]);
1056fmt_err({{bad_boolean_value, Default}, {Msg, Field}}) ->
1057    ?f("in msg ~s, field ~s: bad default value ~p for boolean",
1058       [Msg, Field, Default]);
1059fmt_err({{bad_unicode_string, Default}, {Msg, Field}}) ->
1060    ?f("in msg ~s, field ~s: bad default value ~p for string",
1061       [Msg, Field, Default]);
1062fmt_err({{bad_binary_value, Default}, {Msg, Field}}) ->
1063    ?f("in msg ~s, field ~s: bad default value ~p for bytes",
1064       [Msg, Field, Default]).
1065
1066%% Rewrites for instance ['.','m1','.',m2] into 'm1.m2'
1067%% Example: {{msg,['.','m1','.',m2]}, [#field{type={msg,['.','m1','.',m3]}}]}
1068%% becomes: {{msg,'m1.m2'},           [#field{type={msg,'m1.m3'}}]}
1069%%
1070%% Prerequisites:
1071%% `Defs' is expected to be flattened and names and references
1072%% are expected to have been resolved
1073reformat_names(Defs) ->
1074    lists:map(fun({{msg,Name}, Fields}) ->
1075                      {{msg,reformat_name(Name)}, reformat_fields(Fields)};
1076                 ({{group,Name}, Fields}) ->
1077                      {{group,reformat_name(Name)}, reformat_fields(Fields)};
1078                 ({{msg_containment, ProtoName}, Msgs}) ->
1079                      {{msg_containment,ProtoName},
1080                       [reformat_name(N) || N <- Msgs]};
1081                 ({{enum,Name}, ENs}) ->
1082                      {{enum,reformat_name(Name)}, reformat_enum_opt_names(ENs)};
1083                 ({{extensions,Name}, Exts}) ->
1084                      {{extensions,reformat_name(Name)}, Exts};
1085                 ({{extend,Name}, Fields}) ->
1086                      {{extend,reformat_name(Name)}, reformat_fields(Fields)};
1087                 ({{service,Name}, RPCs}) ->
1088                      {{service,reformat_name(Name)}, reformat_rpcs(RPCs)};
1089                 ({{service_containment, ProtoName}, ServiceNames}) ->
1090                      {{service_containment,ProtoName},
1091                       [reformat_name(Name) || Name <- ServiceNames]};
1092                 ({{rpc_containment, ProtoName}, RpcNames}) ->
1093                      {{rpc_containment,ProtoName},
1094                       [{reformat_name(ServiceName), RpcName}
1095                        || {ServiceName,RpcName} <- RpcNames]};
1096                 ({package, Name}) ->
1097                      {package, reformat_name(Name)};
1098                 ({{pkg_containment, ProtoName}, PkgName}) ->
1099                      {{pkg_containment,ProtoName}, reformat_name(PkgName)};
1100                 ({proto3_msgs,Names}) ->
1101                      {proto3_msgs,[reformat_name(Name) || Name <- Names]};
1102                 ({{reserved_numbers,Name}, Ns}) ->
1103                      {{reserved_numbers,reformat_name(Name)}, Ns};
1104                 ({{reserved_names,Name}, FieldNames}) ->
1105                      {{reserved_names,reformat_name(Name)}, FieldNames};
1106                 ({{msg_options,MsgName}, Opt}) ->
1107                      {{msg_options,reformat_name(MsgName)}, Opt};
1108                 (OtherElem) ->
1109                      OtherElem
1110              end,
1111              Defs).
1112
1113reformat_fields(Fields) ->
1114    lists:map(
1115      fun(#?gpb_field{type={T,Nm}}=F) ->
1116              F#?gpb_field{type={T,reformat_name(Nm)}};
1117         (#?gpb_field{type={map,KeyType,{T,Nm}}}=F) ->
1118              F#?gpb_field{type={map,KeyType,{T,reformat_name(Nm)}}};
1119         (#?gpb_field{}=F) ->
1120              F;
1121         (#gpb_oneof{fields=Fs}=O) ->
1122              O#gpb_oneof{fields=reformat_fields(Fs)}
1123      end,
1124      Fields).
1125
1126%% `Defs' is expected to be parsed.
1127reformat_enum_opt_names(Def) ->
1128    [case Item of
1129         {option, Name, Value} ->
1130             {option, reformat_name(Name), Value};
1131         Other ->
1132             Other
1133     end
1134     || Item <- Def].
1135
1136reformat_name(Name) ->
1137    list_to_atom(gpb_lib:dot_join([atom_to_list(P) || P <- Name, P /= '.'])).
1138
1139reformat_rpcs(RPCs) ->
1140    lists:map(fun(#?gpb_rpc{name=RpcName, input=Arg, output=Return}=R) ->
1141                      R#?gpb_rpc{name=RpcName,
1142                                 input=reformat_name(Arg),
1143                                 output=reformat_name(Return)}
1144              end,
1145              RPCs).
1146
1147%% `Defs' is expected to be flattened and may or may not be reformatted
1148%% `Defs' is expected to be verified, to not extend missing messages
1149extend_msgs(Defs0) ->
1150    Extendings = [E || {{extend,_MsgToExtend},_MoreFields}=E <- Defs0],
1151    lists:foldl(fun possibly_extend_msg/2, Defs0, Extendings).
1152
1153
1154possibly_extend_msg({{extend,Msg}, MoreFields}=Extending, Defs) ->
1155    case lists:keyfind({msg,Msg}, 1, Defs) of
1156        {{msg,Msg}, OrigFields} ->
1157            NewDef = {{msg,Msg}, OrigFields ++ MoreFields},
1158            lists:keyreplace({msg,Msg}, 1, Defs, NewDef) -- [Extending];
1159        false ->
1160            Defs
1161    end.
1162
1163%% `Defs' is expected to be flattened
1164enumerate_msg_fields(Defs) ->
1165    lists:map(fun({{msg,Name}, Fields}) ->
1166                      {{msg, Name}, enumerate_fields(Fields)};
1167                 ({{group,Name}, Fields}) ->
1168                      {{group, Name}, enumerate_fields(Fields)};
1169                 (OtherElem) ->
1170                      OtherElem
1171              end,
1172              Defs).
1173
1174enumerate_fields(Fields) ->
1175    lists:map(fun({I, #?gpb_field{}=F}) ->
1176                      F#?gpb_field{rnum=I};
1177                 ({I, #gpb_oneof{fields=Fs}=O}) ->
1178                      NewFields = [F#?gpb_field{rnum=I} || F <- Fs],
1179                      O#gpb_oneof{rnum=I, fields=NewFields}
1180              end,
1181              index_seq(2, Fields)).
1182
1183index_seq(_Start, []) -> [];
1184index_seq(Start, L)   -> lists:zip(lists:seq(Start, length(L) + Start - 1), L).
1185
1186%% `Defs' is expected to be parsed.
1187normalize_msg_field_options(Defs) ->
1188    lists:map(fun({{msg,Name}, Fields}) ->
1189                      {{msg, Name}, normalize_field_options(Fields)};
1190                 ({{group,Name}, Fields}) ->
1191                      {{group, Name}, normalize_field_options(Fields)};
1192                 (OtherElem) ->
1193                      OtherElem
1194              end,
1195              Defs).
1196
1197normalize_field_options(Fields) ->
1198    lists:map(fun(#?gpb_field{type={map,_KeyType,_ValueType}, opts=Opts}=F) ->
1199                      Opts1    = normalize_field_options_2(Opts),
1200                      Opts2    = Opts1 -- [packed],
1201                      F#?gpb_field{opts = Opts2};
1202                 (#?gpb_field{opts=Opts}=F) ->
1203                      Opts1    = normalize_field_options_2(Opts),
1204                      F#?gpb_field{opts = Opts1};
1205                 (#gpb_oneof{fields=Fs}=O) ->
1206                      O#gpb_oneof{fields=normalize_field_options(Fs)}
1207              end,
1208              Fields).
1209
1210normalize_field_options_2(Opts) ->
1211    Opts1 = opt_tuple_to_atom_if_defined_true(packed, Opts),
1212    opt_tuple_to_atom_if_defined_true(deprecated, Opts1).
1213
1214opt_tuple_to_atom_if_defined_true(Opt, Opts) ->
1215    case proplists:get_bool(Opt, Opts) of
1216        false -> lists:keydelete(Opt, 1, Opts);
1217        true  -> [Opt | lists:keydelete(Opt, 1, Opts)]
1218    end.
1219
1220%% Fetch the `import'ed files.
1221%% `Defs' is expected to be parsed, but not necessarily post_processed.
1222-spec fetch_imports(defs()) -> [ProtoFile::string()].
1223fetch_imports(Defs) ->
1224    [Path || {import,Path} <- Defs].
1225
1226mk_meta_info(ProtoName, Defs, Opts) ->
1227    meta_msg_containment(ProtoName, Defs)
1228        ++ meta_pkg_containment(ProtoName, Defs, Opts)
1229        ++ meta_service_and_rpc_containment(ProtoName, Defs).
1230
1231meta_msg_containment(ProtoName, Defs) ->
1232    [{{msg_containment, ProtoName}, lists:sort(gpb_lib:msg_names(Defs))}].
1233
1234meta_pkg_containment(ProtoName, Defs, Opts) ->
1235    case proplists:get_value(package, Defs, '$undefined') of
1236        '$undefined' ->
1237            [];
1238        Pkg ->
1239            case proplists:get_bool(use_packages, Opts) of
1240                false ->
1241                    [];
1242                true ->
1243                    [{{pkg_containment,ProtoName}, Pkg}]
1244            end
1245    end.
1246
1247meta_service_and_rpc_containment(ProtoName, Defs) ->
1248    Services = [{Name,RPCs} || {{service,Name}, RPCs} <- Defs],
1249    if Services == [] ->
1250            [];
1251       true ->
1252            ServiceNames = [Name || {Name, _RPCs} <- Services],
1253            RpcNames = lists:append([[{SName, RName}
1254                                      || {RName, _In,_Out, _Opts} <- RPCs]
1255                                     || {SName, RPCs} <- Services]),
1256            [{{service_containment, ProtoName}, lists:sort(ServiceNames)},
1257             {{rpc_containment, ProtoName}, RpcNames}]
1258    end.
1259