1%%% Copyright (C) 2010-2011  Tomas Abrahamsson
2%%%
3%%% Author: Tomas Abrahamsson <tab@lysator.liu.se>
4%%%
5%%% This library is free software; you can redistribute it and/or
6%%% modify it under the terms of the GNU Lesser General Public
7%%% License as published by the Free Software Foundation; either
8%%% version 2.1 of the License, or (at your option) any later version.
9%%%
10%%% This library is distributed in the hope that it will be useful,
11%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
12%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
13%%% Lesser General Public License for more details.
14%%%
15%%% You should have received a copy of the GNU Lesser General Public
16%%% License along with this library; if not, write to the Free Software
17%%% Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston,
18%%% MA  02110-1301  USA
19
20-module(gpb_compile_tests).
21
22-include_lib("kernel/include/file.hrl").
23-include_lib("eunit/include/eunit.hrl").
24-include("../include/gpb.hrl").
25
26-export([test_nifs/1]). %% set whether to test nifs or not
27
28-export([compile_iolist/2]).
29-export([compile_to_string_get_hrl/2]).
30-export([compile_erl_iolist/1]).
31-export([unload_code/1]).
32
33%% NIF related
34-export([nif_tests_check_prerequisites/1]).
35-export([nif_oneof_tests_check_prerequisites/1]).
36-export([nif_oneof_tests_check_prerequisites/3]).
37-export([nif_mapfield_tests_check_prerequisites/1]).
38-export([nif_proto3_tests_check_prerequisites/1]).
39-export([increase_timeouts/1]).
40-export([with_tmpdir/1]).
41-export([in_separate_vm/4]).
42-export([compile_nif_msg_defs/3, compile_nif_msg_defs/4]).
43-export([check_protoc_can_do_oneof/0]).
44-export([check_protoc_can_do_mapfields/0]).
45-export([check_protoc_can_do_proto3/0]).
46
47%% internally used
48-export([main_in_separate_vm/1]).
49
50%% Translators for without user-data
51-export([any_e_atom/1, any_d_atom/1, any_m_atom/2, any_v_atom/2]).
52-export([any_v_atom/1]).
53%% Translators for user-data
54-export([any_e_atom/2, any_d_atom/2, any_m_atom/3, any_v_atom/3]).
55%% Translators for user-data and op
56-export([any_e_atom/3, any_d_atom/3, any_m_atom/4, any_v_atom/4]).
57
58%% Translators for {translate_type, {{msg,uuid},...}} option tests:
59-export([uuid_e/1, uuid_d/1, uuid_m/2, uuid_v/1]).
60
61%% Translators for {translate_type, {bytes,...}} tests
62-export([e_ipv4_addr/2, d_ipv4_addr/2, v_ipv4_addr/2]).
63
64%% Translators for {translate_type, {<Scalar>,...}} tests
65-export([e_astt/1, d_astt/1, v_astt/1]).
66
67%% Translators for {translate_type, {{map,_,_},...}} test
68-export([is_dict/1]).
69
70%% Translators for {translate_field, {<Oneof>,...}} tests
71-export([e_ipv4or6/1, d_ipv4or6/1, v_ipv4or6/1]).
72
73%% Translators for {translate_field, {<Repeated>,...} tests
74-export([id/1, v_is_set/1]).
75
76%% Translators for top-level message tests
77-export([e_value_to_msg/2, d_msg_to_value/2, v_value/2]).
78
79
80-ifndef(NO_HAVE_STACKTRACE_SYNTAX).
81-compile({nowarn_deprecated_function, {erlang, get_stacktrace, 0}}).
82-endif.
83
84%% Include a bunch of tests from gpb_tests.
85%% The shared tests are for stuff that must work both
86%% for gpb and for the code that gpb_compile generates.
87%% (I know it is a bit unorthodox to include .erl files,
88%% but actually seems to work. Better than duplicating tests)
89-define(gpb_compile_common_tests, true).
90-ifdef(gpb_compile_common_tests).
91-include("gpb_tests.erl").
92-else.  %% gpb_compile_common_tests
93-record(m1,{a}).
94-endif. %% gpb_compile_common_tests
95
96-define(is_string(X), is_list(X)).
97
98parses_non_importing_file_test() ->
99    Contents = iolist_to_binary(
100                 ["message Msg { required uint32 field1 = 1; }\n"]),
101    ok = gpb_compile:file(
102           "X.proto",
103           [mk_fileop_opt([{read_file, fun(_) -> {ok, Contents} end}]),
104            mk_defs_probe_sender_opt(self()),
105            {i,"."}]),
106    [{{msg,'Msg'},_}] = receive_filter_sort_msgs_defs().
107
108
109parses_importing_file_test() ->
110    ContentsX = iolist_to_binary(
111                  ["import \"Y.proto\";\n"
112                   "message X { required Y f1 = 1; }\n"]),
113    ContentsY = iolist_to_binary(
114                  ["message Y { required uint32 f1 = 1; }\n"]),
115    ok = gpb_compile:file(
116           "X.proto",
117           [mk_fileop_opt([{read_file, fun("X.proto") -> {ok, ContentsX};
118                                          ("Y.proto") -> {ok, ContentsY}
119                                       end}]),
120            mk_defs_probe_sender_opt(self()),
121            {i,"."}]),
122    [{{msg,'X'},_}, {{msg,'Y'},_}] = receive_filter_sort_msgs_defs().
123
124
125import_fetcher_test() ->
126    Master = self(),
127    ContentsX = iolist_to_binary(
128                  ["import \"Y.proto\";\n"
129                   "message X { required Y f1 = 1; }\n"]),
130    ContentsY = iolist_to_binary(
131                  ["message Y { required uint32 f1 = 1; }\n"]),
132    FileReadOpt = mk_fileop_opt([{read_file,
133                                  fun("X.proto") ->
134                                          Master ! {read,"X.proto"},
135                                          {ok, ContentsX};
136                                     ("Y.proto") ->
137                                          Master ! {read,"Y.proto"},
138                                          {ok, ContentsY}
139                                  end}]),
140    %% Importer returns `from_file'
141    ok = gpb_compile:file(
142           "X.proto",
143           [{import_fetcher, fun(F) -> Master ! {redir_to_file,F},
144                                       from_file
145                             end},
146            FileReadOpt, {i,"."}]),
147    [{redir_to_file,"X.proto"},
148     {read,"X.proto"},
149     {redir_to_file,"Y.proto"},
150     {read,"Y.proto"}] = flush_msgs(),
151
152    %% Importer returns contents
153    ok = gpb_compile:file(
154           "X.proto",
155           [{import_fetcher, fun(F) ->
156                                     Master ! {fetched,F},
157                                     {ok, binary_to_list(
158                                            case F of
159                                                "X.proto" -> ContentsX;
160                                                "Y.proto" -> ContentsY
161                                            end)}
162                             end},
163            FileReadOpt, {i,"."}]),
164    [{fetched,"X.proto"},
165     {fetched,"Y.proto"}] = flush_msgs(),
166
167    %% Importer returns error
168    {error,{fetcher_issue,"Y.proto",reason_for_y}} =
169        gpb_compile:file(
170          "X.proto",
171          [{import_fetcher, fun(F) ->
172                                    case F of
173                                        "X.proto" -> from_file;
174                                        "Y.proto" -> {error,reason_for_y}
175                                    end
176                            end},
177           FileReadOpt, {i,"."}]),
178
179    %% Make sure we've flushed every message, synchronously
180    ok = gpb_compile:string(x, binary_to_list(ContentsY),
181                            [mk_defs_probe_sender_opt(self()),
182                             mk_fileop_opt([])]),
183    [_|_] = receive_filter_sort_msgs_defs(),
184    flush_msgs(),
185    ok.
186
187
188
189flush_msgs() ->
190    receive
191        M ->
192             [M | flush_msgs()]
193    after 0 ->
194            []
195    end.
196
197parses_file_to_binary_test() ->
198    Contents = <<"message Msg { required uint32 field1 = 1; }\n">>,
199    {ok, 'X', Code, []} =
200        gpb_compile:file(
201          "X.proto",
202          [mk_fileop_opt([{read_file, fun(_) -> {ok, Contents} end}]),
203           mk_defs_probe_sender_opt(self()),
204           {i,"."},
205           binary, return_warnings]),
206    true = is_binary(Code),
207    [{{msg,'Msg'},_}] = receive_filter_sort_msgs_defs().
208
209parses_file_to_msg_defs_test() ->
210    Contents = <<"message Msg { required uint32 field1 = 1; }\n">>,
211    {ok, [{{msg_containment,"X"},['Msg']},
212          {{msg,'Msg'},[#?gpb_field{}]}]=MsgDefs} =
213        gpb_compile:file(
214          "X.proto",
215          [mk_fileop_opt([{read_file, fun(_) -> {ok, Contents} end}]),
216           {i,"."},
217           to_proto_defs, report_warnings]),
218    %% Check that the returned msgdefs are usable
219    M = compile_defs(MsgDefs),
220    ?assertMatch(<<_/binary>>, M:encode_msg({'Msg',33})),
221    unload_code(M).
222
223parses_msgdefs_to_binary_test() ->
224    Defs = [{{msg,'Msg'},
225             [#?gpb_field{name=field1, rnum=2, fnum=1, type=uint32,
226                          occurrence=required, opts=[]}]}],
227    M = find_unused_module(),
228    {ok, M, Code} = gpb_compile:proto_defs(M, Defs, [binary]),
229    true = is_binary(Code).
230
231parses_and_generates_good_code_also_for_reserved_keywords_test() ->
232    %% use erlang reserved words on as many .proto locations as possible
233    %% to verify that the generated code compiles and works.
234    M = compile_iolist(["enum if { begin=1; end=2; }"
235                        "message catch { required if case = 1; }\n"]),
236    ?assertMatch(true, is_binary(M:encode_msg({'catch', 'begin'}))),
237    unload_code(M).
238
239parses_and_generates_good_code_also_for_empty_msgs_test() ->
240    M = compile_iolist(["message m1 { }\n"]),
241    ?assertMatch(true, is_binary(M:encode_msg({m1}))),
242    ?assertMatch({m1}, M:decode_msg(M:encode_msg({m1}), m1)),
243    unload_code(M).
244
245encoding_decoding_functions_for_epb_compatibility_test() ->
246    epb_encoding_decoding_functions_aux(epb_compatibility).
247
248encoding_decoding_functions_for_epb_functions_test() ->
249    epb_encoding_decoding_functions_aux(epb_functions).
250
251epb_encoding_decoding_functions_aux(Opt) ->
252    DefsM1 = "message m1 { required uint32 a = 1; }\n",
253    DefsNoMsgs = "enum ee { a = 0; }\n",
254    {error, Reason1, []} = compile_iolist_get_errors_or_warnings(
255                             DefsM1,
256                             [Opt, maps]),
257    true = is_list(gpb_compile:format_error(Reason1)),
258
259    %% Verify we get an error for epb_compatibility with a message named 'msg'
260    %% due to collision with standard gpb encode_msg/decode_msg functions
261    {error, Reason2, []} = compile_iolist_get_errors_or_warnings(
262                             "message msg { }\n",
263                             [Opt, maps]),
264    true = is_list(gpb_compile:format_error(Reason2)),
265
266    Mod1 = compile_iolist(DefsM1, [Opt]),
267    M1 = #m1{a=1234},
268    B1 = Mod1:encode(M1),
269    ?assertMatch(true, is_binary(B1)),
270    B1 = Mod1:encode_m1(M1),
271    M1 = Mod1:decode(m1, B1),
272    M1 = Mod1:decode_m1(B1),
273    unload_code(Mod1),
274
275    %% verify no compatibility functions generated with no compat options
276    Mod2 = compile_iolist(DefsM1, []),
277    ?assertError(undef, Mod2:encode(M1)),
278    ?assertError(undef, Mod2:encode_m1(M1)),
279    ?assertError(undef, Mod2:decode(m1, B1)),
280    ?assertError(undef, Mod2:decode_m1(B1)),
281    unload_code(Mod2),
282
283    %% verify functions generated ok when no msgs specified
284    Mod3 = compile_iolist(DefsNoMsgs, [Opt]),
285    _ = Mod3:module_info(),
286    unload_code(Mod3).
287
288epb_compatibility_opt_implies_pb_modsuffix_test() ->
289    Contents = <<"message m { required uint32 f = 1; }\n">>,
290    T = self(),
291    ok = gpb_compile:file(
292           "X.proto",
293           [mk_fileop_opt([{read_file, fun(_) -> {ok, Contents} end},
294                           {write_file, fun(Nm, _) -> T ! {file_name, Nm},
295                                                      ok
296                                        end}]),
297            {i,"."},
298            epb_compatibility]),
299    ["X_pb.erl", "X_pb.hrl"] =
300        lists:sort([receive {file_name, Nm1} -> Nm1 end,
301                    receive {file_name, Nm2} -> Nm2 end]).
302
303epb_compatibility_opt_implies_msg_name_to_lower_test() ->
304    Contents = <<"message SomeMsg { required uint32 f = 1; }\n">>,
305    ok = gpb_compile:file(
306           "X.proto",
307           [mk_fileop_opt([{read_file, fun(_) -> {ok, Contents} end}]),
308            mk_defs_probe_sender_opt(self()),
309            {i,"."},
310            epb_compatibility]),
311    [{{msg,somemsg},_}] = receive_filter_sort_msgs_defs().
312
313epb_compatibility_opt_implies_defaults_for_omitted_optionals_test() ->
314    Proto = ["message m {",
315             "  optional uint32 f = 1 [default=3];\n",
316             %% for verifying that type-defaults is not implied:
317             "  optional uint32 g = 2;\n",
318             "}\n"],
319    M = compile_iolist(Proto, [epb_compatibility]),
320    {m,3,undefined} = M:decode_msg(<<>>, m),
321    unload_code(M).
322
323field_pass_as_params_test() ->
324    {timeout,10,fun field_pass_as_params_test_aux/0}.
325
326field_pass_as_params_test_aux() ->
327    MsgDef = ["message m2 { required uint32 f22 = 1; }"
328              "message m1 { required uint32  f1 = 1;",
329              "             optional fixed32 f2 = 2;",
330              "             repeated fixed32 f3 = 3;",
331              "             repeated fixed32 f4 = 4 [packed];",
332              "             repeated uint32  f5 = 5;",
333              "             repeated uint32  f6 = 6 [packed];",
334              "             optional string  f7 = 7;",
335              "             optional m2      f8 = 8;",
336              "             oneof o1 { m2     x1 = 15;",
337              "                        uint32 y1 = 16; };",
338              "             oneof o2 { m2     x2 = 25;",
339              "                        uint32 y2 = 26; }",
340              "             oneof o3 { m2     x3 = 35;",
341              "                        uint32 y3 = 36; }",
342              "}"],
343    Msg = {m1, 4711, undefined,      %% f1,f2
344           [4713,4714], [4715,4716], %% f3,f4
345           [4717,4718], [4719,4720], %% f5,f6
346           "abc", {m2,33}, {x1,{m2,45}}, {y2,226}, undefined},
347    lists:foreach(
348      fun(Opts) ->
349              ?assertMatch({Msg,_},
350                           {encode_decode_round_trip(MsgDef, Msg, Opts), Opts})
351      end,
352      [[{field_pass_method,pass_as_params}],
353       [{field_pass_method,pass_as_record}],
354       [{{field_pass_method,m1},pass_as_record},
355        {{field_pass_method,m2},pass_as_params}],
356       [{{field_pass_method,m1},pass_as_params},
357        {{field_pass_method,m2},pass_as_record}]]).
358
359encode_decode_round_trip(MsgDefAsIoList, Msg, Opts) ->
360    M = compile_iolist(MsgDefAsIoList, Opts),
361    MsgName = element(1, Msg),
362    Result = M:decode_msg(M:encode_msg(Msg), MsgName),
363    unload_code(M),
364    Result.
365
366mk_fileop_opt(NonDefaults) ->
367    NonDefaults1 = [case Op of
368                        read_file_info -> {Op, mk_with_basename_1(Fn)};
369                        read_file      -> {Op, mk_with_basename_1(Fn)};
370                        write_file     -> {Op, mk_with_basename_2(Fn)}
371                    end
372                    || {Op, Fn} <- NonDefaults],
373    {file_op, NonDefaults1 ++ mk_default_file_ops()}.
374
375mk_with_basename_1(Fn) -> fun(Path) -> Fn(filename:basename(Path)) end.
376mk_with_basename_2(Fn) -> fun(Path, A) -> Fn(filename:basename(Path), A) end.
377
378mk_default_file_ops() ->
379    [{read_file_info, fun(_FileName) -> {ok, #file_info{access=read}} end},
380     {read_file,      fun(_FileName) -> {error, enoent} end},
381     {write_file,     fun(_FileName, _Bin) -> ok end}].
382
383mk_defs_probe_sender_opt(SendTo) ->
384    {probe_defs, fun(Defs) -> SendTo ! {defs, Defs} end}.
385
386receive_filter_sort_msgs_defs() ->
387    lists:sort([Msg || {{msg,_},_} = Msg <- receive {defs, Defs} -> Defs end]).
388
389-record(m9,{aa, bb, cc, dd}).
390-record(m10,{aaa}).
391
392code_generation_when_submsg_size_is_known_at_compile_time_test() ->
393    KnownSizeM9 =
394        [{{msg,m9}, [#?gpb_field{name=aa, type={enum,e}, occurrence=required,
395                                 fnum=1, rnum=#m9.aa, opts=[]},
396                     #?gpb_field{name=bb, type=fixed32, occurrence=required,
397                                 fnum=2, rnum=#m9.bb, opts=[]},
398                     #?gpb_field{name=cc, type=fixed64, occurrence=required,
399                                 fnum=3, rnum=#m9.cc, opts=[]},
400                     #?gpb_field{name=dd, type={msg,m10}, occurrence=required,
401                                 fnum=4, rnum=#m9.dd, opts=[]}]}],
402    UnknownSizeM9 =
403        [{{msg,m9}, [#?gpb_field{name=aa, type={enum,e}, occurrence=optional,
404                                 fnum=1, rnum=#m9.aa, opts=[]},
405                     #?gpb_field{name=bb, type=fixed32, occurrence=optional,
406                                 fnum=2, rnum=#m9.bb, opts=[]},
407                     #?gpb_field{name=cc, type=fixed64, occurrence=optional,
408                                 fnum=3, rnum=#m9.cc, opts=[]},
409                     #?gpb_field{name=dd, type={msg,m10}, occurrence=required,
410                                 fnum=4, rnum=#m9.dd, opts=[]}]}],
411
412    CommonDefs =
413        [{{msg,m1}, [#?gpb_field{name=a, type={msg,m9}, occurrence=required,
414                                 fnum=1, rnum=2, opts=[]}]},
415         {{msg,m10},[#?gpb_field{name=aaa, type=bool, occurrence=required,
416                                 fnum=1, rnum=#m10.aaa, opts=[]}]},
417         {{enum,e}, [{x1, 1}, {x2, 2}]} %% all enum values same encode size
418        ],
419
420    M1 = compile_defs(CommonDefs++KnownSizeM9),
421    M2 = compile_defs(CommonDefs++UnknownSizeM9),
422    Msg = #m1{a=#m9{aa=x1, bb=33, cc=44, dd=#m10{aaa=true}}},
423    Encoded1 = M1:encode_msg(Msg),
424    Encoded2 = M2:encode_msg(Msg),
425    Encoded1 = Encoded2,
426    unload_code(M1),
427    unload_code(M2).
428
429code_generation_when_map_enum_size_is_unknown_at_compile_time_test() ->
430    %% calculation of whether e_varint is needed or not when only
431    %% an enum needs it, when that enum is in a map
432    Defs = [{{msg,m1}, [#?gpb_field{name=a, type={map,bool,{enum,e1}},
433                                    fnum=1, rnum=2, occurrence=repeated,
434                                    opts=[]}]},
435            {{enum,e1}, [{x1,0},{x2,128}]}], %% encodes to different sizes
436    M = compile_defs(Defs),
437    true = is_binary(M:encode_msg({m1,[{true,x1}]})),
438    unload_code(M).
439
440no_dialyzer_attributes_for_erlang_version_pre_18_test() ->
441    %% -dialyzer({nowarn_function,f/1}). attrs first appeared in Erlang/OTP 18
442    %% such attributes are emitted for verifiers and map translators
443    Proto = "message m { map<uint32,string> m = 1; }",
444    S1 = compile_to_string(Proto, [{target_erlang_version,17}]),
445    false = gpb_lib:is_substr("-dialyzer(", S1),
446    S2 = compile_to_string(Proto, [{target_erlang_version,18}]),
447    true = gpb_lib:is_substr("-dialyzer(", S2).
448
449empty_group_test() ->
450    M = compile_iolist("syntax = \"proto2\";
451                        message Quz {optional group E = 11 {}}",
452                       [{verify,always},
453                        to_proto_defs]),
454    EStart = <<91>>, % (11 bsl 3) bor 3
455    EEnd = <<92>>,   % (11 bsl 3) bor 4
456    EGroup = <<EStart/binary, EEnd/binary>>,
457    EGroup = M:encode_msg({'Quz',{'Quz.E'}}),
458    unload_code(M).
459
460%% --- default values --------------
461
462default_value_handling_test() ->
463    Proto = ["message m {",
464             "  optional uint32 f1 = 1;",
465             "  optional uint32 f2 = 2 [default=2];",
466             "}"],
467    [begin
468         M = compile_iolist(Proto, Opts ++ OptVariation),
469         ?assertMatch({Expected,_}, {M:decode_msg(<<>>, m), Opts}),
470         unload_code(M)
471     end
472     || {Expected, Opts} <-
473            [{{m,undefined,undefined}, []},
474             {{m,0,2},         [defaults_for_omitted_optionals,
475                                type_defaults_for_omitted_optionals]},
476             {{m,undefined,2}, [defaults_for_omitted_optionals]},
477             {{m,0,0},         [type_defaults_for_omitted_optionals]}],
478        OptVariation <- [[pass_as_params],
479                         [pass_as_record]]].
480
481type_default_option_should_be_ignored_for_proto3_test() ->
482    Proto = ["syntax=\"proto3\";\n",
483             "message m { uint32 f1 = 1; };"],
484    M = compile_iolist(Proto, [{type_defaults_for_omitted_optionals, false}]),
485    {m,0} = M:decode_msg(<<>>, m),
486    unload_code(M).
487
488%% --- introspection ---------------
489
490introspection_package_name_test() ->
491    M = compile_iolist(["package foo.bar;",
492                        "message M { required uint32 f1=1; }"]),
493    'foo.bar' = M:get_package_name(),
494    unload_code(M),
495    M = compile_iolist(["message M { required uint32 f1=1; }"]),
496    undefined = M:get_package_name(),
497    unload_code(M).
498
499introspection_msgs_test() ->
500    M = compile_iolist(["message msg1 { required uint32 f1=1; }"]),
501    [msg1] = M:get_msg_names(),
502    [#?gpb_field{name=f1, type=uint32, fnum=1}] = M:find_msg_def(msg1),
503    [#?gpb_field{name=f1, type=uint32, fnum=1}] = M:fetch_msg_def(msg1),
504    error = M:find_msg_def(msg_ee),
505    ?assertError(_, M:fetch_msg_def(msg_ee)),
506    unload_code(M).
507
508introspection_enums_test() ->
509    %% Names
510    M = compile_iolist(["enum e1 { n1=1; n2=2; }",
511                        "message msg1 { required uint32 f1=1; }"]),
512    [e1] = M:get_enum_names(),
513    %% find and fetch
514    [{n1,1},{n2,2}] = M:find_enum_def(e1),
515    error = M:find_enum_def(ee),
516    [{n1,1},{n2,2}] = M:fetch_enum_def(e1),
517    ?assertError(_, M:fetch_enum_def(ee)),
518    %% symbol <--> value mapping
519    n1 = M:enum_symbol_by_value(e1, 1),
520    n2 = M:enum_symbol_by_value(e1, 2),
521    n1 = M:enum_symbol_by_value_e1(1),
522    n2 = M:enum_symbol_by_value_e1(2),
523    1  = M:enum_value_by_symbol(e1, n1),
524    2  = M:enum_value_by_symbol(e1, n2),
525    1  = M:enum_value_by_symbol_e1(n1),
526    2  = M:enum_value_by_symbol_e1(n2),
527    unload_code(M).
528
529introspection_groups_test() ->
530    M0 = compile_iolist(["enum e1 { n1=1; n2=2; }"]), % no message or groups
531    [] = M0:get_msg_names(),
532    [] = M0:get_group_names(),
533    [] = M0:get_msg_or_group_names(),
534    error = M0:find_msg_def(e1), % e1 for the lack of better...
535    ?assertError(_, M0:fetch_msg_def(e1)),
536    M1 = compile_iolist(["message m1 {",
537                         "  required group g = 1 { required uint32 f = 2; };",
538                         "}"]),
539    [m1] = M1:get_msg_names(),
540    [G] = M1:get_group_names(),
541    [m1, G] = lists:sort(M1:get_msg_or_group_names()),
542    [#?gpb_field{name=g, type={group,G}}] = M1:find_msg_def(m1),
543    [#?gpb_field{name=f, type=uint32}]    = M1:find_msg_def(G),
544    [#?gpb_field{name=g, type={group,G}}] = M1:fetch_msg_def(m1),
545    [#?gpb_field{name=f, type=uint32}]    = M1:fetch_msg_def(G),
546    unload_code(M0),
547    unload_code(M1).
548
549introspection_defs_as_proplists_test() ->
550    Proto = ["message msg1 { required uint32 f1=1; }",
551             "service s1 {",
552             "  rpc req1(msg1) returns (msg1);",
553             "  rpc req2(msg1) returns (msg1);",
554             "}",
555             "service s2 {",
556             "  rpc req2(msg1) returns (msg1);",
557             "}"],
558    %% With the defs_as_proplists option
559    M = compile_iolist(Proto, [defs_as_proplists]),
560    NoIStr = {input_stream, false},
561    NoOStr = {output_stream, false},
562    NoOpts = {opts, []},
563    [[{name,       f1},
564      {fnum,       1},
565      {rnum,       2},
566      {type,       uint32},
567      {occurrence, required},
568      {opts,       []}]] = PL = M:find_msg_def(msg1),
569    [{{msg, msg1}, PL}] = M:get_msg_defs(),
570    [s1, s2] = M:get_service_names(),
571    {{service, s1},
572     [[{name, req1}, {input, msg1}, {output, msg1}, NoIStr, NoOStr, NoOpts],
573      [{name, req2}, {input, msg1}, {output, msg1}, NoIStr, NoOStr, NoOpts]]} =
574        M:get_service_def(s1),
575    {{service, s2},
576     [[{name, req2}, {input, msg1}, {output, msg1}, NoIStr, NoOStr, NoOpts]]} =
577        M:get_service_def(s2),
578    [{name, req1}, {input, msg1}, {output, msg1}, NoIStr, NoOStr, NoOpts] =
579        M:find_rpc_def(s1, req1),
580    [{name, req2}, {input, msg1}, {output, msg1}, NoIStr, NoOStr, NoOpts] =
581        M:find_rpc_def(s2, req2),
582    unload_code(M),
583
584    %% No defs_as_proplists option
585    M = compile_iolist(Proto, [{defs_as_proplists, false}]),
586    [#?gpb_field{name       = f1,
587                 fnum       = 1,
588                 rnum       = 2,
589                 type       = uint32,
590                 occurrence = required,
591                 opts       = []}] = Fs = M:find_msg_def(msg1),
592    [{{msg, msg1}, Fs}] = Defs = M:get_msg_defs(),
593    {{service, s1},
594     [#?gpb_rpc{name=req1, input=msg1, output=msg1},
595      #?gpb_rpc{name=req2, input=msg1, output=msg1}]} =
596        M:get_service_def(s1),
597    {{service, s2},
598     [#?gpb_rpc{name=req2, input=msg1, output=msg1}]} =
599        M:get_service_def(s2),
600    #?gpb_rpc{name=req1, input=msg1, output=msg1} = M:find_rpc_def(s1, req1),
601    #?gpb_rpc{name=req2, input=msg1, output=msg1} = M:find_rpc_def(s2, req2),
602    unload_code(M),
603
604    %% make sure the generated erl file does not -include[_lib] "gpb.hrl"
605    Master = self(),
606    ReportOutput = fun(FName, Contents) ->
607                           Master ! {filename:extension(FName), Contents},
608                           ok
609                   end,
610    FileOpOpt = mk_fileop_opt([{write_file, ReportOutput}]),
611    ok = gpb_compile:proto_defs(M, Defs, [FileOpOpt, defs_as_proplists]),
612    receive {".hrl", Hrl1} -> nomatch = re:run(Hrl1, "\"gpb.hrl\"") end,
613    receive {".erl", Erl1} -> nomatch = re:run(Erl1, "\"gpb.hrl\"") end,
614    ok = gpb_compile:proto_defs(M, Defs, [FileOpOpt, defs_as_proplists,
615                                          include_as_lib]),
616    receive {".hrl", Hrl2} -> nomatch = re:run(Hrl2, "\"gpb.hrl\"") end,
617    receive {".erl", Erl2} -> nomatch = re:run(Erl2, "\"gpb.hrl\"") end.
618
619introspection_rpcs_test() ->
620    Proto = ["message m1 { required uint32 f1=1; }",
621             "message m2 { required uint32 f2=1; }",
622             "service s1 {",
623             "  rpc req1(m1) returns (m2);",
624             "  rpc req2(m2) returns (m1);",
625             "}"],
626    M = compile_iolist(Proto),
627    {{service, s1},
628     [#?gpb_rpc{name=req1, input='m1', output='m2'},
629      #?gpb_rpc{name=req2, input='m2', output='m1'}]} = M:get_service_def(s1),
630    [req1, req2] = M:get_rpc_names(s1),
631    #?gpb_rpc{name=req1, input='m1', output='m2'} = M:find_rpc_def(s1, req1),
632    #?gpb_rpc{name=req1, input='m1', output='m2'} = M:fetch_rpc_def(s1, req1),
633    #?gpb_rpc{name=req2, input='m2', output='m1'} = M:fetch_rpc_def(s1, req2),
634    #?gpb_rpc{name=req2, input='m2', output='m1'} = M:find_rpc_def(s1, req2),
635    error = M:find_rpc_def(s1, req_ee),
636    ?assertError(_, M:fetch_rpc_def(s2, req_ee)),
637    unload_code(M).
638
639introspection_multiple_rpcs_test() ->
640    Proto = ["message m1 { required uint32 f1=1; }",
641             "message m2 { required uint32 f2=1; }",
642             "service s1 {",
643             "  rpc req1(m1) returns (m2);",
644             "  rpc req2(m2) returns (m1);",
645             "}",
646             "service s2 {",
647             "  rpc req21(m2) returns (m1);",
648             "  rpc req22(m1) returns (m2);",
649             "}"],
650    M = compile_iolist(Proto),
651    [s1, s2] = M:get_service_names(),
652    {{service, s1},
653     [#?gpb_rpc{name=req1, input='m1', output='m2'},
654      #?gpb_rpc{name=req2, input='m2', output='m1'}]} = M:get_service_def(s1),
655    {{service, s2},
656     [#?gpb_rpc{name=req21, input='m2', output='m1'},
657      #?gpb_rpc{name=req22, input='m1', output='m2'}]} = M:get_service_def(s2),
658    #?gpb_rpc{name=req21,  input='m2', output='m1'} = M:find_rpc_def(s2, req21),
659    #?gpb_rpc{name=req1, input='m1', output='m2'} = M:fetch_rpc_def(s1, req1),
660    #?gpb_rpc{name=req2,  input='m2', output='m1'} = M:fetch_rpc_def(s1, req2),
661    #?gpb_rpc{name=req22, input='m1', output='m2'} = M:find_rpc_def(s2, req22),
662    error = M:find_rpc_def(s1, req_ee),
663    error = M:find_rpc_def(s2, req_aa),
664    ?assertError(_, M:fetch_rpc_def(s2, req_ee)),
665    ?assertError(_, M:fetch_rpc_def(s1, req_aa)),
666    unload_code(M).
667
668%% --- decoder tests ---------------
669
670decodes_overly_long_varints_test() ->
671    M = compile_defs([{{msg,m1}, [#?gpb_field{name=a, type=int32,
672                                              fnum=1, rnum=#m1.a,
673                                              occurrence=required, opts=[]}]}]),
674    #m1{a=54} = M:decode_msg(<<8, 54>>, m1), %% canonically encoded
675    #m1{a=54} = M:decode_msg(<<8, (128+54), 128, 128, 0>>, m1),
676    unload_code(M).
677
678decode_failure_error_for_invalid_binary_test() ->
679    M = compile_defs([{{msg,m1}, [#?gpb_field{name=a, type=int32,
680                                              fnum=1, rnum=#m1.a,
681                                              occurrence=required,
682                                              opts=[]}]}]),
683    Bad1 = <<8>>,
684    ?assertError({gpb_error,
685                  {decoding_failure,
686                   {Bad1, m1, {_Class,_Reason,_Stack}}}},
687                 M:decode_msg(Bad1, m1)),
688    unload_code(M).
689
690%% --- scoped messages ---------------
691
692dotted_names_gives_no_compilation_error_test() ->
693    %% make sure dotted names does not give compilation errors,
694    %% for instance if some generated code would rely on names
695    %% having the same syntax as erlang atoms, or, when prepended
696    %% with an upper case character, having the same syntax as an
697    %% erlang variable
698    M = compile_iolist(["message m1 {"
699                        "  message m2 { required uint32 x = 1; }",
700                        "  enum    e1 { ea = 17; eb = 18; }",
701                        "  required m2     y = 1;",
702                        "  required .m1.m2 z = 2;",
703                        "  required e1     w = 3;",
704                        "}",
705                        "message m3 { required m1.m2 b = 1; }"]),
706    M1Msg = {m1, {'m1.m2', 1}, {'m1.m2', 2}, ea},
707    Data = M:encode_msg(M1Msg),
708    M1Msg = M:decode_msg(Data, m1),
709    unload_code(M).
710
711%% --- module/msg name prefix/suffix ---------------
712module_msg_name_prefix_test() ->
713    Proto = <<"message msg1 { required uint32 f1=1; }\n">>,
714    Master = self(),
715    ReadInput = fun(FName) -> Master ! {read, FName}, {ok, Proto} end,
716    ReportOutput = fun(FName, Contents) ->
717                           Ext = list_to_atom(tl(filename:extension(FName))),
718                           Master ! {write, {Ext, FName, Contents}},
719                           ok
720                   end,
721    FileOpOpt = mk_fileop_opt([{read_file, ReadInput},
722                               {write_file, ReportOutput}]),
723    ModPrefix = "mp_",
724    MsgPrefix = "mm_",
725    ModSuffix = "_xp",
726    MsgSuffix = "_xm",
727    ok = gpb_compile:file("m.proto",
728                          [FileOpOpt, {i,"."},
729                           {module_name_prefix, ModPrefix},
730                           {msg_name_prefix, MsgPrefix},
731                           {module_name_suffix, ModSuffix},
732                           {msg_name_suffix, MsgSuffix}]),
733    receive
734        {read, "m.proto"} -> ok;
735        {read, X} -> erlang:error({"reading from odd file", X})
736    end,
737    receive
738        {write, {hrl, "mp_m_xp.hrl", Hrl}} ->
739            assert_contains_regexp(Hrl, "mm_msg1_xm"),
740            ok;
741        {write, {hrl, "m.hrl", _}} ->
742            erlang:error("hrl file not prefixed or suffixed!");
743        {write, {hrl, X2, C2}} ->
744            erlang:error({"writing odd hrl file!", X2, C2})
745    end,
746    receive
747        {write, {erl, "mp_m_xp.erl", Erl}} ->
748            assert_contains_regexp(Erl, "-include.*\"mp_m_xp.hrl\""),
749            assert_contains_regexp(Erl, "-module.*mp_m_xp"),
750            assert_contains_regexp(Erl, "mm_msg1_xm"),
751            ok;
752        {write, {erl, "m.erl", _}} ->
753            erlang:error("erl file not prefixed or suffixed!");
754        {write, {erl, X3, C3}} ->
755            erlang:error({"writing odd erl file!", X3, C3})
756    end,
757    ok.
758
759module_name_test() ->
760    Proto = <<"message msg1 { required uint32 f1=1; }\n">>,
761    Master = self(),
762    ReadInput = fun(FName) -> Master ! {read, FName}, {ok, Proto} end,
763    ReportOutput = fun(FName, Contents) ->
764                           Ext = list_to_atom(tl(filename:extension(FName))),
765                           Master ! {write, {Ext, FName, Contents}},
766                           ok
767                   end,
768    FileOpOpt = mk_fileop_opt([{read_file, ReadInput},
769                               {write_file, ReportOutput}]),
770    ok = gpb_compile:file("m.proto",
771                          [FileOpOpt, {i,"."},
772                           {module_name, "new"}]),
773    receive
774        {read, "m.proto"} -> ok;
775        {read, X} -> erlang:error({"reading from odd file", X})
776    end,
777    receive
778        {write, {hrl, "new.hrl", _Hrl}} ->
779            ok;
780        {write, {hrl, "m.hrl", _}} ->
781            erlang:error("expected new.hrl, not m.hrl!");
782        {write, {hrl, X2, C2}} ->
783            erlang:error({"writing odd hrl file!", X2, C2})
784    end,
785    receive
786        {write, {erl, "new.erl", Erl}} ->
787            assert_contains_regexp(Erl, "-include.*\"new.hrl\""),
788            assert_contains_regexp(Erl, "-module.*new"),
789            ok;
790        {write, {erl, "m.erl", _}} ->
791            erlang:error("expected new.erl, not m.erl!");
792        {write, {erl, X3, C3}} ->
793            erlang:error({"writing odd erl file!", X3, C3})
794    end,
795    ok.
796
797module_name_with_suffix_prefix_test() ->
798    %% interaction between options module_name and module_name_prefix/suffix
799    Proto = <<"message msg1 { required uint32 f1=1; }\n">>,
800    Master = self(),
801    ReadInput = fun(FName) -> Master ! {read, FName}, {ok, Proto} end,
802    ReportOutput = fun(FName, Contents) ->
803                           Ext = list_to_atom(tl(filename:extension(FName))),
804                           Master ! {write, {Ext, FName, Contents}},
805                           ok
806                   end,
807    FileOpOpt = mk_fileop_opt([{read_file, ReadInput},
808                               {write_file, ReportOutput}]),
809    ModPrefix = "mp_",
810    ModSuffix = "_xp",
811    ok = gpb_compile:file("m.proto",
812                          [FileOpOpt, {i,"."},
813                           {module_name, "new"},
814                           {module_name_prefix, ModPrefix},
815                           {module_name_suffix, ModSuffix}]),
816    receive
817        {read, "m.proto"} -> ok;
818        {read, X} -> erlang:error({"reading from odd file", X})
819    end,
820    receive
821        {write, {hrl, "mp_new_xp.hrl", _Hrl}} ->
822            ok;
823        {write, {hrl, "m.hrl", _}} ->
824            erlang:error("hrl file not changed + prefixed or suffixed!");
825        {write, {hrl, X2, C2}} ->
826            erlang:error({"writing odd hrl file!", X2, C2})
827    end,
828    receive
829        {write, {erl, "mp_new_xp.erl", Erl}} ->
830            assert_contains_regexp(Erl, "-include.*\"mp_new_xp.hrl\""),
831            assert_contains_regexp(Erl, "-module.*mp_new_xp"),
832            ok;
833        {write, {erl, "m.erl", _}} ->
834            erlang:error("erl file not changed + prefixed or suffixed!");
835        {write, {erl, X3, C3}} ->
836            erlang:error({"writing odd erl file!", X3, C3})
837    end,
838    ok.
839
840assert_contains_regexp(IoData, Re) ->
841    case re:run(IoData, Re) of
842        {match, _} -> ok;
843        nomatch    ->
844            ?debugFmt("~nERROR: Regexp ~s not found in:~n~s~n", [Re, IoData]),
845            erlang:error({"Re ", Re, "not found in", IoData})
846    end.
847
848%% --- bytes ----------
849
850list_as_bytes_indata_test() ->
851    HasBinary = (catch binary:copy(<<1>>)) == <<1>>, % binary exists since R14A
852    if HasBinary ->
853            M = compile_iolist(["message m1 { required bytes f1 = 1; }"]),
854            Data = M:encode_msg({m1, [1,2,3,4]}),
855            {m1, <<1,2,3,4>>} = M:decode_msg(Data, m1),
856            unload_code(M);
857       true ->
858            %% nothing to test
859            ok
860    end.
861
862copy_bytes_unconditionally_test() ->
863    HasBinary = (catch binary:copy(<<1>>)) == <<1>>, % binary exists since R14A
864    if HasBinary ->
865            M = compile_iolist(["message m1 { required bytes f1 = 1; }"],
866                               [{copy_bytes, true}]),
867            Data = M:encode_msg({m1, <<"d">>}),
868            {m1, <<"d">>=Bs} = M:decode_msg(Data, m1),
869            %% If the Bs has not been copied, then it is a sub-binary
870            %% of a larger binary: of the message, ie of Data.
871            %% So verify copying by verifying size of referenced data.
872            ?assertEqual(byte_size(Bs), binary:referenced_byte_size(Bs)),
873            unload_code(M);
874       true ->
875            %% nothing to test
876            ok
877    end.
878
879copy_bytes_false_test() ->
880    M = compile_iolist(["message m1 { required bytes f1 = 1; }"],
881                       [{copy_bytes, false}]),
882    Data = M:encode_msg({m1, <<"d">>}),
883    {m1, <<"d">>=Bs} = M:decode_msg(Data, m1),
884    HasBinary = (catch binary:copy(<<1>>)) == <<1>>, % binary exists since R14A
885    if HasBinary ->
886            %% If the StrBin has not been copied, then it is a sub-binary
887            %% of a larger binary: of the message, ie of Data.
888            %% So verify copying by verifying size of referenced data.
889            ?assertEqual(byte_size(Data), binary:referenced_byte_size(Bs));
890       true ->
891            ok
892    end,
893    unload_code(M).
894
895copy_bytes_auto_test() ->
896    M = compile_iolist(["message m1 { required bytes f1 = 1; }"],
897                       [{copy_bytes, auto}]),
898    Data = M:encode_msg({m1, <<"d">>}),
899    {m1, <<"d">>=Bs} = M:decode_msg(Data, m1),
900    HasBinary = (catch binary:copy(<<1>>)) == <<1>>,
901    if HasBinary ->
902            ?assertEqual(byte_size(Bs), binary:referenced_byte_size(Bs));
903       true ->
904            ok %% cannot test more if we don't have the binary module
905    end,
906    unload_code(M).
907
908copy_bytes_fraction_test() ->
909    HasBinary = (catch binary:copy(<<1>>)) == <<1>>,
910    if HasBinary ->
911            Proto = ["message m1 {",
912                     "  required bytes f1 = 1;",
913                     "  required bytes f2 = 2;",
914                     "}"],
915            M1 = compile_iolist(Proto, [{copy_bytes, 2}]),   % fraction as int
916            M2 = compile_iolist(Proto, [{copy_bytes, 2.0}]), % fraction as float
917            D1 = <<"d">>, %% small
918            D2 = <<"dddddddddddddddddddddddddddd">>, %% large
919            Data = M1:encode_msg({m1, D1, D2}),
920            ?assert(byte_size(Data) > (2 * byte_size(D1))),
921            ?assert(byte_size(Data) < (2 * byte_size(D2))),
922            {m1, D1Bs, D2Bs} = M1:decode_msg(Data, m1),
923            ?assertEqual(D1, D1Bs),
924            ?assertEqual(D2, D2Bs),
925            %% The small data should have been copied, but not the larger
926            ?assertEqual(byte_size(D1Bs), binary:referenced_byte_size(D1Bs)),
927            ?assertEqual(byte_size(Data), binary:referenced_byte_size(D2Bs)),
928
929            {m1, D3Bs, D4Bs} = M2:decode_msg(Data, m1),
930            ?assertEqual(D1, D3Bs),
931            ?assertEqual(D2, D4Bs),
932            ?assertEqual(byte_size(D3Bs), binary:referenced_byte_size(D3Bs)),
933            ?assertEqual(byte_size(Data), binary:referenced_byte_size(D4Bs)),
934
935            unload_code(M1),
936            unload_code(M2);
937       true ->
938            ok
939    end.
940
941%% --- strings ----------
942
943strings_as_binaries_option_produces_bins_test() ->
944    M = compile_iolist(["message m1 {"
945                        "  required string f1 = 1;",
946                        "}"],
947                       [strings_as_binaries]),
948    Data = M:encode_msg({m1, "some string"}),
949    {m1, <<"some string">>} = M:decode_msg(Data, m1),
950    unload_code(M).
951
952strings_as_lists_is_the_default_test() ->
953    M = compile_iolist(["message m1 {"
954                        "  required string f1 = 1;",
955                        "}"],
956                       []),
957    Data = M:encode_msg({m1, "some string"}),
958    {m1, "some string"} = M:decode_msg(Data, m1),
959    unload_code(M).
960
961strings_as_binaries_opt_together_with_copy_bytes_opt_test() ->
962    M = compile_iolist(["message m1 {"
963                        "  required string f1 = 1;",
964                        "}"],
965                       [strings_as_binaries, {copy_bytes, auto}]),
966    Data = M:encode_msg({m1, "some string"}),
967    {m1, <<"some string">>=StrBin} = M:decode_msg(Data, m1),
968    HasBinary = (catch binary:copy(<<1>>)) == <<1>>, % binary exists since R14A
969    if HasBinary ->
970            ?assertEqual(byte_size(StrBin),
971                         binary:referenced_byte_size(StrBin));
972       true ->
973            ok
974    end,
975    unload_code(M).
976
977accepts_both_strings_and_binaries_as_input_test() ->
978    M = compile_iolist(["message m1 {"
979                        "  required string f1 = 1;",
980                        "  required string f2 = 2;",
981                        "}"]),
982    Data = M:encode_msg({m1, "some string", <<"some other string">>}),
983    {m1, "some string", "some other string"} = M:decode_msg(Data, m1),
984    unload_code(M).
985
986verifies_both_strings_and_binaries_as_input_test() ->
987    M = compile_iolist(["message m1 {"
988                        "  required string f1 = 1;",
989                        "  required string f2 = 2;",
990                        "}"],
991                        [strings_as_binaries]),
992    R = {m1, "some string", <<"some other string">>},
993    ok = M:verify_msg(R),
994    ?assertError(_, M:verify_msg({m1, "a", <<97,98,99,255,191>>})),
995    unload_code(M).
996
997utf8_bom_test() ->
998    Utf8ByteOrderMark = <<239,187,191>>, % EF BB BF
999    M = compile_iolist([Utf8ByteOrderMark,
1000                        "message m1 {"
1001                        "  required string f1 = 1;",
1002                        "}"]),
1003    Data = M:encode_msg({m1, "x"}),
1004    {m1, "x"} = M:decode_msg(Data, m1),
1005    unload_code(M).
1006
1007nonascii_default_values_for_strings_test() ->
1008    Utf8 = unicode:characters_to_binary([1000,2000,3000]),
1009    M = compile_iolist(["message m1 {"
1010                        "  required string f1 = 1 [default=\"",Utf8,"\"];",
1011                        "}"]),
1012    Data = M:encode_msg({m1, "x"}),
1013    {m1, "x"} = M:decode_msg(Data, m1),
1014    unload_code(M).
1015
1016reading_file_falls_back_to_latin1_test() ->
1017    Latin1 = [255,255,255], % Not decodable as utf8
1018    M = compile_iolist(["// "++Latin1++"\n",
1019                        "message m1 {"
1020                        "  required string f1 = 1;",
1021                        "}"]),
1022    Data = M:encode_msg({m1, "x"}),
1023    {m1, "x"} = M:decode_msg(Data, m1),
1024    unload_code(M).
1025
1026error_for_invalid_boms_test() ->
1027    [{_,{error,{utf8_decode_failed,{invalid_proto_byte_order_mark,_},_},[]}} =
1028         {Bom, compile_iolist_get_errors_or_warnings(
1029                 [Bom, "message m1 {"
1030                  "  required string f1 = 1;",
1031                  "}"])}
1032     || Bom <- [<<0,0,16#FE,16#FF>>, % utf32-big endian
1033                <<16#FF,16#FE,0,0>>, % utf32-little
1034                <<16#FE,16#FF>>,     % utf16-big
1035                <<16#FF,16#FE>>]].   % utf16-little
1036
1037
1038generates_escaped_utf8_for_old_erlang_versions_test() ->
1039    Unicode = [255],
1040    Utf8 = unicode:characters_to_binary(Unicode),
1041    Proto = ["message m1 {"
1042             "  required string f1 = 1 [default=\"",Unicode,"\"];",
1043             "}"],
1044    S1 = compile_to_string_get_hrl(Proto, [{target_erlang_version,15}]),
1045    true = gpb_lib:is_substr("x{ff}", S1), %% 255 = 16#ff
1046    S2 = compile_to_string_get_hrl(Proto, [{target_erlang_version,16}]),
1047    true = gpb_lib:is_substr(binary_to_list(Utf8), S2),
1048    [Line1 | _] = gpb_lib:string_lexemes(S2, "\n"),
1049    true = gpb_lib:is_substr("coding: ", Line1).
1050
1051%% -- translation of google.protobuf.Any ----------
1052
1053-define(x_com_atom_1(C), 10,10,"x.com/atom",18,1,C).
1054
1055'translation_of_google.protobuf.Any_test_'() ->
1056    {timeout,10,fun 'translation_of_google.protobuf.Any_aux'/0}.
1057
1058'translation_of_google.protobuf.Any_aux'() ->
1059    %% The any.proto contains:
1060    %%
1061    %%     syntax = "proto3";
1062    %%     ...
1063    %%     message Any {
1064    %%       string type_url = 1;
1065    %%       bytes value = 2;
1066    %%     }
1067    %%
1068    M = compile_iolist(
1069          ["syntax=\"proto3\";",
1070           "import \"google/protobuf/any.proto\";",
1071           "message m {",
1072           "  repeated google.protobuf.Any f1=1;",
1073           "  required google.protobuf.Any f2=3;",
1074           "  optional google.protobuf.Any f3=4;",
1075           "  oneof f4 {",
1076           "    google.protobuf.Any f5=6;",
1077           "  }",
1078           "}"],
1079          [use_packages,
1080           %% The translations assume value is an atom.
1081           {any_translate,[{encode,{?MODULE,any_e_atom,['$1']}},
1082                           {decode,{?MODULE,any_d_atom,['$1']}},
1083                           {merge,{?MODULE,any_m_atom,['$1','$2']}},
1084                           {verify,{?MODULE,any_v_atom,['$1','$errorf']}}]}]),
1085    R = {m, [a,b,c], d, e, {f5,f}},
1086    <<10,15,?x_com_atom_1("a"),
1087      10,15,?x_com_atom_1("b"),
1088      10,15,?x_com_atom_1("c"),
1089      26,15,?x_com_atom_1("d"),
1090      34,15,?x_com_atom_1("e"),
1091      50,15,?x_com_atom_1("f")>> = B = M:encode_msg(R),
1092    R = M:decode_msg(B, m),
1093
1094    ok = M:verify_msg(R),
1095    ?verify_gpb_err(M:verify_msg({m, ["a",b,c], d, e, {f5,f}})),
1096    ?verify_gpb_err(M:verify_msg({m, [a,b,c], "d", e, {f5,f}})),
1097    ?verify_gpb_err(M:verify_msg({m, [a,b,c], d, "e", {f5,f}})),
1098    ?verify_gpb_err(M:verify_msg({m, [a,b,c], d, e, {f5,"f"}})),
1099
1100    RR = {m, [a,b,c,a,b,c], dd, ee, {f5,ff}},
1101    RR = M:merge_msgs(R, R),
1102    RR = M:decode_msg(<<B/binary, B/binary>>, m),
1103    unload_code(M).
1104
1105translation_of_Any_as_a_map_value_test() ->
1106    M = compile_iolist(
1107          ["syntax=\"proto3\";",
1108           "import \"google/protobuf/any.proto\";",
1109           "message m {",
1110           "  map<string,google.protobuf.Any> f1=1;",
1111           "}"],
1112          [use_packages,
1113           {any_translate,[{encode,{?MODULE,any_e_atom,['$1']}},
1114                           {decode,{?MODULE,any_d_atom,['$1']}},
1115                           {merge,{?MODULE,any_m_atom,['$1','$2']}}, % unused
1116                           {verify,{?MODULE,any_v_atom,['$1','$errorf']}}]}]),
1117    R = {m, MapI=[{"x",a},{"y",b}]},
1118    <<10,20, % "pseudo" msg for map item
1119      10,1,"x", % key=x
1120      18,15,?x_com_atom_1("a"), % value=a
1121      10,20,
1122      10,1,"y",
1123      18,15,?x_com_atom_1("b")>> = B = M:encode_msg(R),
1124    {m,MapO} = M:decode_msg(B, m),
1125    true = lists:sort(MapI) == lists:sort(MapO),
1126
1127    ok = M:verify_msg(R),
1128    ?verify_gpb_err(M:verify_msg({m, [{"a","not an atom"}]})),
1129    unload_code(M).
1130
1131merge_callback_for_Any_is_optional_test() ->
1132    M = compile_iolist(
1133          ["syntax=\"proto3\";",
1134           "import \"google/protobuf/any.proto\";",
1135           "message m {",
1136           "  required google.protobuf.Any f1=1;",
1137           "}"],
1138          [use_packages,
1139           {any_translate,[{encode,{?MODULE,any_e_atom,['$1']}},
1140                           {decode,{?MODULE,any_d_atom,['$1']}},
1141                           {verify,{?MODULE,any_v_atom,['$1','$errorf']}}]}]),
1142    %% Expected behaviour in case of a "default" merge op is overwrite
1143    {m,a} = M:decode_msg(<<10,15,?x_com_atom_1("a")>>, m),
1144    {m,b} = M:decode_msg(<<10,15,?x_com_atom_1("a"),
1145                           10,15,?x_com_atom_1("b")>>, % overwrite
1146                         m),
1147    unload_code(M).
1148
1149-define(recv(Pattern),
1150        (fun() -> receive Pattern=__V -> __V
1151                  after 4000 ->
1152                          error({receive_timed_out,
1153                                 {pattern,??Pattern},
1154                                 {message_queue,
1155                                  element(2,process_info(self(),messages))}})
1156                  end
1157         end)()).
1158
1159userdata_to_Any_callback_test() ->
1160    M = compile_iolist(
1161          ["syntax=\"proto3\";",
1162           "import \"google/protobuf/any.proto\";",
1163           "message m {",
1164           "  required google.protobuf.Any f1=1;",
1165           "}"],
1166          [use_packages,
1167           {any_translate,[{encode,{?MODULE,any_e_atom,['$1','$user_data']}},
1168                           {decode,{?MODULE,any_d_atom,['$1','$user_data']}},
1169                           {merge,{?MODULE,any_m_atom,['$1','$2',
1170                                                       '$user_data']}},
1171                           {verify,{?MODULE,any_v_atom,['$1','$errorf',
1172                                                        '$user_data']}}]}]),
1173    R1 = {m,a},
1174    Self = self(),
1175    SendToSelf = fun(Result) -> Self ! {res,Result} end,
1176    B1 = M:encode_msg(R1,[{user_data,SendToSelf}]),
1177    ?recv({res,{'google.protobuf.Any',"x.com/atom",<<"a">>}}),
1178    R1 = M:decode_msg(B1, m, [{user_data,SendToSelf}]),
1179    ?recv({res,a}),
1180    {m,aa} = M:merge_msgs(R1, R1, [{user_data,SendToSelf}]),
1181    ?recv({res,aa}),
1182    ok = M:verify_msg(R1, [{user_data,SendToSelf}]),
1183    ?recv({res,ok}),
1184    unload_code(M).
1185
1186userdata_and_op_to_Any_callback_test() ->
1187    M = compile_iolist(
1188          ["syntax=\"proto3\";",
1189           "import \"google/protobuf/any.proto\";",
1190           "message m {",
1191           "  required google.protobuf.Any f1=1;",
1192           "}"],
1193          [use_packages,
1194           {any_translate,[{encode,{?MODULE,any_e_atom,['$1',
1195                                                        '$user_data','$op']}},
1196                           {decode,{?MODULE,any_d_atom,['$1',
1197                                                        '$user_data','$op']}},
1198                           {merge,{?MODULE,any_m_atom,['$1','$2',
1199                                                       '$user_data','$op']}},
1200                           {verify,{?MODULE,any_v_atom,['$1','$errorf',
1201                                                        '$user_data','$op']}}]}
1202          ]),
1203    R1 = {m,a},
1204    Self = self(),
1205    SendToSelf = fun(Result,Op) -> Self ! {{res,Result},{op,Op}} end,
1206    B1 = M:encode_msg(R1,[{user_data,SendToSelf}]),
1207    ?recv({{res,{'google.protobuf.Any',"x.com/atom",<<"a">>}},{op,encode}}),
1208    %% When encode is called with verify, the same option list and
1209    %% hence the same user data is sent to verify too, so for that
1210    %% case, expect two messages back.
1211    B1 = M:encode_msg(R1,[{user_data,SendToSelf},
1212                          {verify,true}]),
1213    ?recv({{res,{'google.protobuf.Any',"x.com/atom",<<"a">>}},{op,encode}}),
1214    ?recv({{res,ok},{op,verify}}),
1215    %% now for decode etc...
1216    R1 = M:decode_msg(B1, m, [{user_data,SendToSelf}]),
1217    ?recv({{res,a},{op,decode}}),
1218    {m,aa} = M:merge_msgs(R1, R1, [{user_data,SendToSelf}]),
1219    ?recv({{res,aa},{op,merge}}),
1220    ok = M:verify_msg(R1, [{user_data,SendToSelf}]),
1221    ?recv({{res,ok},{op,verify}}),
1222    unload_code(M).
1223
1224default_merge_callback_for_repeated_Any_test() ->
1225    %% A merge callback for a google.protobuf.Any that is repeated,
1226    %% is not needed
1227    M = compile_iolist(
1228          ["syntax=\"proto3\";",
1229           "import \"google/protobuf/any.proto\";",
1230           "message m {",
1231           "  repeated google.protobuf.Any f1=1;",
1232           "}"],
1233          [use_packages,
1234           {any_translate,[{encode,{?MODULE,any_e_atom,['$1']}},
1235                           {decode,{?MODULE,any_d_atom,['$1']}},
1236                           {verify,{?MODULE,any_v_atom,['$1','$errorf']}}]}]),
1237    {m,[a,b]} = M:decode_msg(<<10,15,?x_com_atom_1("a"),
1238                               10,15,?x_com_atom_1("b")>>,
1239                             m),
1240    {m,[a,b]} = M:merge_msgs({m,[a]}, {m,[b]}),
1241    unload_code(M).
1242
1243verify_callback_for_Any_is_optional_test() ->
1244    M = compile_iolist(
1245          ["syntax=\"proto3\";",
1246           "import \"google/protobuf/any.proto\";",
1247           "message m {",
1248           "  required google.protobuf.Any f1=1;",
1249           "}"],
1250          [use_packages,
1251           {any_translate,[{encode,{?MODULE,any_e_atom,['$1']}},
1252                           {decode,{?MODULE,any_d_atom,['$1']}},
1253                           {merge,{?MODULE,any_m_atom,['$1','$2']}}]}]),
1254    %% Expected behaviour in case of a "default" verify op to accept anything
1255    ok = M:verify_msg({m,a}),
1256    ok = M:verify_msg({m,"not an atom"}),
1257    unload_code(M).
1258
1259verify_callback_with_and_without_errorf_test() ->
1260    DefsM1 = ["syntax=\"proto3\";",
1261              "import \"google/protobuf/any.proto\";",
1262              "message m1 {",
1263              "  required google.protobuf.Any a=1;",
1264              "}"],
1265
1266    Mod1 = compile_iolist(
1267             DefsM1,
1268             [use_packages,
1269              {any_translate,
1270               [{encode,{?MODULE,any_e_atom,['$1']}},
1271                {decode,{?MODULE,any_d_atom,['$1']}},
1272                {verify,{?MODULE,any_v_atom,['$1','$errorf']}}]}]),
1273    ok = Mod1:verify_msg(#m1{a=abc}),
1274    ?assertError({gpb_type_error,{not_an_atom,[{value,123},{path,'m1.a'}]}},
1275                 Mod1:verify_msg(#m1{a=123})),
1276    unload_code(Mod1),
1277
1278    Mod2 = compile_iolist(
1279             DefsM1,
1280             [use_packages,
1281              {any_translate,
1282               [{encode,{?MODULE,any_e_atom,['$1']}},
1283                {decode,{?MODULE,any_d_atom,['$1']}},
1284                {verify,{?MODULE,any_v_atom,['$1']}}]}]), % no '$errorf'
1285    ok = Mod2:verify_msg(#m1{a=abc}),
1286    ?assertError({gpb_type_error,{oops_no_atom,[{value,123},{path,'m1.a'}]}},
1287                 Mod2:verify_msg(#m1{a=123})),
1288    unload_code(Mod2).
1289
1290%% Translators/callbacks:
1291any_e_atom(A) ->
1292    {'google.protobuf.Any', "x.com/atom", list_to_binary(atom_to_list(A))}.
1293
1294any_d_atom({'google.protobuf.Any', "x.com/atom", B}) ->
1295    list_to_atom(binary_to_list(B)).
1296
1297any_m_atom(A1, A2) ->
1298    list_to_atom(atom_to_list(A1) ++ atom_to_list(A2)).
1299
1300any_v_atom(A, ErrorF) ->
1301    if is_atom(A) -> ok;
1302       true -> ErrorF(not_an_atom)
1303    end.
1304
1305any_v_atom(A) when is_atom(A) -> ok;
1306any_v_atom(_) -> erlang:error(oops_no_atom).
1307
1308%% Translators/callbacks for user-data
1309any_e_atom(A, Fn) -> call_tr_userdata_fn(Fn, any_e_atom(A)).
1310any_d_atom(Any, Fn) -> call_tr_userdata_fn(Fn, any_d_atom(Any)).
1311any_m_atom(A1, A2, Fn) -> call_tr_userdata_fn(Fn, any_m_atom(A1, A2)).
1312any_v_atom(A, ErrorF, Fn) -> call_tr_userdata_fn(Fn, any_v_atom(A, ErrorF)).
1313
1314call_tr_userdata_fn(Fn, Result) ->
1315    Fn(Result),
1316    Result.
1317
1318%% Translators/callbacks for user-data and op
1319any_e_atom(A, Fn, Op) -> call_tr_userdata_fn(Fn, any_e_atom(A), Op).
1320any_d_atom(Any, Fn, Op) -> call_tr_userdata_fn(Fn, any_d_atom(Any), Op).
1321any_m_atom(A1, A2, Fn, Op) -> call_tr_userdata_fn(Fn, any_m_atom(A1, A2), Op).
1322any_v_atom(A, ErrorF, Fn, Op) -> call_tr_userdata_fn(Fn, any_v_atom(A, ErrorF),
1323                                                     Op).
1324call_tr_userdata_fn(Fn, Result, Op) ->
1325    Fn(Result, Op),
1326    Result.
1327
1328%% -- translation of other messages ----------
1329
1330translate_msg_type_test() ->
1331    %% in this test, the internal representation of the uuid message
1332    %% is an integer.
1333    M = compile_iolist(
1334          ["message m {",
1335           "  repeated uuid f1=1;",
1336           "  required uuid f2=2;",
1337           "  optional uuid f3=3;",
1338           "  oneof f4 { uuid f5=5; }",
1339           "}",
1340           "message uuid { required string id = 1; }",
1341           "",
1342           %% For comparison: similar message x, with similar sub message u2,
1343           %% which should encode to the same, so we can verify encoding.
1344           "message x {",
1345           "  repeated u f1=1;",
1346           "  required u f2=2;",
1347           "  optional u f3=3;",
1348           "  oneof f4 { u f5=5; }",
1349           "}",
1350           "message u { required string id = 1; }"],
1351          [%% The translation changes #uuid{id=string()} <-> integer()
1352           {translate_type,
1353            {{msg,uuid},
1354             [{encode, {?MODULE, uuid_e, ['$1']}},
1355              {decode, {?MODULE, uuid_d, ['$1']}},
1356              {merge,  {?MODULE, uuid_m, ['$1','$2']}},
1357              {verify, {?MODULE, uuid_v, ['$1']}}]}}]),
1358    M1 = {m, [11,12], 22, 33, {f5,55}},
1359    X1 = {x, [{u,"11"}, {u,"12"}], {u,"22"}, {u,"33"}, {f5,{u,"55"}}},
1360    ok = M:verify_msg(M1),
1361    B1 = M:encode_msg(M1),
1362    B1 = M:encode_msg(X1),
1363    M2 = {m, [13,14], 23, 34, {f5,56}},
1364    X2 = {x, [{u,"13"}, {u,"14"}], {u,"23"}, {u,"34"}, {f5,{u,"56"}}},
1365    B2 = M:encode_msg(M2),
1366    B2 = M:encode_msg(X2),
1367    Expected = {m,
1368                [11,12, 13,14],
1369                22 bxor 23, % the "odd" merge operation is bitwise xor
1370                33 bxor 34,
1371                {f5, 55 bxor 56}},
1372    Expected = M:decode_msg(<<B1/binary, B2/binary>>, m),
1373    Expected = M:merge_msgs(M1, M2),
1374    unload_code(M).
1375
1376uuid_e(Uuid) when is_integer(Uuid) ->
1377    {uuid, integer_to_list(Uuid)}.
1378
1379uuid_d({uuid,UuidStr}) when ?is_string(UuidStr) ->
1380    list_to_integer(UuidStr).
1381
1382uuid_v(Uuid) when is_integer(Uuid) -> ok;
1383uuid_v(X) -> error({non_int_uuid,X}).
1384
1385uuid_m(Uuid1, Uuid2) when is_integer(Uuid1), is_integer(Uuid2) ->
1386    Uuid1 bxor Uuid2.
1387
1388%% -- translation of other types ----------
1389
1390basic_translate_with_userdata_test() ->
1391    %% For this test, we'll pretend `bytes' values are ipv4 addresses
1392    %% and the userdata denotes a network (for instance: "192.168.0.0/16")
1393    M = compile_iolist(
1394          ["message m {",
1395           "  required bytes f = 1;",
1396           "}"],
1397          [{translate_type,
1398            {bytes, % no merge function since bytes is a scalar type
1399             [{encode, {?MODULE, e_ipv4_addr, ['$1', '$user_data']}},
1400              {decode, {?MODULE, d_ipv4_addr, ['$1', '$user_data']}},
1401              {verify, {?MODULE, v_ipv4_addr, ['$1', '$user_data']}}]}}]),
1402    Nw = fun(V) -> [{user_data, V}] end,
1403    <<10,4, 127,0,0,1>>   = M:encode_msg({m,{127,0,0,1}}, Nw("127.0.0.0/8")),
1404    <<10,4, 127,1,2,3>>   = M:encode_msg({m,{255,1,2,3}}, Nw("127.0.0.0/8")),
1405    <<10,4, 192,168,2,3>> = M:encode_msg({m,{127,1,2,3}}, Nw("192.168.0.0/16")),
1406    {m,{127,0,0,1}}  = M:decode_msg(<<10,4, 127,0,0,1>>,m,Nw("127.0.0.0/8")),
1407    {m,{127,1,2,3}}  = M:decode_msg(<<10,4, 255,1,2,3>>,m,Nw("127.0.0.0/8")),
1408    {m,{192,168,2,3}}= M:decode_msg(<<10,4, 127,1,2,3>>,m,Nw("192.168.0.0/16")),
1409    ok = M:verify_msg({m,{127,0,0,1}}, Nw("127.0.0.0/8")),
1410    ?assertError(_, M:verify_msg({m,{10,1,2,3}}, Nw("127.0.0.0/8"))),
1411    unload_code(M).
1412
1413e_ipv4_addr({A,B,C,D}, Net) ->
1414    list_to_binary(tuple_to_list(apply_ipv4_netmask({A,B,C,D}, Net))).
1415
1416d_ipv4_addr(<<A,B,C,D>>, Net) ->
1417    apply_ipv4_netmask({A,B,C,D}, Net).
1418
1419v_ipv4_addr({A,B,C,D}, Net) ->
1420    %% verify IP {A,B,C,D} is within Net (on format "10.0.0.0/8")
1421    {ok, [N1,N2,N3,N4, Netmask], []} = io_lib:fread("~d.~d.~d.~d/~d", Net),
1422    <<Ip:32>> = <<A,B,C,D>>,
1423    <<N:32>> = <<N1,N2,N3,N4>>,
1424    M = ((1 bsl Netmask) - 1) bsl (32 - Netmask),
1425    if ((Ip band M) bxor (N band M)) =:= 0 -> ok;
1426       true -> error({address_outside_of_network,{A,B,C,D},Net})
1427    end.
1428
1429apply_ipv4_netmask({A,B,C,D}, Net) ->
1430    %% set/change the network bits of ip {A,B,C,D}, to those in Net
1431    {ok, [N1,N2,N3,N4, Netmask], []} = io_lib:fread("~d.~d.~d.~d/~d", Net),
1432    <<Ip:32>> = <<A,B,C,D>>,
1433    <<N:32>> = <<N1,N2,N3,N4>>,
1434    Subnetmask = (1 bsl (32 - Netmask)) - 1,
1435    Mask = ((1 bsl Netmask) - 1) bsl (32 - Netmask),
1436    list_to_tuple(
1437      binary_to_list(<<((N band Mask) + (Ip band Subnetmask)):32>>)).
1438
1439translate_all_scalar_types_test() ->
1440    M = compile_iolist(
1441          ["message o_i32     { optional int32      f = 1; }",
1442           "message o_s32     { optional sint32     f = 1; }",
1443           "message o_uf32    { optional fixed32    f = 1; }",
1444           "message o_ee      { optional ee         f = 1; }",
1445           "message o_bool    { optional bool       f = 1; }",
1446           "message o_str     { optional string     f = 1; }",
1447           "message o_bytes   { optional bytes      f = 1; }",
1448           "message o_float   { optional float      f = 1; }",
1449           "message o_double  { optional double     f = 1; }",
1450           "",
1451           "message u_i32     { oneof u { int32      f = 1; } }",
1452           "message u_s32     { oneof u { sint32     f = 1; } }",
1453           "message u_uf32    { oneof u { fixed32    f = 1; } }",
1454           "message u_ee      { oneof u { ee         f = 1; } }",
1455           "message u_bool    { oneof u { bool       f = 1; } }",
1456           "message u_str     { oneof u { string     f = 1; } }",
1457           "message u_bytes   { oneof u { bytes      f = 1; } }",
1458           "message u_float   { oneof u { float      f = 1; } }",
1459           "message u_double  { oneof u { double     f = 1; } }",
1460           "",
1461           "message rq_i32     { required int32     f = 1; }",
1462           "message rq_s32     { required sint32    f = 1; }",
1463           "message rq_uf32    { required fixed32   f = 1; }",
1464           "message rq_ee      { required ee        f = 1; }",
1465           "message rq_bool    { required bool      f = 1; }",
1466           "message rq_str     { required string    f = 1; }",
1467           "message rq_bytes   { required bytes     f = 1; }",
1468           "message rq_float   { required float     f = 1; }",
1469           "message rq_double  { required double    f = 1; }",
1470           "",
1471           "message rp_i32     { repeated int32     f = 1; }",
1472           "message rp_s32     { repeated sint32    f = 1; }",
1473           "message rp_uf32    { repeated fixed32   f = 1; }",
1474           "message rp_ee      { repeated ee        f = 1; }",
1475           "message rp_bool    { repeated bool      f = 1; }",
1476           "message rp_str     { repeated string    f = 1; }",
1477           "message rp_bytes   { repeated bytes     f = 1; }",
1478           "message rp_float   { repeated float     f = 1; }",
1479           "message rp_double  { repeated double    f = 1; }",
1480           "",
1481           "message rpp_i32     { repeated int32    f = 1 [packed]; }",
1482           "message rpp_s32     { repeated sint32   f = 1 [packed]; }",
1483           "message rpp_uf32    { repeated fixed32  f = 1 [packed]; }",
1484           "message rpp_ee      { repeated ee       f = 1 [packed]; }",
1485           "message rpp_bool    { repeated bool     f = 1 [packed]; }",
1486           "message rpp_str     { repeated string   f = 1; } // unpackable;\n",
1487           "message rpp_bytes   { repeated bytes    f = 1; } // unpackable;\n",
1488           "message rpp_float   { repeated float    f = 1 [packed]; }",
1489           "message rpp_double  { repeated double   f = 1 [packed]; }",
1490           "",
1491           "enum ee { zero = 0; one = 1; }"
1492          ],
1493          [{translate_type,
1494            {Scalar,
1495             [{encode, {?MODULE, e_astt, ['$1']}},
1496              {decode, {?MODULE, d_astt, ['$1']}},
1497              {verify, {?MODULE, v_astt, ['$1']}}]}}
1498           || Scalar <- [int32, sint32, fixed32, {enum,ee}, bool,
1499                         string, bytes, float, double]]),
1500
1501    [ok = round_trip_translate_test(
1502            [{Prefix, i32,    "value:4711"},
1503             {Prefix, s32,    "value:4711"},
1504             {Prefix, s32,    "value:-4711"},
1505             {Prefix, uf32,   "value:4711"},
1506             {Prefix, ee,     "value:one"},
1507             {Prefix, bool,   "value:true"},
1508             {Prefix, str,    "value:\"some-string\""},
1509             {Prefix, bytes,  "value:<<13,14,215,216>>"},
1510             {Prefix, float,  "value:1.125"},
1511             {Prefix, double, "value:1.25"}],
1512            M)
1513     || Prefix <- [o, u, rq, rp, rpp]],
1514        unload_code(M).
1515
1516round_trip_translate_test([{Prefix, Suffix, IntValue0} | Rest], M) ->
1517    IntValues = case Prefix of
1518                   o   -> [IntValue0, undefined];
1519                   u   -> [{f,IntValue0}, undefined];
1520                   rq  -> [IntValue0];
1521                   rp  -> [[IntValue0]];
1522                   rpp -> [[IntValue0]]
1523                end,
1524    MsgName = list_to_atom(lists:concat([Prefix, "_", Suffix])),
1525    [begin
1526         ok = M:verify_msg({MsgName, IntValue}),
1527         ?assertError(_, M:verify_msg({MsgName, "bad"++IntValue})),
1528         Msg = {MsgName, IntValue},
1529         Encoded = M:encode_msg(Msg),
1530         Msg = M:decode_msg(Encoded, MsgName)
1531     end
1532     || IntValue <- IntValues],
1533    round_trip_translate_test(Rest, M);
1534round_trip_translate_test([], _M) ->
1535    ok.
1536
1537e_astt("value:"++Rest) -> string_to_value(Rest).
1538
1539d_astt(Value) -> "value:"++value_to_string(Value).
1540
1541v_astt("value:"++_Rest)   -> ok;
1542v_astt("badvalue:"++Rest) -> error({badvalue,Rest}).
1543
1544string_to_value(S) ->
1545    {ok,Tokens,_EndL} = erl_scan:string(S++"."),
1546    {ok,Term} = erl_parse:parse_term(Tokens),
1547    Term.
1548
1549value_to_string(V) ->
1550    lists:flatten(io_lib:format("~p", [V])).
1551
1552%%-
1553translate_maptype_test() ->
1554    %% For this tests, the internal format of the map<_,_> is a dict()
1555    M = compile_iolist(
1556          ["message m {",
1557           "  map<int32,string> m = 1;"
1558           "}"],
1559          [{translate_type,
1560            {{map,int32,string},
1561             [{encode,{dict,to_list, ['$1']}},
1562              {decode,{dict,from_list, ['$1']}},
1563              {verify,{?MODULE,is_dict, ['$1']}}]}}]),
1564    D0 = dict:from_list([{1,"one"},{2,"two"}]),
1565    M1 = {m,D0},
1566    ok = M:verify_msg(M1),
1567    B1 = M:encode_msg(M1),
1568    {m,D1} = M:decode_msg(B1, m),
1569    ?assertEqual(lists:sort(dict:to_list(D0)),
1570                 lists:sort(dict:to_list(D1))),
1571    ?assertError({gpb_type_error, _}, M:verify_msg({m, not_a_dict})),
1572    unload_code(M).
1573
1574is_dict(D) ->
1575    try dict:to_list(D), ok
1576    catch _:_ -> error({not_a_dict,D})
1577    end.
1578
1579%% -
1580translate_oneof_test() ->
1581    %% For this test, we'll have an oneof which is either an ipv4 or ipv6
1582    %% (with some non-obvious types, just to test different)
1583    %% and translations of the ip field itself (the oneo) is what we want
1584    %% to test.
1585    %% The internal format is either a 4-tuple or an 8-tuple.
1586    M = compile_iolist(
1587          ["message m {",
1588           "  oneof ip {",
1589           "    fixed32 ipv4 = 1;",
1590           "    bytes ipv6 = 2;",
1591           "  }",
1592           "}"],
1593          [{translate_field,
1594            {[m,ip], [{encode, {?MODULE, e_ipv4or6, ['$1']}},
1595                      {decode, {?MODULE, d_ipv4or6, ['$1']}},
1596                      {verify, {?MODULE, v_ipv4or6, ['$1']}}]}}]),
1597    M1 = {m, {127,0,0,1}},
1598    M2 = {m, {0,0,0,0, 0,0,0,1}},
1599    ok = M:verify_msg(M1),
1600    ok = M:verify_msg(M2),
1601    <<13, _/bits>>    = B1 = M:encode_msg(M1), % check field tag+wiretype
1602    <<18,16, _/bits>> = B2 = M:encode_msg(M2), % check field tag+wiretype, len
1603    M1 = M:decode_msg(B1, m),
1604    M2 = M:decode_msg(B2, m),
1605    ?assertError({gpb_type_error, _},
1606                 M:verify_msg({m,{1,2,3,4,5,6}})), % wrong tuple size
1607    unload_code(M).
1608
1609e_ipv4or6({A,B,C,D}) ->
1610    <<Ipv4AsInt:32>> = <<A,B,C,D>>,
1611    {ipv4, Ipv4AsInt};
1612e_ipv4or6({A,B,C,D, E,F,G,H}) ->
1613    Bytes = << <<N:16>> || N <- [A,B,C,D, E,F,G,H] >>,
1614    {ipv6, Bytes}.
1615
1616d_ipv4or6({ipv4, Ipv4AsInt}) when is_integer(Ipv4AsInt) ->
1617    <<A,B,C,D>> = <<Ipv4AsInt:32>>,
1618    {A,B,C,D};
1619d_ipv4or6({ipv6, Bytes}) when bit_size(Bytes) =:= 128 ->
1620    [A,B,C,D, E,F,G,H] = [N || <<N:16>> <= Bytes],
1621    {A,B,C,D, E,F,G,H}.
1622
1623v_ipv4or6({_,_,_,_}) -> ok;
1624v_ipv4or6({_,_,_,_, _,_,_,_}) -> ok;
1625v_ipv4or6(X) -> error({invalid_ipv4_or_ipv6, X}).
1626
1627%%-
1628translate_repeated_test() ->
1629    %% For this test, the internal format of a repeated field is a set
1630    M = compile_iolist(
1631          ["message m {",
1632           "  repeated uint32 f = 1;",
1633           "}"],
1634          [{translate_field,
1635            {[m,f], [{encode, {sets,to_list, ['$1']}},
1636                     {decode_init_default, {sets, new, []}},
1637                     {decode_repeated_add_elem, {sets, add_element,
1638                                                 ['$1', '$2']}},
1639                     {decode_repeated_finalize, {?MODULE, id, ['$1']}},
1640                     {merge, {sets, union, ['$1', '$2']}},
1641                     {verify, {?MODULE, v_is_set, ['$1']}}]}}]),
1642    S0 = sets:from_list([1,2,3,4,5]),
1643    S2 = sets:from_list([4,5,6,7,8]),
1644    M1 = {m,S0},
1645    ok = M:verify_msg(M1),
1646    B1 = M:encode_msg(M1),
1647    {m,S1} = M:decode_msg(B1, m),
1648    ?assertEqual(lists:sort(sets:to_list(S0)),
1649                 lists:sort(sets:to_list(S1))),
1650    ?assertError({gpb_type_error, _}, M:verify_msg({m, not_a_set})),
1651    M2 = {m,S2},
1652    B2 = M:encode_msg(M2),
1653    {m,S22a} = M:decode_msg(<<B1/binary, B2/binary>>, m),
1654    ?assertEqual(lists:sort(sets:to_list(sets:union(S0,S2))),
1655                 lists:sort(sets:to_list(S22a))),
1656    {m,S22b} = M:merge_msgs(M1, M2),
1657    ?assertEqual(lists:sort(sets:to_list(sets:union(S0,S2))),
1658                 lists:sort(sets:to_list(S22b))),
1659    unload_code(M).
1660
1661v_is_set(X) ->
1662    case sets:is_set(X) of
1663        true  -> ok;
1664        false -> error({not_a_set, X})
1665    end.
1666
1667%%-
1668translate_messages_on_toplevel_test() ->
1669    %% For this test, the internal format of a message, m1, is an integer.
1670    %% and a string for f2.
1671    M = compile_iolist(
1672          ["message m1 {",
1673           "  required uint32 f = 1;",
1674           "}",
1675           "message m2 {",
1676           "  required string f = 1;",
1677           "}"],
1678          [{translate_type,
1679            {{msg,m1}, [{encode, {?MODULE, e_value_to_msg, ['$1', m1]}},
1680                        {decode, {?MODULE, d_msg_to_value, ['$1', m1]}},
1681                        {verify, {?MODULE, v_value, ['$1', integer]}},
1682                        {merge,  {erlang, '+', ['$1', '$2']}}]}},
1683           {translate_field,
1684            {[m2], [{encode, {?MODULE, e_value_to_msg, ['$1', m2]}},
1685                    {decode, {?MODULE, d_msg_to_value, ['$1', m2]}},
1686                    {verify, {?MODULE, v_value, ['$1', string]}},
1687                    {merge,  {erlang, '++', ['$1', '$2']}}]}}]),
1688    I1 = 28746,
1689    ok = M:verify_msg(I1, m1),
1690    B1 = M:encode_msg(I1, m1),
1691    I1 = M:decode_msg(B1, m1),
1692    ?assertEqual(I1 * 2, M:merge_msgs(I1, I1, m1)),
1693    ?assertError({gpb_type_error, _}, M:verify_msg(xyz, m1)),
1694    S2 = "abc",
1695    B2 = M:encode_msg(S2, m2),
1696    S2 = M:decode_msg(B2, m2),
1697    ?assertEqual(S2 ++ "def", M:merge_msgs(S2, "def", m2)),
1698    ?assertError({gpb_type_error, _}, M:verify_msg(xyzw, m2)),
1699    unload_code(M).
1700
1701e_value_to_msg(Value, MsgName) -> {MsgName, Value}.
1702
1703d_msg_to_value({MsgName, Value}, MsgName) -> Value.
1704
1705v_value(Value, integer) when is_integer(Value) -> ok;
1706v_value(Value, string) when is_list(Value) -> ok;
1707v_value(X, Expected) -> error({bad_value, Expected, X}).
1708
1709verify_is_optional_for_translate_toplevel_messages_test() ->
1710    M = compile_iolist(
1711          ["message m1 {",
1712           "  required uint32 f = 1;",
1713           "}"],
1714          [{translate_field,
1715            {[m1], [{encode, {?MODULE, e_value_to_msg, ['$1', m2]}},
1716                    {decode, {?MODULE, d_msg_to_value, ['$1', m2]}},
1717                    {merge,  {erlang, '++', ['$1', '$2']}}]}}]),
1718    ok = M:verify_msg(9348, m1),
1719    ok = M:verify_msg(bad_int_ok_since_no_verify_specified, m1),
1720    unload_code(M).
1721
1722%% --- misc ----------
1723
1724typespecs_and_uppercase_oneof_fields_test() ->
1725    M = compile_iolist(["message M {",
1726                        "  oneof x {",
1727                        "    uint32 Abc = 1;",
1728                        "  }",
1729                        "}"],
1730                       [type_specs]),
1731    E = M:encode_msg({'M', {'Abc', 17}}),
1732    ?assert(is_binary(E)),
1733    unload_code(M).
1734
1735only_enums_no_msgs_test() ->
1736    M = compile_iolist(["enum e {"
1737                        "  a = 1;",
1738                        "}"]),
1739    ?assertError({gpb_error, no_messages}, M:encode_msg({x})),
1740    ?assertError({gpb_error, no_messages}, M:encode_msg({x}, [])),
1741    ?assertError({gpb_error, no_messages}, M:decode_msg(<<>>, x)),
1742    ?assertError({gpb_error, no_messages}, M:merge_msgs({x}, {x})),
1743    ?assertError({gpb_type_error, {not_a_known_message, _}}, M:verify_msg({x})),
1744    [] = M:get_msg_names(),
1745    [e] = M:get_enum_names(),
1746    unload_code(M).
1747
1748ignores_packed_for_nonpackable_repeated_on_encoding_test() ->
1749    {ok, M, [_WarningAboutIgnoredPackedOption]} =
1750        compile_iolist_get_errors_or_warnings(
1751          ["message m1 { repeated string s1 = 1 [packed]; }"]),
1752    %% expect no length-delimited wrapping around the field
1753    %% just the elements one after the other.
1754    <<10,3,"abc",10,3,"def">> = M:encode_msg({m1, ["abc", "def"]}).
1755
1756%% --- Returning/reporting warnings/errors (and warnings_as_errors) tests -----
1757%% ... when compiling to file/binary/defs
1758%% ... when compiling from file/defs
1759%% ... when there are/aren't warnings/errors
1760
1761report_or_return_warnings_or_errors_test_() ->
1762    %% On my slow machine (1.6 GHz Atom N270), it currently takes ~61 seconds
1763    {timeout,120,fun report_or_return_warnings_or_errors_test_aux/0}.
1764
1765report_or_return_warnings_or_errors_test_aux() ->
1766    [begin
1767         Options = WarningOptions ++ ErrorOptions ++ WarnsAsErrsOpts,
1768         try
1769             rwre_go(Options, CompileTo, SrcType, SrcQuality)
1770         catch Class:Reason ->
1771                 Stack = erlang:get_stacktrace(),
1772                 %% Need some trouble shooting info for the failing combination
1773                 %% This could have been made into a test generator,
1774                 %% with each combination its won test,
1775                 %% but in total 544 tests are executed, and if running
1776                 %% with verbose mode, it'll always be half a thousand lines
1777                 %% of (almost) non-interesting info.
1778                 ?debugFmt("~nFailed for~n"
1779                           "   Options=~p~n"
1780                           "   CompileTo=~p~n"
1781                           "   SrcType=~p~n"
1782                           "   SrcQuality=~p~n",
1783                           [Options, CompileTo, SrcType, SrcQuality]),
1784                 erlang:raise(Class, Reason, Stack)
1785         end
1786     end
1787     || WarningOptions     <- [[], [report_warnings], [return_warnings],
1788                               [report_warnings, return_warnings]],
1789        ErrorOptions       <- [[], [report_errors], [return_errors],
1790                               [report_errors, return_errors]],
1791        WarnsAsErrsOpts    <- [[], [warnings_as_errors]],
1792        CompileTo          <- [to_binary, to_file, to_proto_defs],
1793        SrcType            <- [from_file, from_defs, from_string],
1794        SrcQuality         <- [clean_code, warningful_code, erroneous_code,
1795                               write_fails],
1796        %% Exclude a few combos
1797        not (SrcQuality == erroneous_code andalso SrcType == from_defs),
1798        not (SrcQuality == write_fails andalso CompileTo == to_binary),
1799        not (SrcQuality == write_fails andalso CompileTo == to_proto_defs)].
1800
1801rwre_go(Options, CompileTo, SrcType, SrcQuality) ->
1802    ExpectedReturn = compute_expected_return(Options, CompileTo, SrcQuality),
1803    ExpectedOutput = compute_expected_output(Options, SrcQuality),
1804    {{return,Returned},
1805     {output,Output}} = compile_the_code(Options, CompileTo,
1806                                         SrcType, SrcQuality),
1807    eval_return(ExpectedReturn, Returned, Output,
1808                Options, CompileTo, SrcType, SrcQuality),
1809    eval_output(ExpectedOutput, Output, Returned,
1810                Options, CompileTo, SrcType, SrcQuality),
1811    ok.
1812
1813
1814compute_expected_return(Options, CompileTo, SrcQuality) ->
1815    WarnsAsErrs = proplists:get_bool(warnings_as_errors, Options),
1816    WarnOpt = get_warning_opt_from_perspective_of_return(Options),
1817    case {WarnsAsErrs, SrcQuality, WarnOpt} of
1818        {true, warningful_code, return} -> {error, '_', non_empty_list};
1819        {true, warningful_code, report} -> error;
1820        _ -> compute_expected_return_normal_warns(Options, CompileTo, SrcQuality)
1821    end.
1822
1823compute_expected_return_normal_warns(Options, CompileTo, write_fails) ->
1824    compute_expected_return_normal_warns(Options, CompileTo, erroneous_code);
1825compute_expected_return_normal_warns(Options, to_file, SrcQuality) ->
1826    WarnOpt = get_warning_opt_from_perspective_of_return(Options),
1827    ErrOpt = get_error_opt_from_perspective_of_return(Options),
1828    case {WarnOpt, ErrOpt, SrcQuality} of
1829        {report, report, clean_code}      -> ok;
1830        {report, report, warningful_code} -> ok;
1831        {report, report, erroneous_code}  -> {error, '_'};
1832        {return, return, clean_code}      -> {ok, []};
1833        {return, return, warningful_code} -> {ok, non_empty_list};
1834        {return, return, erroneous_code}  -> {error, '_', []};
1835        {report, return, clean_code}      -> ok;
1836        {report, return, warningful_code} -> ok;
1837        {report, return, erroneous_code}  -> {error, '_'};
1838        {return, report, clean_code}      -> {ok, []};
1839        {return, report, warningful_code} -> {ok, non_empty_list};
1840        {return, report, erroneous_code}  -> {error, '_', []}
1841    end;
1842compute_expected_return_normal_warns(Options, to_binary, SrcQuality) ->
1843    WarnOpt = get_warning_opt_from_perspective_of_return(Options),
1844    ErrOpt = get_error_opt_from_perspective_of_return(Options),
1845    case {WarnOpt, ErrOpt, SrcQuality} of
1846        {report, report, clean_code}      -> {ok, mod, binary};
1847        {report, report, warningful_code} -> {ok, mod, binary};
1848        {report, report, erroneous_code}  -> {error, '_'};
1849        {return, return, clean_code}      -> {ok, mod, binary, []};
1850        {return, return, warningful_code} -> {ok, mod, binary, non_empty_list};
1851        {return, return, erroneous_code}  -> {error, '_', []};
1852        {report, return, clean_code}      -> {ok, mod, binary};
1853        {report, return, warningful_code} -> {ok, mod, binary};
1854        {report, return, erroneous_code}  -> {error, '_'};
1855        {return, report, clean_code}      -> {ok, mod, binary, []};
1856        {return, report, warningful_code} -> {ok, mod, binary, non_empty_list};
1857        {return, report, erroneous_code}  -> {error, '_', []}
1858    end;
1859compute_expected_return_normal_warns(Options, to_proto_defs, SrcQuality) ->
1860    WarnOpt = get_warning_opt_from_perspective_of_return(Options),
1861    ErrOpt = get_error_opt_from_perspective_of_return(Options),
1862    case {WarnOpt, ErrOpt, SrcQuality} of
1863        {report, report, clean_code}      -> {ok, non_empty_list};
1864        {report, report, warningful_code} -> {ok, non_empty_list};
1865        {report, report, erroneous_code}  -> {error, '_'};
1866        {return, return, clean_code}      -> {ok, non_empty_list, []};
1867        {return, return, warningful_code} -> {ok, non_empty_list,non_empty_list};
1868        {return, return, erroneous_code}  -> {error, '_', []};
1869        {report, return, clean_code}      -> {ok, non_empty_list};
1870        {report, return, warningful_code} -> {ok, non_empty_list};
1871        {report, return, erroneous_code}  -> {error, '_'};
1872        {return, report, clean_code}      -> {ok, non_empty_list, []};
1873        {return, report, warningful_code} -> {ok, non_empty_list,non_empty_list};
1874        {return, report, erroneous_code}  -> {error, '_', []}
1875    end.
1876
1877
1878compute_expected_output(_Options, clean_code) ->
1879    "";
1880compute_expected_output(Options, warningful_code) ->
1881    WarnOpt = get_warning_opt_from_perspective_of_output(Options),
1882    ErrOpt = get_error_opt_from_perspective_of_output(Options),
1883    case {WarnOpt, ErrOpt} of
1884        {report, report} -> non_empty_list;
1885        {report, return} -> non_empty_list;
1886        {return, report} -> "";
1887        {return, return} -> ""
1888    end;
1889compute_expected_output(Options, write_fails) ->
1890    compute_expected_output(Options, erroneous_code);
1891compute_expected_output(Options, erroneous_code) ->
1892    WarnOpt = get_warning_opt_from_perspective_of_output(Options),
1893    ErrOpt = get_error_opt_from_perspective_of_output(Options),
1894    case {WarnOpt, ErrOpt} of
1895        {report, report} -> non_empty_list;
1896        {report, return} -> "";
1897        {return, report} -> non_empty_list;
1898        {return, return} -> ""
1899    end.
1900
1901get_warning_opt_from_perspective_of_return(Opts) -> get_warn_opt(Opts, return).
1902get_warning_opt_from_perspective_of_output(Opts) -> get_warn_opt(Opts, report).
1903
1904get_error_opt_from_perspective_of_return(Opts) -> get_err_opt(Opts, return).
1905get_error_opt_from_perspective_of_output(Opts) -> get_err_opt(Opts, report).
1906
1907get_warn_opt(Opts, WhatToReturnIfBothAreSet) ->
1908    case {member(return_warnings, Opts), member(report_warnings, Opts)} of
1909        {false, false} -> report; %% default
1910        {true,  false} -> return;
1911        {false,  true} -> report;
1912        {true,   true} -> WhatToReturnIfBothAreSet
1913    end.
1914
1915get_err_opt(Opts, WhatToReturnIfBothAreSet) ->
1916    case {member(return_errors, Opts), member(report_errors, Opts)} of
1917        {false, false} -> report; %% default
1918        {true,  false} -> return;
1919        {false,  true} -> report;
1920        {true,   true} -> WhatToReturnIfBothAreSet
1921    end.
1922
1923member(Elem, List) ->
1924    lists:member(Elem, List).
1925
1926compile_the_code(Options, CompileTo, from_defs, SrcQuality) ->
1927    compile_msg_defs_get_output(get_proto_defs(SrcQuality),
1928                                compute_compile_opts(Options, CompileTo,
1929                                                     SrcQuality));
1930compile_the_code(Options, CompileTo, from_file, SrcQuality) ->
1931    compile_file_get_output(get_proto_file(SrcQuality),
1932                            compute_compile_opts(Options, CompileTo,
1933                                                 SrcQuality));
1934compile_the_code(Options, CompileTo, from_string, SrcQuality) ->
1935    compile_string_get_output(get_proto_file(SrcQuality),
1936                              compute_compile_opts(Options, CompileTo,
1937                                                   SrcQuality)).
1938
1939get_proto_defs(clean_code) ->
1940    [{{msg,m1}, [#?gpb_field{name=field11, type=uint32, occurrence=optional,
1941                             fnum=1, rnum=2, opts=[]}]}];
1942get_proto_defs(warningful_code) ->
1943    %% warning: packed field of type bytes
1944    [{{msg,m1}, [#?gpb_field{name=field11, type=bytes, occurrence=optional,
1945                             fnum=1, rnum=2, opts=[packed]}]}];
1946get_proto_defs(write_fails) ->
1947    get_proto_defs(clean_code).
1948
1949get_proto_file(clean_code) ->
1950    "message m1 { optional uint32 field11 = 1; }\n" ++
1951    "message MessageInfo1 { optional uint32 field11 = 1; }\n";
1952get_proto_file(warningful_code) ->
1953    %% warning: packed field of type bytes
1954    ["message m1 { optional bytes field11 = 1 [packed]; }\n"];
1955get_proto_file(erroneous_code) ->
1956    "g&~#";
1957get_proto_file(write_fails) ->
1958    get_proto_file(clean_code).
1959
1960compute_compile_opts(Options, CompileTo, write_fails) ->
1961    compute_compile_opts_2(Options, CompileTo) ++ mk_failing_write_option();
1962compute_compile_opts(Options, CompileTo, _SrcQuality) ->
1963    compute_compile_opts_2(Options, CompileTo).
1964
1965compute_compile_opts_2(Opts, to_binary)   -> [binary, type_specs | Opts];
1966compute_compile_opts_2(Opts, to_proto_defs) -> [to_proto_defs, type_specs | Opts];
1967compute_compile_opts_2(Opts, to_file)     -> [type_specs | Opts].
1968
1969mk_failing_write_option() ->
1970    [fail_write].
1971
1972compile_msg_defs_get_output(MsgDefs, Opts) ->
1973    Opts2 = case lists:member(fail_write, Opts) of
1974                false ->
1975                    Opts;
1976                true ->
1977                    RestOpts = Opts -- [fail_write],
1978                    FOpt = mk_fileop_opt([{write_file,fun(_,_) -> {error,eacces}
1979                                                      end}]),
1980                    [FOpt | RestOpts]
1981            end,
1982    Opts3 = ensure_file_writing_stubbed_opt(Opts2),
1983    capture_stdout(fun() -> gpb_compile:proto_defs('x', MsgDefs, Opts3) end).
1984
1985compile_file_get_output(Txt, Opts) ->
1986    Contents = iolist_to_binary(Txt),
1987    FailWrite = lists:member(fail_write, Opts),
1988    RestOpts = Opts -- [fail_write],
1989    FileOpOpts = if FailWrite -> mk_fileop_opt(
1990                                   [{read_file, fun(_) -> {ok, Contents} end},
1991                                    {write_file,fun(_, _) -> {error,eacces} end}
1992                                   ]);
1993                    true -> mk_fileop_opt(
1994                              [{read_file, fun(_) -> {ok, Contents} end}])
1995                 end,
1996    Opts2 = [FileOpOpts, {i,"."} | RestOpts],
1997    Opts3 = ensure_file_writing_stubbed_opt(Opts2),
1998    capture_stdout(fun() -> gpb_compile:file("X.proto", Opts3) end).
1999
2000compile_string_get_output(Txt, Opts) ->
2001    Opts2 = case lists:member(fail_write, Opts) of
2002                false ->
2003                    Opts;
2004                true ->
2005                    RestOpts = Opts -- [fail_write],
2006                    FOpt = mk_fileop_opt([{write_file,fun(_,_) -> {error,eacces}
2007                                                      end}]),
2008                    [FOpt | RestOpts]
2009            end,
2010    Opts3 = ensure_file_writing_stubbed_opt(Opts2),
2011    Txt2 = binary_to_list(iolist_to_binary(Txt)),
2012    capture_stdout(fun() -> gpb_compile:string('x', Txt2, Opts3) end).
2013
2014ensure_file_writing_stubbed_opt(Opts) ->
2015    case proplists:get_value(file_op, Opts) of
2016        undefined ->
2017            [mk_fileop_opt([]) | Opts]; % the default will stub writing
2018        _ ->
2019            Opts % already stubbed or changed
2020    end.
2021
2022eval_return(Expected, Actual, Output,
2023            Options, CompileTo, SrcType, SrcQuality) ->
2024    case match_values(Expected, Actual) of
2025        true ->
2026            ok;
2027        false ->
2028            erlang:error({bad_return,Expected,Actual,
2029                          [{output,Output},
2030                           {setup,{Options, CompileTo,
2031                                   SrcType, SrcQuality}}]})
2032    end.
2033
2034eval_output(Expected, Actual, Returned,
2035            Options, CompileTo, SrcType, SrcQuality) ->
2036    case match_value(Expected, Actual) of
2037        true ->
2038            ok;
2039        false ->
2040            erlang:error({bad_output,Expected,Actual,
2041                          [{returned,Returned},
2042                           {setup,{Options, CompileTo,
2043                                   SrcType, SrcQuality}}]})
2044    end.
2045
2046
2047match_values(X, X) ->
2048    true;
2049match_values([E | ERest], [A | ARest]) ->
2050    case match_value(E, A) of
2051        true  -> match_values(ERest, ARest);
2052        false -> false
2053    end;
2054match_values(ET, AT) when is_tuple(ET), is_tuple(AT),
2055                          tuple_size(ET) == tuple_size(AT) ->
2056    match_values(tuple_to_list(ET), tuple_to_list(AT));
2057match_values(_, _) ->
2058    false.
2059
2060match_value('_', _) ->
2061    true;
2062match_value(non_empty_list, X) when is_list(X), X /= [] ->
2063    true;
2064match_value(binary, X) when is_binary(X) ->
2065    true;
2066match_value(mod, X) when is_atom(X) ->
2067    true;
2068match_value(atom, X) when is_atom(X) ->
2069    true;
2070match_value(X, X)  ->
2071    true;
2072match_value(ET, AT) when is_tuple(ET), is_tuple(AT),
2073                          tuple_size(ET)==tuple_size(AT) ->
2074    match_values(ET, AT);
2075match_value(_, _) ->
2076    false.
2077
2078capture_stdout_actually_works_test() ->
2079    Ret = x,
2080    {{return, Ret},
2081     {output, "z"}} = capture_stdout(fun() -> io:format("~s", [z]), Ret end).
2082
2083capture_stdout(Fun) ->
2084    {_Pid,MRef} = spawn_monitor(
2085                   fun() ->
2086                           EvalExitWithResult = fun() -> exit(Fun()) end,
2087                           group_leader(self(), self()),
2088                           {_Pid, MRef} = spawn_monitor(EvalExitWithResult),
2089                           handle_io_requests(MRef, [])
2090                   end),
2091    receive
2092        {'DOWN', MRef, _, _, {{return, _Ret}, {output, _Output}}=Res} ->
2093            Res
2094    end.
2095
2096handle_io_requests(MRef, Acc) ->
2097    receive
2098        {'DOWN', MRef, _, _, FunRes} ->
2099            exit({{return, FunRes},
2100                  {output, lists:flatten(lists:reverse(Acc))}});
2101        {io_request, From, ReplyAs, Req} ->
2102            {IoRes, Output} = handle_io_req(Req),
2103            From ! {io_reply, ReplyAs, IoRes},
2104            handle_io_requests(MRef, [Output | Acc])
2105    end.
2106
2107handle_io_req({put_chars, Mod, Fun, Args}) ->
2108    {ok, apply(Mod, Fun, Args)};
2109handle_io_req({put_chars, _Enc, Mod, Fun, Args}) ->
2110    {ok, apply(Mod, Fun, Args)};
2111handle_io_req({put_chars, Txt}) ->
2112    {ok, Txt};
2113handle_io_req({put_chars, _Enc, Txt}) ->
2114    {ok, Txt};
2115handle_io_req({setopts, _}) ->
2116    {ok, ""};
2117handle_io_req({requests, IoRequests}) ->
2118    handle_io_reqs(IoRequests, []);
2119handle_io_req(_) ->
2120    %% {get_geometry, _??}
2121    %% {get_password, Prompt}
2122    %% {get_password, Enc, Prompt}
2123    %% {get_until, Prompt, Mod, Fun, Args}
2124    %% {get_until, Prompt, Enc, Mod, Fun, Args}
2125    %% {get_line, Prompt}
2126    %% {get_line, Enc, Prompt}
2127    %% {get_chars, Prompt, N}
2128    %% {get_chars, Enc, Prompt, N}
2129    {{error, enotsup}, ""}.
2130
2131handle_io_reqs([Req | Rest], Acc) ->
2132    {_Res, Output} = handle_io_req(Req),
2133    handle_io_reqs(Rest, [Output | Acc]);
2134handle_io_reqs([], Acc) ->
2135    {ok, lists:flatten(lists:reverse(Acc))}.
2136
2137failure_to_write_output_files_not_ignored_test() ->
2138    Contents = <<"message m1 { optional uint32 field11 = 1; }\n">>,
2139    CommonFileOpOpts = [{read_file, fun(_) -> {ok, Contents} end}],
2140    CommonOpts = [{i,"."}, return],
2141    WriteErlFailsOpts =
2142        [mk_fileop_opt([{write_file, fun("X.erl", _) -> ok;
2143                                        ("X.hrl", _) -> {error, eacces}
2144                                     end} | CommonFileOpOpts]) | CommonOpts],
2145    WriteHrlFailsOpts =
2146        [mk_fileop_opt([{write_file, fun("X.erl", _) -> ok;
2147                                        ("X.hrl", _) -> {error, eacces}
2148                                     end} | CommonFileOpOpts]) | CommonOpts],
2149    {error, _Reason, []}=Err1 = gpb_compile:file("X.proto", WriteErlFailsOpts),
2150    {error, _Reason, []}=Err2 = gpb_compile:file("X.proto", WriteHrlFailsOpts),
2151    gpb_compile:format_error(Err1),
2152    gpb_compile:format_error(Err2).
2153
2154%% --- format_error and format_warning tests ----------
2155
2156format_error_works_for_scan_errors_test() ->
2157    compile_and_assert_that_format_error_produces_iolist(
2158      ["message Msg ~~ required uint32 field1 = & }\n"],
2159      [".proto:1: "]).
2160
2161format_error_works_for_parse_errors_test() ->
2162    compile_and_assert_that_format_error_produces_iolist(
2163      ["message Msg { required uint32 field1 = }\n"],
2164      [".proto:1: ", "syntax error"]).
2165
2166format_error_works_when_failed_to_read_import_file_test() ->
2167    compile_and_assert_that_format_error_produces_iolist(
2168      ["import \"ZZ.proto\";\n",
2169       "message Msg { required uint32 field1 = 2;}\n"],
2170      [{read_file, [{"ZZ.proto", {error, eacces}}]}],
2171      ["read", "permission denied"]).
2172
2173format_error_works_when_import_file_not_found_test() ->
2174    compile_and_assert_that_format_error_produces_iolist(
2175      ["import \"ZZ.proto\";\n",
2176       "message Msg { required uint32 field1 = 2;}\n"],
2177      [{read_file_info, [{"ZZ.proto", {error, enoent}}]}],
2178      ["import", "not"]).
2179
2180format_error_works_for_verification_errors_test() ->
2181    compile_and_assert_that_format_error_produces_iolist(
2182      ["message Msg1 { required Msg2 field1 = 2;}\n"],
2183      ["Msg2", "Msg1", "field1"]).
2184
2185format_warning_works_with_packed_for_unpackable_test() ->
2186    compile_and_assert_that_format_warning_produces_iolist(
2187      ["message Msg1 { repeated string field1 = 2 [packed]; }\n"],
2188      ["Msg1", "field1", "ignor", "packed"]).
2189
2190compile_and_assert_that_format_error_produces_iolist(Contents, ExpectedWords) ->
2191    compile_and_assert_that_format_error_produces_iolist(
2192      Contents, [], ExpectedWords).
2193
2194compile_and_assert_that_format_error_produces_iolist(Contents,
2195                                                     ExtraFileOpReturnValues,
2196                                                     ExpectedWords) ->
2197    compile_and_assert_that_format_x_produces_iolist(
2198      Contents, ExtraFileOpReturnValues, ExpectedWords, format_error).
2199
2200compile_and_assert_that_format_warning_produces_iolist(Contents,
2201                                                       ExpectedWords) ->
2202    compile_and_assert_that_format_x_produces_iolist(
2203      Contents, [], ExpectedWords, format_warning).
2204
2205
2206compile_and_assert_that_format_x_produces_iolist(Contents,
2207                                                 ExtraFileOpReturnValues,
2208                                                 ExpectedPhrases,
2209                                                 FormatWhat) ->
2210    FileContents = iolist_to_binary(Contents),
2211    FileRetriever = mk_file_retriever(FileContents, ExtraFileOpReturnValues),
2212    FileInfoReader = mk_read_file_info("X.proto", ExtraFileOpReturnValues),
2213    Opts = [mk_fileop_opt([{read_file, FileRetriever},
2214                           {read_file_info, FileInfoReader}]),
2215            mk_defs_probe_sender_opt(self()),
2216            {i,"."},
2217            return_errors, return_warnings],
2218    Txt = case gpb_compile:file("X.proto", Opts) of
2219              {error, _Reason, _Warns}=Res when FormatWhat == format_error ->
2220                  gpb_compile:format_error(Res);
2221              {ok, Warns} when FormatWhat == format_warning ->
2222                  [gpb_compile:format_warning(Warn) || Warn <- Warns]
2223          end,
2224    IsIoList = io_lib:deep_char_list(Txt),
2225    ?assertMatch({true, _}, {IsIoList, Txt}),
2226    FlatTxt = lists:flatten(Txt),
2227    PhrasesFound = [gpb_lib:is_substr(Word, FlatTxt)
2228                    || Word <- ExpectedPhrases],
2229    AllPhrasesFound = lists:all(fun id/1, PhrasesFound),
2230    ?assertMatch({true,_,_}, {AllPhrasesFound, FlatTxt, PhrasesFound}).
2231
2232mk_file_retriever(MainProtoFileContents, ExtraFileOpReturnValues) ->
2233    ExtraFileReturnValues =
2234        proplists:get_value(read_file, ExtraFileOpReturnValues, []),
2235    fun(FileName) ->
2236            case lists:keysearch(FileName, 1, ExtraFileReturnValues) of
2237                {value, {FileName, ReturnValue}} ->
2238                    ReturnValue;
2239                false ->
2240                    {ok, MainProtoFileContents}
2241            end
2242    end.
2243
2244mk_read_file_info(_MainProtoFileName, ExtraFileOpReturnValues) ->
2245    ExtraFileReturnValues =
2246        proplists:get_value(read_file_info, ExtraFileOpReturnValues, []),
2247    fun(FileName) ->
2248            case lists:keysearch(FileName, 1, ExtraFileReturnValues) of
2249                {value, {FileName, ReturnValue}} ->
2250                    ReturnValue;
2251                false ->
2252                    {ok, #file_info{access=read}}
2253            end
2254    end.
2255
2256
2257%% --- hrl file tests -----------------
2258
2259defaults_for_proto3_fields_test() ->
2260    Proto = fun(ProtoVersion) ->
2261                    ["message m {",
2262                     case ProtoVersion of
2263                         proto2 ->
2264                             ["  optional int32    o_i32   = 11;",
2265                              "  optional string   o_str   = 12;",
2266                              "  optional m        o_subm  = 13;"];
2267                         proto3 ->
2268                             ["  int32    o_i32   = 11;",
2269                              "  string   o_str   = 12;",
2270                              "  m        o_subm  = 13;"]
2271                     end,
2272                     "  repeated int32 r_i = 21;",
2273                     "  oneof u { int32 u_i = 31; };",
2274                     "  map<int32, int32> mii = 41;",
2275                     "",
2276                     "}"]
2277            end,
2278    MkMod = fun(ProtoVersion, GOpts) ->
2279                    compile_erl_iolist(
2280                      ["-export([new_m_msg/0]).\n",
2281                       compile_to_string_get_hrl(
2282                         ["syntax=\"",atom_to_list(ProtoVersion),"\";\n",
2283                          Proto(ProtoVersion)],
2284                         [strip_preprocessor_lines | GOpts]),
2285                       "new_m_msg() -> #m{}.\n"])
2286            end,
2287    P3Ma = MkMod(proto3, [type_specs]),
2288    {m, 0, "", undefined, [], undefined, []} = P3Ma:new_m_msg(),
2289    unload_code(P3Ma),
2290
2291    P3Mb = MkMod(proto3, [type_specs, strings_as_binaries]),
2292    {m, 0, <<>>, undefined, [], undefined, []} = P3Mb:new_m_msg(),
2293    unload_code(P3Mb),
2294
2295    P3Mc = MkMod(proto3, []),
2296    {m, 0, "", undefined, [], undefined, []} = P3Mc:new_m_msg(),
2297    unload_code(P3Mc),
2298
2299    P2M = MkMod(proto2, []),
2300    {m, undefined, undefined, undefined, [], undefined, []} = P2M:new_m_msg(),
2301    unload_code(P2M).
2302
2303%% --- nif generation tests -----------------
2304
2305generates_nif_as_binary_and_file_test() ->
2306    Defs = mk_one_msg_field_of_each_type(),
2307    M = gpb_nif_test,
2308    LoadNif = "load_nif() -> erlang:load_nif({{nifbase}}, {{loadinfo}}).\n",
2309    LoadNifOpt = {load_nif, LoadNif},
2310    {ok, M, Codes} = gpb_compile:proto_defs(M, Defs, [binary, nif, LoadNifOpt]),
2311    Nif1 = proplists:get_value(nif, Codes),
2312    Master = self(),
2313    ReportWriteCc = fun(FName, Contents) ->
2314                            case filename:extension(FName) of
2315                                ".cc" -> Master ! {cc, Contents}, ok;
2316                                _     -> ok
2317                            end
2318                    end,
2319    FileOpOpt = mk_fileop_opt([{write_file, ReportWriteCc}]),
2320    ok = gpb_compile:proto_defs(M, Defs, [nif, FileOpOpt, LoadNifOpt]),
2321    Nif2 = receive {cc, Cc} -> Cc end,
2322    ?assertMatch(Nif1, Nif2).
2323
2324nif_code_test_() ->
2325    increase_timeouts(
2326      nif_tests_check_prerequisites(
2327        [{"Verify errors in sepatarate vm are caught",
2328          fun verify_errors_in_separate_vm_are_caught/0},
2329         {"Nif compiles", fun nif_compiles/0},
2330         {"Nif encode decode", fun nif_encode_decode/0},
2331         increase_timeouts(
2332           nif_oneof_tests_check_prerequisites(
2333             [{"encode decode", fun nif_encode_decode_oneof/0}])),
2334         increase_timeouts(
2335           nif_mapfield_tests_check_prerequisites(
2336             [{"encode decode", fun nif_encode_decode_mapfields/0}])),
2337         increase_timeouts(
2338           nif_proto3_tests_check_prerequisites(
2339             [{"encode decode", fun nif_encode_decode_proto3/0},
2340              {"Nif with C++ keywords", fun nif_with_cxx_keywords/0}])),
2341         {"Nif enums in msgs", fun nif_enum_in_msg/0},
2342         {"Nif enums with pkgs", fun nif_enum_with_pkgs/0},
2343         {"Nif enums from integers", fun nif_enum_from_integers/0},
2344         {"Nif with groups", fun nif_with_groups/0},
2345         {"Nif with strbin", fun nif_with_strbin/0},
2346         {"Nif with booleans", fun nif_with_booleans/0},
2347         {"Nif with list indata for bytes",
2348          fun nif_with_list_indata_for_bytes/0},
2349         {"Nif and +-Inf/NaN", fun nif_with_non_normal_floats/0},
2350         {"Error if both Any translations and nif",
2351          fun error_if_both_translations_and_nif/0}])).
2352
2353increase_timeouts({Descr, Tests}) ->
2354    %% On my slow 1.6 GHz Atom N270 machine, the map field test takes
2355    %% ~77 seconds to run, allow for a bit more
2356    PerTestTimeout = 140,
2357    {Descr,
2358     {timeout, PerTestTimeout * length(Tests),  %% timeout for all tests
2359      [{timeout, PerTestTimeout,
2360        [{TestDescr, TestFun}]}
2361       || {TestDescr, TestFun} <- Tests]}}.
2362
2363nif_tests_check_prerequisites(Tests) ->
2364    case nif_verify_prerequisites() of
2365        ok            -> {"nif tests", Tests};
2366        {error, Text} -> {Text, []}
2367    end.
2368
2369nif_verify_prerequisites() ->
2370    case {want_nif_tests(), find_protoc(), find_cplusplus_compiler()} of
2371        {false,_,_} -> {error, "Nif tests not wanted"};
2372        {_,false,_} -> {error, "Protoc not found, not trying to compile"};
2373        {_,_,false} -> {error, "No C++ compiler found, not trying to compile"};
2374        {_,_,_}     -> ok
2375    end.
2376
2377'do_nif?'() ->
2378    nif_verify_prerequisites() == ok.
2379
2380nif_oneof_tests_check_prerequisites(Tests) ->
2381    nif_oneof_tests_check_prerequisites("Nif with oneof fields", fun id/1, Tests).
2382
2383nif_oneof_tests_check_prerequisites(Title, ExtraPrereq, Tests) ->
2384    case 'do_nif?'() andalso check_protoc_can_do_oneof() of
2385        true  -> {Title, ExtraPrereq(Tests)};
2386        false -> {"Protoc < 2.6.0, not testing nifs with oneof", []}
2387    end.
2388
2389nif_mapfield_tests_check_prerequisites(Tests) ->
2390    case 'do_nif?'() andalso check_protoc_can_do_mapfields() of
2391        true  -> {"Nif with map fields", Tests};
2392        false -> {"Protoc < 3.0.0, not testing nifs with map fields", []}
2393    end.
2394
2395nif_proto3_tests_check_prerequisites(Tests) ->
2396    case 'do_nif?'() andalso check_protoc_can_do_proto3() of
2397        true  -> {"Nif with proto3", Tests};
2398        false -> {"Protoc < 3.0.0, not testing nifs with proto3", []}
2399    end.
2400
2401verify_errors_in_separate_vm_are_caught() ->
2402    %% Sanity check of the machinery for running tests in a separate vm
2403    %% Verify that any errors emanating from "the other side" are caught
2404    ?assertError({in_separate_vm, bad_badness},
2405                 with_tmpdir(
2406                   fun(TmpDir) ->
2407                           M = gpb_in_separate_vm_test_env_check,
2408                           Code = create_dummy_module(M),
2409                           in_separate_vm(
2410                             TmpDir, M, Code,
2411                             fun() ->
2412                                     erlang:error(bad_badness)
2413                             end)
2414                   end)).
2415
2416create_dummy_module(MName) ->
2417    {ok,Toks,_} = erl_scan:string(f("-module(~p).~n", [MName])),
2418    {ok,Form} = erl_parse:parse_form(Toks),
2419    {ok,MName,Code} = compile:forms([Form]),
2420    Code.
2421
2422nif_compiles() ->
2423    with_tmpdir(
2424      fun(TmpDir) ->
2425              NCM = gpb_nif_test_c1,
2426              Defs = mk_one_msg_field_of_each_type(),
2427              {ok, _Code} = compile_nif_msg_defs(NCM, Defs, TmpDir)
2428      end).
2429
2430nif_encode_decode() ->
2431    with_tmpdir(
2432      fun(TmpDir) ->
2433              NEDM = gpb_nif_test_ed1,
2434              Defs = mk_one_msg_field_of_each_type(),
2435              {ok, Code} = compile_nif_msg_defs(NEDM, Defs, TmpDir),
2436              in_separate_vm(
2437                TmpDir, NEDM, Code,
2438                fun() ->
2439                        nif_encode_decode_test_it(NEDM, Defs),
2440                        nif_encode_decode_strings(NEDM, Defs),
2441                        ok
2442                end)
2443      end).
2444
2445nif_encode_decode_test_it(NEDM, Defs) ->
2446    MsgNames = [MsgName || {{msg, MsgName}, _Fields} <- Defs],
2447    Variants = [small, big, short, long],
2448    lists:foreach(fun({MsgName, Variant}) ->
2449                          OrigMsg = mk_msg(MsgName, Defs, Variant),
2450                          %% to avoid errors in nif encode/decode
2451                          %% cancelling out each other and nif bugs go
2452                          %% undetected, cross-check with gpb:encode/decode_msg
2453                          MEncoded  = NEDM:encode_msg(OrigMsg),
2454                          GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2455                          MMDecoded = NEDM:decode_msg(MEncoded, MsgName),
2456                          GMDecoded = gpb:decode_msg(MEncoded, MsgName, Defs),
2457                          MGDecoded = NEDM:decode_msg(GEncoded, MsgName),
2458                          ?assertEqual(OrigMsg, MMDecoded),
2459                          ?assertEqual(OrigMsg, GMDecoded),
2460                          ?assertMatch({OrigMsg,_,_,_,_},
2461                                       {MGDecoded,OrigMsg,GEncoded,MEncoded,
2462                                        Variant})
2463                  end,
2464                  [{MsgName,Variant} || MsgName <- MsgNames,
2465                                        Variant <- Variants]).
2466
2467nif_encode_decode_strings(NEDM, Defs) ->
2468    %% Check UTF-8 encoding/decoding
2469    CodePoints = [0,                16#7f,  %% this range reqiures 1 octet
2470                  16#80,          16#7fff,  %% this range reqiures 2 octets
2471                  16#800,         16#FFff,  %% this range reqiures 3 octets
2472                  16#10000,     16#10FFff], %% this range reqiures 4 octets
2473    %%            16#200000,   16#3ffFFff,  %% would require 5 octets
2474    %%            16#4000000, 16#7fffFFff   %% would require 6 octets
2475    %% These are outside of unicode, but encodable integers using UTF-8:
2476    %% Maybe ought to run these through the nif encoder/decoder just
2477    %% to test its UTF-8 handling, but (a) would be able to cross check with
2478    %% the gpb encoder/decoder, and (b) might not get it through the protoc
2479    %% lib.
2480    lists:foreach(fun(CodePoint) ->
2481                          OrigMsg = {strmsg, [CodePoint]},
2482                          %% to avoid errors in nif encode/decode
2483                          %% cancelling out each other and nif bugs go
2484                          %% undetected, cross-check with gpb:encode/decode_msg
2485                          MEncoded  = NEDM:encode_msg(OrigMsg),
2486                          GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2487                          MMDecoded = NEDM:decode_msg(MEncoded, strmsg),
2488                          GMDecoded = gpb:decode_msg(MEncoded, strmsg, Defs),
2489                          MGDecoded = NEDM:decode_msg(GEncoded, strmsg),
2490                          ?assertEqual(OrigMsg, MMDecoded),
2491                          ?assertEqual(OrigMsg, GMDecoded),
2492                          ?assertEqual(OrigMsg, MGDecoded)
2493                  end,
2494                  CodePoints).
2495
2496nif_encode_decode_oneof() ->
2497    with_tmpdir(
2498      fun(TmpDir) ->
2499              NEDM = gpb_nif_test_ed_oneof1,
2500              Defs = mk_one_oneof_field_of_each_type(),
2501              {ok, Code} = compile_nif_msg_defs(NEDM, Defs, TmpDir),
2502              in_separate_vm(
2503                TmpDir, NEDM, Code,
2504                fun() ->
2505                        nif_encode_decode_oneof(NEDM, Defs),
2506                        ok
2507                end)
2508      end).
2509
2510
2511nif_encode_decode_oneof(NEDM, Defs) ->
2512    [#gpb_oneof{fields=OFields}] = [O || {{msg, oneof1}, [O]} <- Defs],
2513    Alts = [{Name, mk_field_value(OF, Defs, small)}
2514            || #?gpb_field{name=Name}=OF <- OFields] ++ [undefined],
2515    lists:foreach(fun(Alt) ->
2516                          OrigMsg = {oneof1, Alt},
2517                          %% to avoid errors in nif encode/decode
2518                          %% cancelling out each other and nif bugs go
2519                          %% undetected, cross-check with gpb:encode/decode_msg
2520                          MEncoded  = NEDM:encode_msg(OrigMsg),
2521                          GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2522                          MMDecoded = NEDM:decode_msg(MEncoded, oneof1),
2523                          GMDecoded = gpb:decode_msg(MEncoded, oneof1, Defs),
2524                          MGDecoded = NEDM:decode_msg(GEncoded, oneof1),
2525                          ?assertEqual(OrigMsg, MMDecoded),
2526                          ?assertEqual(OrigMsg, GMDecoded),
2527                          ?assertEqual(OrigMsg, MGDecoded)
2528                  end,
2529                  Alts).
2530
2531nif_encode_decode_mapfields() ->
2532    with_tmpdir(
2533      fun(TmpDir) ->
2534              NEDM = gpb_nif_test_ed_mapfields1,
2535              Defs = mk_one_map_field_of_each_type(),
2536              {ok, Code} = compile_nif_msg_defs(NEDM, Defs, TmpDir),
2537              in_separate_vm(
2538                TmpDir, NEDM, Code,
2539                fun() ->
2540                        nif_encode_decode_mapfields(NEDM, Defs),
2541                        ok
2542                end)
2543      end).
2544
2545nif_encode_decode_proto3() ->
2546    with_tmpdir(
2547      fun(TmpDir) ->
2548              NEDM = gpb_nif_test_ed_mapfields1,
2549              Defs = mk_proto3_fields(),
2550              {ok, Code} = compile_nif_msg_defs(NEDM, Defs, TmpDir),
2551              in_separate_vm(
2552                TmpDir, NEDM, Code,
2553                fun() ->
2554                        nif_encode_decode_test_it(NEDM, Defs),
2555                        ok
2556                end)
2557      end).
2558
2559nif_encode_decode_mapfields(NEDM, Defs) ->
2560    OrigMsg = usort_all_fields(mk_msg(map1, Defs, small_random)),
2561    %% cross-check with gpb:encode/decode_msg to avoid errors cancelling out
2562    MEncoded  = NEDM:encode_msg(OrigMsg),
2563    GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2564    MMDecoded = NEDM:decode_msg(MEncoded, map1),
2565    GMDecoded = gpb:decode_msg(MEncoded, map1, Defs),
2566    MGDecoded = NEDM:decode_msg(GEncoded, map1),
2567    ?assertEqual(OrigMsg, sort_all_fields(MMDecoded)),
2568    ?assertEqual(OrigMsg, sort_all_fields(GMDecoded)),
2569    ?assertEqual(OrigMsg, sort_all_fields(MGDecoded)).
2570
2571usort_all_fields(R) -> map_all_fields(R, fun usort_by_mapkey/1).
2572
2573sort_all_fields(R) -> map_all_fields(R, fun lists:sort/1).
2574
2575usort_by_mapkey(L) ->
2576    lists:sort(key_unique(L)).
2577
2578key_unique([{K,V} | Rest]) ->
2579    [{K,V} | key_unique([X2 || {K2,_}=X2 <- Rest, K2 =/= K])];
2580key_unique([]) ->
2581    [].
2582
2583map_all_fields(R, Fn) ->
2584    [RName | Fields] = tuple_to_list(R),
2585    list_to_tuple([RName | [Fn(Field) || Field <- Fields]]).
2586
2587nif_enum_in_msg() ->
2588    with_tmpdir(
2589      fun(TmpDir) ->
2590              M = gpb_nif_test_enum_in_msgs,
2591              DefsTxt = lf_lines(["message ntest1 {",
2592                                  "    enum bo {",
2593                                  "        x = 1;",
2594                                  "        y = 2;",
2595                                  "    };",
2596                                  "    optional bo f1 = 1;",
2597                                  "    repeated bo f2 = 2;",
2598                                  "}"]),
2599              Defs = parse_to_proto_defs(DefsTxt),
2600              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir),
2601              in_separate_vm(
2602                TmpDir, M, Code,
2603                fun() ->
2604                        OrigMsg = {ntest1,x,[x,y]},
2605                        MEncoded  = M:encode_msg(OrigMsg),
2606                        GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2607                        MMDecoded = M:decode_msg(MEncoded, ntest1),
2608                        GMDecoded = gpb:decode_msg(MEncoded, ntest1, Defs),
2609                        MGDecoded = M:decode_msg(GEncoded, ntest1),
2610                        ?assertEqual(OrigMsg, MMDecoded),
2611                        ?assertEqual(OrigMsg, GMDecoded),
2612                        ?assertEqual(OrigMsg, MGDecoded)
2613                end)
2614      end).
2615
2616nif_enum_with_pkgs() ->
2617    with_tmpdir(
2618      fun(TmpDir) ->
2619              M = gpb_nif_test_enum_with_pkgs,
2620              DefsTxt = lf_lines(["package p1.p2;",
2621                                  "    enum ee {",
2622                                  "        ee1 = 1;",
2623                                  "        ee2 = 2;",
2624                                  "    };",
2625                                  "message ntest2 {",
2626                                  "    optional ee f1 = 1;",
2627                                  "}"]),
2628              Defs = parse_to_proto_defs(DefsTxt),
2629              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir),
2630              in_separate_vm(
2631                TmpDir, M, Code,
2632                fun() ->
2633                        OrigMsg = {ntest2,ee1},
2634                        MEncoded  = M:encode_msg(OrigMsg),
2635                        GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2636                        MMDecoded = M:decode_msg(MEncoded, ntest2),
2637                        GMDecoded = gpb:decode_msg(MEncoded, ntest2, Defs),
2638                        MGDecoded = M:decode_msg(GEncoded, ntest2),
2639                        ?assertEqual(OrigMsg, MMDecoded),
2640                        ?assertEqual(OrigMsg, GMDecoded),
2641                        ?assertEqual(OrigMsg, MGDecoded)
2642                end)
2643      end).
2644
2645nif_enum_from_integers() ->
2646    with_tmpdir(
2647      fun(TmpDir) ->
2648              M = gpb_nif_test_enum_from_integers,
2649              DefsTxt = lf_lines(["enum e {",
2650                                  "    e0 = 0;",
2651                                  "    e1 = 1;",
2652                                  "};",
2653                                  "message ntest3 {",
2654                                  "    optional e f1 = 1;",
2655                                  "}"]),
2656              Defs = parse_to_proto_defs(DefsTxt),
2657              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir),
2658              in_separate_vm(
2659                TmpDir, M, Code,
2660                fun() ->
2661                        OrigMsg = {ntest3,1},
2662                        ExpectedEncoded = <<8,1>>,
2663                        MEncoded  = M:encode_msg(OrigMsg),
2664                        GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2665                        ?assertEqual(ExpectedEncoded, MEncoded),
2666                        ?assertEqual(ExpectedEncoded, GEncoded)
2667                end)
2668      end).
2669
2670nif_with_groups() ->
2671    with_tmpdir(
2672      fun(TmpDir) ->
2673              M = gpb_nif_with_groups,
2674              DefsTxt = lf_lines(["message m1 {",
2675                                  "    repeated group Rp = 10 {",
2676                                  "      required uint32 f = 11;",
2677                                  "    }",
2678                                  "    required group Rq = 20 {",
2679                                  "      required uint32 g = 21;",
2680                                  "    }",
2681                                  "    optional group O  = 30 {",
2682                                  "      required uint32 h = 31;",
2683                                  "    }",
2684                                  "}"]),
2685              Defs = parse_to_proto_defs(DefsTxt),
2686              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir),
2687              in_separate_vm(
2688                TmpDir, M, Code,
2689                fun() ->
2690                        OrigMsg = {m1,
2691                                   [{'m1.Rp',111},{'m1.Rp',112}],
2692                                   {'m1.Rq',211},
2693                                   {'m1.O',311}},
2694                        MEncoded  = M:encode_msg(OrigMsg),
2695                        GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2696                        MMDecoded = M:decode_msg(MEncoded, m1),
2697                        GMDecoded = gpb:decode_msg(MEncoded, m1, Defs),
2698                        MGDecoded = M:decode_msg(GEncoded, m1),
2699                        ?assertEqual(OrigMsg, MMDecoded),
2700                        ?assertEqual(OrigMsg, GMDecoded),
2701                        ?assertEqual(OrigMsg, MGDecoded)
2702                end)
2703      end).
2704
2705nif_with_strbin() ->
2706    with_tmpdir(
2707      fun(TmpDir) ->
2708              M = gpb_nif_with_strbin,
2709              DefsTxt = lf_lines(["message ntest2 {",
2710                                  "    required string s = 1;",
2711                                  "}"]),
2712              Defs = parse_to_proto_defs(DefsTxt),
2713              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir,
2714                                                [strings_as_binaries]),
2715              in_separate_vm(
2716                TmpDir, M, Code,
2717                fun() ->
2718                        OrigMsgB = {ntest2,<<"abc">>},
2719                        OrigMsgS = {ntest2,"abc"}, %% gpb can't do strbin
2720                        MEncoded  = M:encode_msg(OrigMsgB),
2721                        GEncoded  = gpb:encode_msg(OrigMsgB, Defs),
2722                        MMDecoded = M:decode_msg(MEncoded, ntest2),
2723                        GMDecoded = gpb:decode_msg(MEncoded, ntest2, Defs),
2724                        MGDecoded = M:decode_msg(GEncoded, ntest2),
2725                        ?assertEqual(OrigMsgB, MMDecoded),
2726                        ?assertEqual(OrigMsgS, GMDecoded),
2727                        ?assertEqual(OrigMsgB, MGDecoded)
2728                end)
2729      end).
2730
2731nif_with_booleans() ->
2732    with_tmpdir(
2733      fun(TmpDir) ->
2734              M = gpb_nif_with_booleans,
2735              DefsTxt = lf_lines(["message ntest3 {",
2736                                  "    required bool b = 1;",
2737                                  "}"]),
2738              Defs = parse_to_proto_defs(DefsTxt),
2739              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir, []),
2740              in_separate_vm(
2741                TmpDir, M, Code,
2742                fun() ->
2743                        OrigMsgInt = {ntest3,1},
2744                        OrigMsgAtom = {ntest3,true},
2745                        MEncoded  = M:encode_msg(OrigMsgInt),
2746                        GEncoded  = gpb:encode_msg(OrigMsgInt, Defs),
2747                        MMDecoded = M:decode_msg(MEncoded, ntest3),
2748                        GMDecoded = gpb:decode_msg(MEncoded, ntest3, Defs),
2749                        MGDecoded = M:decode_msg(GEncoded, ntest3),
2750                        ?assertEqual(OrigMsgAtom, MMDecoded),
2751                        ?assertEqual(OrigMsgAtom, GMDecoded),
2752                        ?assertEqual(OrigMsgAtom, MGDecoded)
2753                end)
2754      end).
2755
2756nif_with_cxx_keywords() ->
2757    with_tmpdir(
2758      fun(TmpDir) ->
2759              M = gpb_nif_with_cxx_keywords,
2760              DefsTxt = lf_lines(["enum E {",
2761                                  "  new = 0;",
2762                                  "  Delete = 1;",
2763                                  "}",
2764                                  "message ntestc {",
2765                                  "  optional E f1 = 1;"
2766                                  "  optional uint32 Private = 2;",
2767                                  "  oneof Union {",
2768                                  "    uint32 protected = 3;",
2769                                  "    uint32 Public = 4;",
2770                                  "  }",
2771                                  "}"]),
2772              Defs = parse_to_proto_defs(DefsTxt),
2773              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir, []),
2774              in_separate_vm(
2775                TmpDir, M, Code,
2776                fun() ->
2777                        OrigMsg = {ntestc,'Delete',2,{'Public',3}},
2778                        MEncoded  = M:encode_msg(OrigMsg),
2779                        GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2780                        MMDecoded = M:decode_msg(MEncoded, ntestc),
2781                        GMDecoded = gpb:decode_msg(MEncoded, ntestc, Defs),
2782                        MGDecoded = M:decode_msg(GEncoded, ntestc),
2783                        ?assertEqual(OrigMsg, MMDecoded),
2784                        ?assertEqual(OrigMsg, GMDecoded),
2785                        ?assertEqual(OrigMsg, MGDecoded)
2786                end)
2787      end).
2788
2789nif_with_list_indata_for_bytes() ->
2790    with_tmpdir(
2791      fun(TmpDir) ->
2792              M = gpb_nif_with_list_indata_for_bytes,
2793              DefsTxt = lf_lines(["message ntest5 {",
2794                                  "    required bytes s = 1;",
2795                                  "}"]),
2796              Defs = parse_to_proto_defs(DefsTxt),
2797              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir),
2798              in_separate_vm(
2799                TmpDir, M, Code,
2800                fun() ->
2801                        OrigMsgList = {ntest5,[4,3,2,1]},
2802                        OrigMsgBin = {ntest5,<<4,3,2,1>>},
2803                        MEncoded  = M:encode_msg(OrigMsgList),
2804                        GEncoded  = gpb:encode_msg(OrigMsgList, Defs),
2805                        MMDecoded = M:decode_msg(MEncoded, ntest5),
2806                        GMDecoded = gpb:decode_msg(MEncoded, ntest5, Defs),
2807                        MGDecoded = M:decode_msg(GEncoded, ntest5),
2808                        ?assertEqual(OrigMsgBin, MMDecoded),
2809                        ?assertEqual(OrigMsgBin, GMDecoded),
2810                        ?assertEqual(OrigMsgBin, MGDecoded)
2811                end)
2812      end).
2813
2814nif_with_non_normal_floats() ->
2815    with_tmpdir(
2816      fun(TmpDir) ->
2817              M = gpb_nif_with_non_normal_floats,
2818              DefsTxt = lf_lines(["message nnf1 {",
2819                                  "    required float f = 1;",
2820                                  "    required double d = 2;",
2821                                  "}"]),
2822              Defs = parse_to_proto_defs(DefsTxt),
2823              {ok, Code} = compile_nif_msg_defs(M, DefsTxt, TmpDir,
2824                                                [strings_as_binaries]),
2825              in_separate_vm(
2826                TmpDir, M, Code,
2827                fun() ->
2828                        [begin
2829                             OrigMsg = {nnf1,Item,Item},
2830                             MEncoded  = M:encode_msg(OrigMsg),
2831                             GEncoded  = gpb:encode_msg(OrigMsg, Defs),
2832                             MMDecoded = M:decode_msg(MEncoded, nnf1),
2833                             GMDecoded = gpb:decode_msg(MEncoded, nnf1, Defs),
2834                             MGDecoded = M:decode_msg(GEncoded, nnf1),
2835                             ?assertEqual(OrigMsg, MMDecoded),
2836                             ?assertEqual(OrigMsg, GMDecoded),
2837                             ?assertEqual(OrigMsg, MGDecoded)
2838                         end
2839                         || Item <- [infinity, '-infinity', nan]]
2840                end)
2841      end).
2842
2843error_if_both_translations_and_nif() ->
2844    %% This is expected to fail, already at option verification, ie
2845    %% not produce any files at all, but should it accidentally
2846    %% succeed (due to a bug or so), it is useful to have it included
2847    %% under the ordinary nif handling umbrella.
2848    with_tmpdir(
2849      fun(_TmpDir) ->
2850              DefsTxt = lf_lines(["message ntest3 {",
2851                                  "    required string s = 1;",
2852                                  "}"]),
2853              Opts = [nif,
2854                      {any_translate,[{encode,{m,e,['$1']}},
2855                                      {decode,{m,d,['$1']}},
2856                                      {merge,{m,m,['$1','$2']}},
2857                                      {verify,{m,v,['$1','$errorf']}}]}],
2858              {{return,{error, _}},
2859               {output,Output1}} =
2860                  compile_file_get_output(DefsTxt, Opts),
2861              true = gpb_lib:is_substr("nif", Output1),
2862              true = gpb_lib:is_substr("translat", Output1),
2863
2864              {{return,{error, _, []}},
2865               {output,""}} =
2866                  compile_file_get_output(DefsTxt, Opts ++ [return]),
2867
2868              ok
2869      end).
2870
2871compile_nif_msg_defs(M, MsgDefsOrIoList, TmpDir) ->
2872    compile_nif_msg_defs(M, MsgDefsOrIoList, TmpDir, []).
2873
2874compile_nif_msg_defs(M, MsgDefsOrIoList, TmpDir, Opts) ->
2875    {MsgDefs, ProtoTxt} =
2876        case is_iolist(MsgDefsOrIoList) of
2877            true -> {parse_to_proto_defs(MsgDefsOrIoList,Opts), MsgDefsOrIoList};
2878            false -> {MsgDefsOrIoList, msg_defs_to_proto(MsgDefsOrIoList)}
2879        end,
2880    [NifCcPath, PbCcPath, NifOPath, PbOPath, NifSoPath, ProtoPath] = Files  =
2881        [filename:join(TmpDir, lists:concat([M, Ext]))
2882         || Ext <- [".nif.cc", ".pb.cc", ".nif.o", ".pb.o", ".nif.so",
2883                    ".proto"]],
2884    LoadNif = f("load_nif() -> erlang:load_nif(\"~s\", {{loadinfo}}).\n",
2885                [filename:join(TmpDir, lists:concat([M,".nif"]))]),
2886    LoadNifOpt = {load_nif, LoadNif},
2887    Opts2 = [binary, nif, LoadNifOpt] ++ Opts,
2888    {ok, M, Codes} = gpb_compile:proto_defs(M, MsgDefs, Opts2),
2889    Code = proplists:get_value(erl, Codes),
2890    NifTxt = proplists:get_value(nif, Codes),
2891    %%
2892    ok = file:write_file(NifCcPath, NifTxt),
2893    ok = file:write_file(ProtoPath, ProtoTxt),
2894    %%
2895    CC = find_cplusplus_compiler(),
2896    Protoc = find_protoc(),
2897    CFlags = get_cflags(),
2898    LdFlags = get_ldflags(),
2899    CompileProto = f("'~s' --proto_path '~s' --cpp_out='~s' '~s'",
2900                     [Protoc, TmpDir, TmpDir, ProtoPath]),
2901    CompileNif = f("'~s' -g -fPIC -Wall -O0 '-I~s' ~s -c -o '~s' '~s'",
2902                   [CC, TmpDir, CFlags, NifOPath, NifCcPath]),
2903    CompilePb = f("'~s' -g -fPIC -Wall -O0 '-I~s' ~s -c -o '~s' '~s'",
2904                  [CC, TmpDir, CFlags, PbOPath, PbCcPath]),
2905    CompileSo = f("'~s' -g -fPIC -shared -Wall -O0 ~s"
2906                  "    -o '~s' '~s' '~s' -lprotobuf",
2907                  [CC, LdFlags, NifSoPath, NifOPath, PbOPath]),
2908    %% Useful if debugging the nif code, see also with_tmpdir(save, Fun)
2909    ToClean = [filename:basename(F) || F <- Files, F /= ProtoPath],
2910    file:write_file(filename:join(TmpDir, "Makefile"),
2911                    iolist_to_binary(
2912                      ["all:\n",
2913                       "\t", CompileProto, "\n",
2914                       "\t", CompileNif, "\n",
2915                       "\t", CompilePb, "\n",
2916                       "\t", CompileSo, "\n",
2917                       "\n",
2918                       "clean:\n",
2919                       "\t", "$(RM)", [[" ",F] || F <- ToClean], "\n"])),
2920    ok = ccompile("~s", ["set -evx\n"
2921                         ++ CompileProto ++ "\n"
2922                         ++ CompileNif ++ "\n"
2923                         ++ CompilePb ++ "\n"
2924                         ++ CompileSo]),
2925    {ok, Code}.
2926
2927lf_lines(Lines) ->
2928    [[L,"\n"] || L <- Lines].
2929
2930is_iolist(X) ->
2931    try iolist_to_binary(X), true
2932    catch error:badarg -> false
2933    end.
2934
2935parse_to_proto_defs(Iolist) ->
2936    parse_to_proto_defs(Iolist, []).
2937
2938parse_to_proto_defs(Iolist, Opts) ->
2939    B = iolist_to_binary(Iolist),
2940    {ok, ProtoDefs} = gpb_compile:file(
2941                        "X.proto",
2942                        [mk_fileop_opt([{read_file, fun(_) -> {ok, B} end}]),
2943                         {i,"."},
2944                         to_proto_defs, report_warnings] ++ Opts),
2945    ProtoDefs.
2946
2947%% Option to run with `save' for debugging nifs
2948with_tmpdir(Fun) ->
2949    with_tmpdir(dont_save, Fun).
2950with_tmpdir(Save, Fun) ->
2951    {ok, TmpDir} = get_tmpdir(),
2952    try Fun(TmpDir)
2953    after
2954        case Save of
2955            dont_save -> clean_tmpdir(TmpDir);
2956            save -> io:format(user, "~nSaved dir ~p~n", [TmpDir])
2957        end
2958    end.
2959
2960get_tmpdir() ->
2961    rand_seed(),
2962    mktempdir(
2963      filename:join(case os:getenv("TMPDIR") of
2964                        false -> "/tmp";
2965                        TDir  -> TDir
2966                    end,
2967                    lists:concat([?MODULE,"-",os:getenv("LOGNAME"),"-",
2968                                  os:getpid(),"-"]))).
2969
2970mktempdir(Base) ->
2971    D = Base ++ f("~8..0w", [rand_uniform(90000000)]),
2972    case file:make_dir(D) of
2973        ok             -> {ok, D};
2974        {error, exist} -> mktempdir(Base);
2975        Error          -> Error
2976    end.
2977
2978clean_tmpdir(TmpDir) ->
2979    os:cmd(f("/bin/rm -rf '~s'", [TmpDir])).
2980
2981in_separate_vm(TmpDir, Module, Code, Fun) ->
2982    %% With nifs in Erlang, one cannot control unloading of the nif,
2983    %% and thus cannot control when unloading of the protobuf library
2984    %% happens. I've seen cases where rapid unloading and reloading of
2985    %% nifs with new proto defs cause segvs (in strcmp), and from the
2986    %% stack trace, it looks like the protobuf library is unloading at
2987    %% the time when (or probably while) the next nif was being
2988    %% loaded. Since the loaded/linked protobuf dynamic library is a
2989    %% shared resource, if unloading and (re)loading happens in
2990    %% different threads, then there might be trouble.
2991    %%
2992    %% Therefore, to make the eunit tests stable, we run them in a
2993    %% separate vm.
2994    TmpCodeWrapperFun = fun() ->
2995                                try
2996                                    load_code(Module, Code),
2997                                    Fun()
2998                                after
2999                                    unload_code(Module)
3000                                end
3001                        end,
3002    FBin = term_to_binary(TmpCodeWrapperFun),
3003    FBinFile = filename:join(TmpDir, "fun-to-run"),
3004    FResFile = filename:join(TmpDir, "fun-run-result"),
3005    ok = file:write_file(FBinFile, FBin),
3006    DirOfThisBeam = filename:dirname(code:which(?MODULE)),
3007    GpbEbin = filename:dirname(code:which(gpb)),
3008    ModuleS = atom_to_list(?MODULE),
3009    CmdResult = run_cmd_collect_output(
3010                  "erl",
3011                  ["+B","-noinput",
3012                   "-boot","start_clean",
3013                   "-sasl","errlog_type","true",
3014                   "-pa",TmpDir,
3015                   "-pa",DirOfThisBeam,
3016                   "-pa",GpbEbin,
3017                   "-run",ModuleS,"main_in_separate_vm", FBinFile,FResFile]),
3018    analyze_output_from_separate_vm(CmdResult, FResFile).
3019
3020main_in_separate_vm([FBinFile, FResFile]) ->
3021    {ok, FBin} = file:read_file(FBinFile),
3022    Fun = binary_to_term(FBin),
3023    Res = try Fun()
3024          catch Class:Reason -> {'EXIT',{Class,Reason,erlang:get_stacktrace()}}
3025          end,
3026    ResBin = term_to_binary(Res),
3027    WRes = file:write_file(FResFile, ResBin),
3028    io:format("Wrote result file (~p bytes) -> ~p~n", [byte_size(ResBin),WRes]),
3029    ensure_output_flushed_halt().
3030
3031ensure_output_flushed_halt() ->
3032    case erlang:system_info(otp_release) of
3033        "R"++_ = Release ->
3034            %% Erlang R16 or earlier, attempt to support earlier releases
3035            %% if not too much work.
3036            if Release >= "R15B01" ->
3037                    %% R15B01 and later: halt waits until pending io has finished
3038                    halt(0);
3039               Release < "R15B01" ->
3040                    timer:sleep(100),
3041                    halt(0)
3042            end;
3043        _ ->
3044            %% Erlang 17 or later
3045            halt(0)
3046    end.
3047
3048run_cmd_collect_output(Cmd, Args) ->
3049    case os:find_executable(Cmd) of
3050        false ->
3051            error({could_not_find_cmd,Cmd});
3052        CmdPath ->
3053            Port = erlang:open_port({spawn_executable,CmdPath},
3054                                    [use_stdio, stderr_to_stdout, binary,
3055                                     exit_status, {args,Args}]),
3056            collect_output(Port, [])
3057    end.
3058
3059collect_output(Port, Acc) ->
3060    receive
3061        {Port, {data, Txt}} ->
3062            collect_output(Port, [Txt | Acc]);
3063        {Port, {exit_status,ExitCode}} ->
3064            {ExitCode, iolist_to_binary(lists:reverse(Acc))}
3065    end.
3066
3067analyze_output_from_separate_vm({ExitCode, Output}, ResultFile) ->
3068    case file:read_file(ResultFile) of
3069        {ok, B} ->
3070            case binary_to_term(B) of
3071                {'EXIT',{Class,Reason,StackTrace}} ->
3072                    erlang:raise(Class, {in_separate_vm,Reason}, StackTrace);
3073                _Result ->
3074                    %% Anything not a crash is success, just like usual
3075                    ok
3076            end;
3077        {error, Reason} ->
3078            ?debugFmt("~nNo result from separate vm, output=~n~s~n", [Output]),
3079            error({no_result_file_from_separate_vm,{ResultFile,Reason},
3080                   {exit_code,ExitCode},
3081                   {execution_output,Output}})
3082    end.
3083
3084test_nifs(Boolean) when is_boolean(Boolean) ->
3085    os:putenv("GPB_NIF_TESTS", lists:concat([Boolean])).
3086
3087want_nif_tests() ->
3088    %% It can be useful to disable nif testing.
3089    %% Previously, it was very desirable, as described below,
3090    %% but since the move to test nifs in a separate vm,
3091    %% this is no longer as compelling a reason. It might still
3092    %% be desirable, eg if the c++ or protoc is not set up.
3093    %%
3094    %% Previously, when the nif tests were executed
3095    %% in the same vm as the eunit tests, then due to the
3096    %% behavior in the libprotoc, that if it detects loading
3097    %% a proto definition with the same name as it already
3098    %% has loaded, it will refuse, and may stop the entire
3099    %% erlang-vm. See the documentation in gpb_compile:c/1,2,
3100    %% the `nif' option, for further details. I have seen it
3101    %% halt the entire erlang-vm when tests failed, which is
3102    %% a pity e.g. when the vm is in an interactive inferior
3103    %% emacs window
3104    case os:getenv("GPB_NIF_TESTS") of
3105        false   -> true; %% default is to test nifs
3106        "true"  -> true;
3107        "false" -> false
3108    end.
3109
3110find_cplusplus_compiler() ->
3111    case os:getenv("CXX") of
3112        false ->
3113            case os:find_executable("g++") of
3114                false -> os:find_executable("c++");
3115                Gxx   -> Gxx
3116            end;
3117        CxxCompiler ->
3118            CxxCompiler
3119    end.
3120
3121find_protoc() ->
3122    case os:getenv("PROTOC") of
3123        false  -> os:find_executable("protoc");
3124        Protoc -> Protoc
3125    end.
3126
3127check_protoc_can_do_oneof() ->
3128    cachingly_check('$cached_check_protoc_can_do_oneof',
3129                    %% oneof appeared in 2.6.0
3130                    fun() -> check_protoc_version_is_at_least([2,6]) end).
3131
3132check_protoc_can_do_mapfields() ->
3133    cachingly_check('$cached_check_protoc_can_do_mapfields',
3134                    %% map<_,_> appeared in 3.0.0
3135                    fun() -> check_protoc_version_is_at_least([3,0]) end).
3136
3137check_protoc_can_do_proto3() ->
3138    cachingly_check('$cached_check_protoc_can_do_proto3',
3139                    %% proto3 appeared in 3.0.0 :)
3140                    fun() -> check_protoc_version_is_at_least([3,0]) end).
3141
3142check_protoc_version_is_at_least(MinVsn) ->
3143    case cachingly_find_protoc_version() of
3144        {ok, Vsn} -> Vsn >= MinVsn;
3145        {error,_} -> false
3146    end.
3147
3148cachingly_find_protoc_version() ->
3149    cachingly_check('$cached_protoc_version', fun find_protoc_version/0).
3150
3151cachingly_check(CacheKey, F) ->
3152    case get(CacheKey) of
3153        undefined ->
3154            CanIt = F(),
3155            put(CacheKey, CanIt),
3156            CanIt;
3157        CanIt ->
3158            CanIt
3159    end.
3160
3161find_protoc_version() ->
3162    Output = os:cmd(find_protoc() ++ " --version"),
3163    Words = gpb_lib:string_lexemes(Output, " \t\r\n"),
3164    case find_protoc_version_aux(Words, Output) of
3165        {ok, _}=Res -> Res;
3166        {error, X}=Res ->
3167            ?debugFmt("Trouble finding protoc version in ~s~n", [X]),
3168            Res
3169    end.
3170
3171find_protoc_version_aux(["libprotoc", VersionStr | _], All) ->
3172    Components = gpb_lib:string_lexemes(VersionStr, "."),
3173    try {ok, [list_to_integer(X) || X <- Components]}
3174    catch error:badarg -> {error, {failed_to_interpret, VersionStr, All}}
3175    end;
3176find_protoc_version_aux([_ | Rest], All) ->
3177    find_protoc_version_aux(Rest, All);
3178find_protoc_version_aux([], All) ->
3179    {error, {no_version_string_found, All}}.
3180
3181get_cflags() ->
3182    Root = code:root_dir(), %% e.g. /usr/lib/erlang
3183    CIncDir = filename:join([Root, "usr", "include"]),
3184    case os:getenv("CFLAGS") of
3185        false  -> "";
3186        CFlags -> CFlags
3187    end ++ case os:getenv("CXXFLAGS") of
3188               false    -> "";
3189               CxxFlags -> CxxFlags
3190           end ++ " " ++ f("-I'~s'", [CIncDir]).
3191
3192platform_ldflags({unix, darwin}) ->
3193  " -undefined dynamic_lookup -dynamiclib";
3194platform_ldflags(_) ->
3195  "".
3196
3197get_ldflags() ->
3198    case os:getenv("LDFLAGS") of
3199        false   -> "";
3200        LdFlags -> LdFlags
3201    end ++ platform_ldflags(os:type()).
3202
3203msg_defs_to_proto(MsgDefs) ->
3204    iolist_to_binary(
3205      [maybe_syntaxdef(MsgDefs),
3206       lists:map(fun(M) -> msg_def_to_proto(M, MsgDefs) end, MsgDefs)]).
3207
3208maybe_syntaxdef(MsgDefs) ->
3209    case proplists:get_value(syntax, MsgDefs) of
3210        undefined ->
3211            case contains_any_maptype_field(MsgDefs) of
3212                true  -> "syntax = \"proto2\";\n";
3213                false -> ""
3214            end;
3215        Syntax ->
3216            f("syntax = \"~s\";\n", [Syntax])
3217    end.
3218
3219contains_any_maptype_field(MsgDefs) ->
3220    lists:any(fun(Fields) ->
3221                      lists:any(fun(#?gpb_field{type={map,_,_}}) -> true;
3222                                   (_) -> false
3223                                end,
3224                                Fields)
3225              end,
3226              [Fields || {{msg,_}, Fields} <- MsgDefs]).
3227
3228msg_def_to_proto({{enum, Name}, EnumValues}, _MsgDefs) ->
3229    f("enum ~s {~n~s}~n~n",
3230      [Name, lists:map(fun format_enumerator/1, EnumValues)]);
3231msg_def_to_proto({{msg, Name}, Fields}, MsgDefs) ->
3232    IsProto3 = gpb:is_msg_proto3(Name, MsgDefs),
3233    f("message ~s {~n~s}~n~n",
3234      [Name, lists:map(fun(F) -> format_field(F, IsProto3) end, Fields)]);
3235msg_def_to_proto(_OtherElem, _MsgDefs) ->
3236    "".
3237
3238
3239format_enumerator({N,V}) ->
3240    f("  ~s = ~w;~n", [N, V]).
3241
3242format_field(#?gpb_field{name=FName, fnum=FNum, type=Type,
3243                         occurrence=Occurrence},
3244             IsProto3) ->
3245    OccurrenceTxt = if Occurrence == repeated -> repeated;
3246                       IsProto3               -> "";
3247                       true                   -> Occurrence
3248                    end,
3249    case Type of
3250        {map,_,_} ->
3251            f("  ~s ~s = ~w;~n", [format_type(Type), FName, FNum]);
3252        _ ->
3253            f("  ~s ~s ~s = ~w;~n",
3254              [OccurrenceTxt, format_type(Type), FName, FNum])
3255    end;
3256format_field(#gpb_oneof{name=FName, fields=Fields}, _IsProto3) ->
3257    f("  oneof ~s {~n"
3258      "~s"
3259      "  };~n",
3260      [FName,
3261       [f("    ~s ~s = ~w;~n", [format_type(Type), OFName, FNum])
3262        || #?gpb_field{name=OFName, fnum=FNum, type=Type} <- Fields]]).
3263
3264format_type({msg,Name})  -> Name;
3265format_type({enum,Name}) -> Name;
3266format_type({map,KeyType,ValueType}) ->
3267    f("map<~s,~s>", [format_type(KeyType), format_type(ValueType)]);
3268format_type(Type) ->
3269    Type.
3270
3271ccompile(F, A) ->
3272    Cmd = f(F, A),
3273    Output = os:cmd("LC_ALL=C; export LC_ALL; " ++ Cmd ++ "; echo $?\n"),
3274    [LastLine | _Rest] = lists:reverse(gpb_lib:string_lexemes(Output, "\r\n")),
3275    try list_to_integer(string_trim(LastLine)) of
3276        0 -> ok;
3277        _ -> ?debugFmt("Compilation failed!~nCmd=~p~nOutput:~n~ts~n~n",
3278                       [Cmd, Output]),
3279             {error, Output}
3280    catch error:badarg ->
3281            ?debugFmt("Compilation failed!~nCmd=~p~nOutput:~n~ts~n~n",
3282                      [Cmd, Output]),
3283            {error, Output}
3284    end.
3285
3286mk_one_msg_field_of_each_type() ->
3287    EachType   = [sint32, sint64, int32, int64, uint32,
3288                  uint64, bool, fixed64, sfixed64,
3289                  double, string, bytes, fixed32, sfixed32,
3290                  float, {enum, ee}, {msg, submsg1}],
3291    EnumDef    = {{enum, ee}, [{en1, 1}, {en2, 2}]},
3292    SubMsgDef  = {{msg, submsg1}, mk_fields_of_type([uint32], required)},
3293    TopMsgDef1 = {{msg, topmsg1}, mk_fields_of_type(EachType, required)},
3294    TopMsgDef2 = {{msg, topmsg2}, mk_fields_of_type(EachType, repeated)},
3295    TopMsgDef3 = {{msg, topmsg3}, mk_fields_of_type(EachType, optional)},
3296    StringMsg = {{msg,strmsg}, mk_fields_of_type([string], required)},
3297    [EnumDef, SubMsgDef, TopMsgDef1, TopMsgDef2, TopMsgDef3, StringMsg].
3298
3299mk_one_oneof_field_of_each_type() ->
3300    EachType   = [sint32, sint64, int32, int64, uint32,
3301                  uint64, bool, fixed64, sfixed64,
3302                  double, string, bytes, fixed32, sfixed32,
3303                  float, {enum, ee}, {msg, submsg1}],
3304    EnumDef    = {{enum, ee}, [{en1, 1}, {en2, 2}]},
3305    SubMsgDef  = {{msg, submsg1}, mk_fields_of_type([uint32], required)},
3306    OneofMsg1  = {{msg, oneof1},  mk_oneof_fields_of_type(EachType, 1)},
3307    [EnumDef, SubMsgDef, OneofMsg1].
3308
3309mk_one_map_field_of_each_type() ->
3310    %% Reduced set of int types to shorten compilation times,
3311    %% while still cover all (most) code paths.
3312    ValueTypes = [sint32, sint64,
3313                  bool,
3314                  double, string, bytes,
3315                  float, {enum, ee}, {msg, submsg1}],
3316    ValueTypes2 = ValueTypes -- [sint64],
3317    KeyTypes   = [T || T <- ValueTypes, gpb:is_allowed_as_key_type(T)],
3318    %% Enum value in map must define 0 as the first value.
3319    EnumDef    = {{enum, ee}, [{en0, 0}, {en1, 1}, {en2, 2}]},
3320    SubMsgDef  = {{msg, submsg1}, mk_fields_of_type([uint32], required)},
3321    MapfldMsg1 = {{msg, map1},  mk_map_fields_of_type(KeyTypes, ValueTypes2)},
3322    [EnumDef, SubMsgDef, MapfldMsg1].
3323
3324mk_proto3_fields() ->
3325    EachType   = [sint32, sint64, bool, double, string, bytes, {enum, ee}],
3326    MsgType    = {msg, submsg1},
3327    EnumDef    = {{enum, ee}, [{en0, 0}, {en1, 1}, {en2, 2}]},
3328    SubMsgDef  = {{msg, submsg1}, mk_fields_of_type([uint32], optional)},
3329    TopMsgDef1 = {{msg, topmsg1}, mk_fields_of_type(
3330                                    EachType ++ [MsgType],
3331                                    optional)},
3332    TopMsgDef2 = {{msg, topmsg2}, mk_fields_of_type(
3333                                    EachType ++ [MsgType],
3334                                    repeated,
3335                                    [{field_opts_f, fun maybe_packed/1}])},
3336    OneofMsg1  = {{msg, oneof1},  mk_oneof_fields_of_type([fixed32], 1)},
3337    [{syntax, "proto3"},
3338     {proto3_msgs, [topmsg1,topmsg2,oneof1,submsg1]},
3339     EnumDef, SubMsgDef, TopMsgDef1, TopMsgDef2, OneofMsg1].
3340
3341mk_fields_of_type(Types, Occurrence) ->
3342    mk_fields_of_type(Types, Occurrence, []).
3343
3344mk_fields_of_type(Types, Occurrence, Opts) ->
3345    FieldOptsF = proplists:get_value(field_opts_f, Opts, fun(_) -> [] end),
3346    Offset = proplists:get_value(offset, Opts, 0),
3347    Types1 = [Type || Type <- Types, can_do_nif_type(Type)],
3348    [#?gpb_field{name=list_to_atom(lists:concat([f, I + Offset])),
3349                 rnum=I + 1 + Offset,
3350                 fnum=I + Offset,
3351                 type=Type,
3352                 occurrence=Occurrence,
3353                 opts=FieldOptsF(Type)}
3354     || {I, Type} <- index_seq(Types1)].
3355
3356mk_oneof_fields_of_type(Types, Pos) ->
3357    Types1 = [Type || Type <- Types, can_do_nif_type(Type)],
3358    [#gpb_oneof{
3359        name   = o,
3360        rnum   = Pos+1,
3361        fields = [#?gpb_field{name=list_to_atom(lists:concat([f,I])),
3362                              rnum=Pos+1,
3363                              fnum=I,
3364                              type=Type,
3365                              occurrence=optional,
3366                              opts=[]}
3367                  || {I, Type} <- index_seq(Types1)]}].
3368
3369mk_map_fields_of_type(KeyTypes, ValueTypes) ->
3370    KeyTypes1 = [KT1 | _] = [T || T <- KeyTypes, can_do_nif_type(T)],
3371    ValueTypes1 = [VT1 | _] = [T || T <- ValueTypes, can_do_nif_type(T)],
3372    Fs1 = [#?gpb_field{type={map,KT1,VT}, occurrence=repeated, opts=[]}
3373           || VT <- ValueTypes1],
3374    Fs2 = [#?gpb_field{type={map,KT,VT1}, occurrence=repeated, opts=[]}
3375           || KT <- KeyTypes1],
3376    Fs3 = tl(Fs2), % avoid KT1,VT1 twice
3377    [F#?gpb_field{name=list_to_atom(lists:concat([f,I])), rnum=I+1, fnum=I}
3378     || {I, F} <- index_seq(Fs1 ++ Fs3)].
3379
3380index_seq(L) -> lists:zip(lists:seq(1, length(L)), L).
3381
3382maybe_packed({msg,_})   -> [];
3383maybe_packed({map,_,_}) -> [];
3384maybe_packed(string)    -> [];
3385maybe_packed(bytes)     -> [];
3386maybe_packed(_)         -> [packed].
3387
3388can_do_nif_type(Type) ->
3389    if Type == int64;
3390       Type == sint64;
3391       Type == sfixed64 ->
3392            %% There's an issue with Erlang 17.0+ (will probably be
3393            %% fixed in 17.2): if compiled with gcc 4.9.0 (or newer, probably)
3394            %% and running on a 32-bit, there is an undefined behaviour
3395            %% which will make the test fail for nifs for sint64
3396            %% for INT64_MIN (-9223372036854775808). See also:
3397            %% http://erlang.org/pipermail/erlang-bugs/2014-July/004513.html
3398            case {is_erlvm_compiled_with_gcc490_or_later(), is_32_bit_os()} of
3399                {true, true} ->
3400                    OtpVsn = get_erlang_otp_major(),
3401                    if OtpVsn <  17 -> true;
3402                       OtpVsn == 17 -> false; % assume bug present
3403                       OtpVsn >  17 -> true   % assume fixed
3404                    end;
3405                _ ->
3406                    true
3407            end;
3408       true ->
3409            true
3410    end.
3411
3412is_erlvm_compiled_with_gcc490_or_later() ->
3413    {Compiler, Version} = erlang:system_info(c_compiler_used),
3414    if Compiler == gnuc, is_tuple(Version) ->
3415            tuple_to_list(Version) >= [4,9,0];
3416       true ->
3417            undefined
3418    end.
3419
3420is_32_bit_os() ->
3421    erlang:system_info({wordsize,external}) == 4. %% Erlang R14+
3422
3423get_erlang_otp_major() ->
3424    case erlang:system_info(otp_release) of
3425        "R"++Rest -> % R16 or ealier
3426            list_to_integer(lists:takewhile(fun is_digit/1, Rest));
3427        RelStr ->
3428            %% In Erlang 17 the leading "R" was dropped,
3429            %% allow for some (possible?) variation
3430            try list_to_integer(RelStr)
3431            catch error:badarg ->
3432                    [NStr | _] = gpb_lib:string_lexemes(RelStr, ".-"),
3433                    try list_to_integer(NStr)
3434                    catch error:badarg -> error({unexpected_otp_version,RelStr})
3435                    end
3436            end
3437    end.
3438
3439is_digit(C) when $0 =< C, C =< $9 -> true;
3440is_digit(_) -> false.
3441
3442mk_msg(MsgName, Defs, Variant) ->
3443    {{msg, MsgName}, Fields} = lists:keyfind({msg, MsgName}, 1, Defs),
3444    R0 = erlang:make_tuple(length(Fields) + 1, undefined, [{1, MsgName}]),
3445    lists:foldl(fun(#?gpb_field{rnum=RNum}=Field, R) ->
3446                        Value = mk_field_value(Field, Defs, Variant),
3447                        setelement(RNum, R, Value);
3448                   (#gpb_oneof{rnum=RNum, fields=[OField1 | _]}, R) ->
3449                        #?gpb_field{name=Name} = OField1,
3450                        Value = mk_field_value(OField1, Defs, Variant),
3451                        setelement(RNum, R, {Name, Value})
3452                end,
3453                R0,
3454                Fields).
3455
3456mk_field_value(#?gpb_field{occurrence=repeated}, _Defs, short) ->
3457    [];
3458mk_field_value(#?gpb_field{occurrence=repeated, type=T}=F, Defs, Variant) ->
3459    case T of
3460        {map, KeyType, ValueType} ->
3461            KF = F#?gpb_field{type=KeyType, occurrence=required},
3462            VF = F#?gpb_field{type=ValueType, occurrence=required},
3463            [begin
3464                 K = mk_field_value(KF, Defs, Variant),
3465                 V = mk_field_value(VF, Defs, Variant),
3466                 {K, V}
3467             end
3468             || _ <- lists:seq(1,10)];
3469        _ ->
3470            [mk_field_value(F#?gpb_field{occurrence=required}, Defs, Variant)]
3471    end;
3472mk_field_value(#?gpb_field{type=sint32}, _Defs, Vnt)   -> mk_sint(32, Vnt);
3473mk_field_value(#?gpb_field{type=sint64}, _Defs, Vnt)   -> mk_sint(64, Vnt);
3474mk_field_value(#?gpb_field{type=int32}, _Defs, Vnt)    -> mk_sint(32, Vnt);
3475mk_field_value(#?gpb_field{type=int64}, _Defs, Vnt)    -> mk_sint(64, Vnt);
3476mk_field_value(#?gpb_field{type=uint32}, _Defs, Vnt)   -> mk_uint(32, Vnt);
3477mk_field_value(#?gpb_field{type=uint64}, _Defs, Vnt)   -> mk_uint(64, Vnt);
3478mk_field_value(#?gpb_field{type=bool}, _Defs, Vnt)     -> mk_bool(Vnt);
3479mk_field_value(#?gpb_field{type=fixed64}, _Defs, Vnt)  -> mk_uint(64, Vnt);
3480mk_field_value(#?gpb_field{type=sfixed64}, _Defs, Vnt) -> mk_sint(64, Vnt);
3481mk_field_value(#?gpb_field{type=double}, _Defs, Vnt)   -> mk_float(64, Vnt);
3482mk_field_value(#?gpb_field{type=string}, _Defs, Vnt)   -> mk_string(Vnt);
3483mk_field_value(#?gpb_field{type=bytes}, _Defs, Vnt)    -> mk_bytes(Vnt);
3484mk_field_value(#?gpb_field{type=fixed32}, _Defs, Vnt)  -> mk_uint(32, Vnt);
3485mk_field_value(#?gpb_field{type=sfixed32}, _Defs, Vnt) -> mk_sint(32, Vnt);
3486mk_field_value(#?gpb_field{type=float}, _Defs, Vnt)    -> mk_float(32, Vnt);
3487mk_field_value(#?gpb_field{type={enum, E}}, Defs, Variant) ->
3488    {{enum, E}, [{E1 , _V1} | _Rest]=Es} = lists:keyfind({enum, E}, 1, Defs),
3489    case Variant of
3490        small_random ->
3491            element(1,random_nth(Es));
3492        _ ->
3493            E1
3494    end;
3495mk_field_value(#?gpb_field{type={msg, SubMsgName}}, Defs, Vnt) ->
3496    mk_msg(SubMsgName, Defs, Vnt).
3497
3498mk_sint(32, small)        -> - (1 bsl 31);
3499mk_sint(32, big)          -> (1 bsl 31) - 1;
3500mk_sint(64, small)        -> - (1 bsl 63);
3501mk_sint(64, big)          -> (1 bsl 63) - 1;
3502mk_sint(_,  small_random) -> random_int(-100, 100);
3503mk_sint(_,  _)            -> 0.
3504
3505mk_uint(32, big)          -> (1 bsl 32) - 1;
3506mk_uint(64, big)          -> (1 bsl 64) - 1;
3507mk_uint(_,  small_random) -> random_int(0, 100);
3508mk_uint(_,  _)            -> 0.
3509
3510mk_bool(small)        -> false;
3511mk_bool(small_random) -> case random_int(0,1) of
3512                             0 -> false;
3513                             1 -> true
3514                         end;
3515mk_bool(_)            -> true.
3516
3517mk_string(short)        -> "";
3518mk_string(big)          -> [16#10ffff];
3519mk_string(small_random) -> [random_int($a, $z) || _ <- lists:seq(1,10)];
3520mk_string(_)            -> "a".
3521
3522mk_bytes(short)        -> <<>>;
3523mk_bytes(small_random) -> list_to_binary(mk_string(small_random));
3524mk_bytes(_)            -> <<"b">>.
3525
3526mk_float(_, small_random) -> float(random_int(-10, 10));
3527mk_float(_, _)            -> 1.0.
3528
3529random_nth(Seq) ->
3530    lists:nth(random_int(1, length(Seq)), Seq).
3531
3532random_int(LowerLim, UpperLim) ->
3533    ensure_seeded(),
3534    rand_uniform(UpperLim - LowerLim + 1) + LowerLim - 1.
3535
3536ensure_seeded() ->
3537    rand_seed().
3538
3539%% --- command line options tests -----------------
3540
3541cmdline_parses_include_opt_test() ->
3542    {ok, {[{i,"inc"}], []}} = gpb_compile:parse_opts_and_args(["-Iinc"]),
3543    {ok, {[{i,"inc"}], []}} = gpb_compile:parse_opts_and_args(["-I","inc"]),
3544    {error, _} = gpb_compile:parse_opts_and_args(["-I"]).
3545
3546cmdline_parses_noarg_opt_test() ->
3547    {ok, {[defs_as_proplists], []}} =
3548         gpb_compile:parse_opts_and_args(["-pldefs"]).
3549
3550cmdline_parses_string_opt_test() ->
3551    {ok, {[{o_erl, "src"}], []}} =
3552        gpb_compile:parse_opts_and_args(["-o-erl", "src"]),
3553    {error, _} = gpb_compile:parse_opts_and_args(["-o-erl"]).
3554
3555cmdline_parses_alternatives_opt_test() ->
3556    {ok, {[{copy_bytes, true}], []}} =
3557        gpb_compile:parse_opts_and_args(["-c", "true"]),
3558    {ok, {[{copy_bytes, 1.25}], []}} =
3559        gpb_compile:parse_opts_and_args(["-c", "1.25"]).
3560
3561cmdline_parses_files_test() ->
3562    {ok, {[], []}} = gpb_compile:parse_opts_and_args([]),
3563    {ok, {[], ["f.proto"]}} = gpb_compile:parse_opts_and_args(["f.proto"]).
3564
3565cmdline_parses_also_non_proto_extensions_test() ->
3566    {ok, {[type_specs, {copy_bytes,auto}], ["a.x", "y.proto"]}} =
3567        gpb_compile:parse_opts_and_args(["-type", "-c", "auto",
3568                                         "a.x", "y.proto"]).
3569
3570opt_test() ->
3571    %% Include dirs + out dirs
3572    {ok, {[{i, "include1"},
3573           {i, "include2"},
3574           {o, "out-dir"},
3575           {o_erl, "o-erl-dir"},
3576           {o_hrl, "o-hrl-dir"}],
3577          ["x.proto", "y.proto"]}} =
3578        gpb_compile:parse_opts_and_args(
3579          ["-Iinclude1",
3580           "-I", "include2",
3581           "-o", "out-dir",
3582           "-o-erl", "o-erl-dir",
3583           "-o-hrl", "o-hrl-dir",
3584           "x.proto", "y.proto"]),
3585    %% nif related
3586    {ok, {[{o_nif_cc, "o-nif-cc-dir"},
3587           nif,
3588           {load_nif, "load-nif"}],
3589          ["x.proto"]}} =
3590        gpb_compile:parse_opts_and_args(
3591          ["-o-nif-cc", "o-nif-cc-dir",
3592           "-nif",
3593           "-load_nif", "load-nif",
3594           "x.proto"]),
3595    %% misc
3596    {ok, {[{verify, optionally},
3597           {verify, always},
3598           {verify, never},
3599           {copy_bytes, true},
3600           {copy_bytes, false},
3601           {copy_bytes, auto},
3602           {copy_bytes, 42}],
3603          ["x.proto"]}} =
3604        gpb_compile:parse_opts_and_args(
3605          ["-v", "optionally",
3606           "-v", "always",
3607           "-v", "never",
3608           "-c", "true",
3609           "-c", "false",
3610           "-c", "auto",
3611           "-c", "42",
3612           "x.proto"]),
3613    {ok, {[strings_as_binaries,
3614           use_packages,
3615           include_as_lib,
3616           type_specs,
3617           descriptor],
3618          ["x.proto"]}} =
3619        gpb_compile:parse_opts_and_args(
3620          ["-strbin",
3621           "-pkgs",
3622           "-il",
3623           "-type",
3624           "-descr",
3625           "x.proto"]),
3626    {ok, {[{msg_name_prefix,    "msg_prefix_"},
3627           {module_name_prefix, "mod_prefix_"},
3628           {msg_name_suffix,    "_msg_suffix"},
3629           {module_name_suffix, "_mod_suffix"},
3630           msg_name_to_lower,
3631           {module_name, "abc"}],
3632          ["x.proto"]}} =
3633        gpb_compile:parse_opts_and_args(
3634          ["-msgprefix", "msg_prefix_",
3635           "-modprefix", "mod_prefix_",
3636           "-msgsuffix", "_msg_suffix",
3637           "-modsuffix", "_mod_suffix",
3638           "-msgtolower",
3639           "-modname", "abc",
3640           "x.proto"]),
3641    {ok, {[defs_as_proplists,
3642           maps, msgs_as_maps, mapfields_as_maps, defs_as_maps],
3643          ["x.proto"]}} =
3644        gpb_compile:parse_opts_and_args(
3645          ["-pldefs",
3646           "-maps", "-msgs-as-maps", "-mapfields-as-maps", "-defs-as-maps",
3647           "x.proto"]),
3648    {ok, {[maps, {maps_oneof, flat}],
3649          ["x.proto"]}} =
3650        gpb_compile:parse_opts_and_args(
3651          ["-maps", "-maps_oneof", "flat",
3652           "x.proto"]),
3653    {ok, {[maps, {maps_key_type, binary}],
3654          ["x.proto"]}} =
3655        gpb_compile:parse_opts_and_args(
3656          ["-maps", "-maps-key-type", "binary",
3657           "x.proto"]),
3658    {ok, {[{erlc_compile_options, "debug_info, inline_list_funcs"}],
3659          ["x.proto"]}} =
3660        gpb_compile:parse_opts_and_args(
3661          ["-erlc_compile_options", "debug_info, inline_list_funcs",
3662           "x.proto"]),
3663    {ok, {[epb_compatibility, epb_functions],
3664          ["x.proto"]}} =
3665        gpb_compile:parse_opts_and_args(
3666          ["-epb", "-epb-functions",
3667           "x.proto"]),
3668    {ok, {[{target_erlang_version,18}],
3669          ["x.proto"]}} =
3670        gpb_compile:parse_opts_and_args(
3671          ["-for-version", "18",
3672           "x.proto"]),
3673    %% Help and version
3674    {ok, {[help, help,
3675           version, version],
3676          []}} =
3677        gpb_compile:parse_opts_and_args(
3678          ["-h", "--help",
3679           "-V", "--version"]).
3680
3681any_translation_options_test() ->
3682    {ok, {[{any_translate,
3683            [{encode, {me,fe,['$1']}},
3684             {decode, {md,fd,['$1']}}]}],
3685          ["x.proto"]}} =
3686        gpb_compile:parse_opts_and_args(
3687          ["-any_translate", "e=me:fe,d=md:fd",
3688           "x.proto"]),
3689    %% Merge
3690    {ok, {[{any_translate,
3691            [{encode, {me,fe,['$1']}},
3692             {decode, {md,fd,['$1']}},
3693             {merge,  {mm,fm,['$1','$2']}}]}],
3694          ["x.proto"]}} =
3695        gpb_compile:parse_opts_and_args(
3696          ["-any_translate", "e=me:fe,d=md:fd,m=mm:fm",
3697           "x.proto"]),
3698    %% Verify
3699    {ok, {[{any_translate,
3700            [{encode, {me,fe,['$1']}},
3701             {decode, {md,fd,['$1']}},
3702             {verify, {mv,fv,['$1']}}]}],
3703          ["x.proto"]}} =
3704        gpb_compile:parse_opts_and_args(
3705          ["-any_translate", "e=me:fe,d=md:fd,V=mv:fv",
3706           "x.proto"]),
3707    %% old style verify
3708    {ok, {[{any_translate,
3709            [{encode, {me,fe,['$1']}},
3710             {decode, {md,fd,['$1']}},
3711             {verify, {mv,fv,['$1','$errorf']}}]}],
3712          ["x.proto"]}} =
3713        gpb_compile:parse_opts_and_args(
3714          ["-any_translate", "e=me:fe,d=md:fd,v=mv:fv",
3715           "x.proto"]).
3716
3717type_translation_options_test() ->
3718    {ok, {[{translate_type, {{msg,m},
3719                             [{encode, {me,fe,['$1']}},
3720                              {decode, {md,fd,['$1']}},
3721                              {merge,  {mm,fm,['$1','$2']}},
3722                              {verify, {mv,fv,['$1']}}]}}],
3723          ["x.proto"]}} =
3724        gpb_compile:parse_opts_and_args(
3725          ["-translate_type", "type=msg:m,e=me:fe,d=md:fd,m=mm:fm,V=mv:fv",
3726           "x.proto"]),
3727    {ok, {[{translate_type, {{enum,ee}, [{encode, {me,fe,['$1']}} | _]}}],
3728          ["x.proto"]}} =
3729        gpb_compile:parse_opts_and_args(
3730          ["-translate_type", "type=enum:ee,e=me:fe,d=md:fd,m=mm:fm,V=mv:fv",
3731           "x.proto"]),
3732    {ok, {[{translate_type, {int32, [{encode, {me,fe,['$1']}} | _]}}],
3733          ["x.proto"]}} =
3734        gpb_compile:parse_opts_and_args(
3735          ["-translate_type", "type=int32,e=me:fe,d=md:fd,m=mm:fm,V=mv:fv",
3736           "x.proto"]),
3737    {ok, {[{translate_type, {{map,int32,{msg,m}},
3738                             [{encode, {me,fe,['$1']}} | _]}}],
3739          ["x.proto"]}} =
3740        gpb_compile:parse_opts_and_args(
3741          ["-translate_type", "type=map<int32,msg:m>,e=me:fe,d=md:fd,V=mv:fv",
3742           "x.proto"]).
3743
3744field_translation_options_test() ->
3745    {ok, {[{translate_field,
3746            {[m,f],
3747             [{encode, {me,fe,['$1']}},
3748              {decode, {md,fd,['$1']}},
3749              {merge,  {mm,fm,['$1','$2']}},
3750              {verify, {mv,fv,['$1']}},
3751              {decode_init_default, {mi,fi,[]}},
3752              {decode_repeated_add_elem, {ma,fa,['$1','$2']}},
3753              {decode_repeated_finalize, {mf,ff,['$1']}}]}}],
3754          ["x.proto"]}} =
3755        gpb_compile:parse_opts_and_args(
3756          ["-translate_field",
3757           "field=m.f,e=me:fe,d=md:fd,m=mm:fm,V=mv:fv,i=mi:fi,a=ma:fa,f=mf:ff",
3758           "x.proto"]),
3759    {ok, {[{translate_field, {[m,f,[]], [{encode, {me,fe,['$1']}} | _]}}],
3760          ["x.proto"]}} =
3761        gpb_compile:parse_opts_and_args(
3762          ["-translate_field", "field=m.f.[],e=me:fe,d=md:fd,m=mm:fm,V=mv:fv",
3763           "x.proto"]),
3764    {ok, {[{translate_field, {[m,c,a], [{encode, {me,fe,['$1']}} | _]}}],
3765          ["x.proto"]}} =
3766        gpb_compile:parse_opts_and_args(
3767          ["-translate_field", "field=m.c.a,e=me:fe,d=md:fd,m=mm:fm,V=mv:fv",
3768           "x.proto"]),
3769    {ok, {[{translate_field, {[m], [{encode, {me,fe,['$1']}} | _]}}],
3770          ["x.proto"]}} =
3771        gpb_compile:parse_opts_and_args(
3772          ["-translate_field", "field=m,e=me:fe,d=md:fd,m=mm:fm,V=mv:fv",
3773           "x.proto"]).
3774
3775no_type_specs_test() ->
3776    {ok, {[{type_specs, false}], ["x.proto"]}} =
3777        gpb_compile:parse_opts_and_args(["-no_type", "x.proto"]).
3778
3779dashes_and_underscores_are_interchangeable_in_options_test() ->
3780    {ok, {[{target_erlang_version,18}, {target_erlang_version,18}],
3781          ["x.proto"]}} =
3782        gpb_compile:parse_opts_and_args(["-for-version", "18", % norm
3783                                         "-for_version", "18", % also accepted
3784                                         "x.proto"]),
3785    {ok, {[{erlc_compile_options, "debug_info, inline_list_funcs"},
3786           {erlc_compile_options, "debug_info, inline_list_funcs"}],
3787          ["x.proto"]}} =
3788        gpb_compile:parse_opts_and_args(
3789          ["-erlc_compile_options", "debug_info, inline_list_funcs", % norm
3790           "-erlc-compile-options", "debug_info, inline_list_funcs", % ok too
3791           "x.proto"]).
3792
3793
3794%% --- auxiliaries -----------------
3795
3796%% vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv
3797%% begin functions that imitates the interface of the gpb module
3798%% needed by the common/shared tests included above from gpb_tests.erl
3799-ifdef(gpb_compile_common_tests).
3800decode_msg(Bin, MsgName, MsgDefs) ->
3801    M = compile_defs(MsgDefs),
3802    try M:decode_msg(Bin, MsgName)
3803    after unload_code(M)
3804    end.
3805
3806encode_msg(Msg, MsgDefs) ->
3807    M = compile_defs(MsgDefs),
3808    try M:encode_msg(Msg)
3809    after unload_code(M)
3810    end.
3811
3812merge_msgs(Msg1, Msg2, MsgDefs) ->
3813    M = compile_defs(MsgDefs),
3814    try M:merge_msgs(Msg1, Msg2)
3815    after unload_code(M)
3816    end.
3817
3818verify_msg(Msg, MsgDefs) ->
3819    M = compile_defs(MsgDefs),
3820    try M:verify_msg(Msg)
3821    after unload_code(M)
3822    end.
3823-endif. %% gpb_compile_common_tests
3824%% end of functions that imitates the interface of the gpb module
3825%% ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
3826
3827compile_defs(MsgDefs) ->
3828    compile_defs(MsgDefs, [{verify, always}]).
3829
3830compile_defs(MsgDefs, ExtraOpts) ->
3831    Mod = find_unused_module(),
3832    Opts = [binary | ExtraOpts],
3833    {ok, Mod, Code} = gpb_compile:proto_defs(Mod, MsgDefs, Opts),
3834    load_code(Mod, Code),
3835    Mod.
3836
3837compile_iolist(IoList) ->
3838    compile_iolist(IoList, []).
3839
3840compile_iolist(IoList, ExtraOpts) ->
3841    compile_iolist_maybe_errors_or_warnings(IoList, ExtraOpts, must_succeed).
3842
3843compile_iolist_maybe_errors_or_warnings(IoList, ExtraOpts, OnFail) ->
3844    Mod = find_unused_module(),
3845    Contents = iolist_to_binary(IoList),
3846    ModProto = f("~s.proto", [Mod]),
3847    ReadFile = fun(F) -> case filename:basename(F) of
3848                             ModProto -> {ok, Contents};
3849                             _ -> file:read_file(F)
3850                         end
3851               end,
3852    ReadFileInfo = fun(F) -> case filename:basename(F) of
3853                                 ModProto -> {ok, #file_info{access=read}};
3854                                 _ -> file:read_file_info(F)
3855                             end
3856                   end,
3857
3858    CompRes = gpb_compile:file(
3859                ModProto,
3860                [{file_op, [{read_file, ReadFile},
3861                            {read_file_info, ReadFileInfo},
3862                            {write_file, fun(_,_) -> ok end}]},
3863                 {i,"."},
3864                 binary, return_errors, return_warnings | ExtraOpts]),
3865    case OnFail of
3866        must_succeed ->
3867            %% Mod1 instead of Mod, since some options can change the
3868            %% module name (module_name_suffix, or epb_compatibility,
3869            %% for instance)
3870            {ok, Mod1, Code, []} = CompRes,
3871            load_code(Mod1, Code),
3872            Mod1;
3873        get_result ->
3874            case CompRes of
3875                {ok, Mod1, Code, Warnings} -> % Mod1 insead of Mod, see above
3876                    load_code(Mod1, Code),
3877                    {ok, Mod1, Warnings};
3878                {error, Reasons, Warnings} ->
3879                    {error, Reasons, Warnings}
3880            end
3881    end.
3882
3883compile_iolist_get_errors_or_warnings(IoList) ->
3884    compile_iolist_get_errors_or_warnings(IoList, []).
3885
3886compile_iolist_get_errors_or_warnings(IoList, ExtraOpts) ->
3887    compile_iolist_maybe_errors_or_warnings(IoList, ExtraOpts, get_result).
3888
3889compile_to_string(Proto, Opts) ->
3890    Self = self(),
3891    FileOps = [{write_file, fun(FName,Data) ->
3892                                    case filename:extension(FName) of
3893                                        ".erl" -> Self ! {data, Data};
3894                                        _ -> ok
3895                                    end,
3896                                    ok
3897                            end}],
3898    PS = lists:flatten(Proto),
3899    ok = gpb_compile:string(some_module, PS, [Opts | [{file_op, FileOps}]]),
3900    {data,Bin} = ?recv({data,_}),
3901    binary_to_list(Bin).
3902
3903compile_to_string_get_hrl(Proto, Opts) ->
3904    Self = self(),
3905    FileOps = [{write_file, fun(FName,Data) ->
3906                                    case filename:extension(FName) of
3907                                        ".hrl" -> Self ! {data, Data};
3908                                        _ -> ok
3909                                    end,
3910                                    ok
3911                            end}],
3912    PS = lists:flatten(Proto),
3913    ok = gpb_compile:string(some_module, PS, [Opts | [{file_op, FileOps}]]),
3914    {data,Bin} = ?recv({data,_}),
3915    case proplists:get_bool(strip_preprocessor_lines, Opts) of
3916        true ->
3917            %% Poor man's in-memory preprocessor
3918            binary_to_list(
3919              iolist_to_binary(
3920                [[Line,$\n] || Line <- binary:split(Bin, <<"\n">>, [global]),
3921                               not is_preprocessor_line(Line)]));
3922        false ->
3923            binary_to_list(Bin)
3924    end.
3925
3926is_preprocessor_line(<<"-ifndef(", _/binary>>) -> true; % ")"
3927is_preprocessor_line(<<"-ifdef(", _/binary>>)  -> true; % ")"
3928is_preprocessor_line(<<"-define(", _/binary>>) -> true; % ")"
3929is_preprocessor_line(<<"-endif.", _/binary>>)  -> true;
3930is_preprocessor_line(_) -> false.
3931
3932compile_erl_iolist(IoList) ->
3933    compile_erl_iolist(IoList, []).
3934compile_erl_iolist(IoList, ExtraOpts) ->
3935    Mod = find_unused_module(),
3936    Forms = iolist_to_forms([io_lib:format("-module(~p).\n",[Mod]), IoList]),
3937    ErlcOpts = [binary, return | ExtraOpts],
3938    {ok, Mod, Code, []} = compile:noenv_forms(Forms, ErlcOpts),
3939    load_code(Mod, Code),
3940    Mod.
3941
3942iolist_to_forms(IoList) ->
3943    {ok, Toks, _End} = erl_scan:string(
3944                         unicode:characters_to_list(
3945                           unicode:characters_to_binary(IoList))),
3946    iol_to_forms2(Toks, [], []).
3947
3948iol_to_forms2([{dot,_}=Dot | Rest], Curr, Acc) ->
3949    {ok, Form} = erl_parse:parse_form(lists:reverse([Dot | Curr])),
3950    iol_to_forms2(Rest, [], [Form | Acc]);
3951iol_to_forms2([Tok | Rest], Curr, Acc) ->
3952    iol_to_forms2(Rest, [Tok | Curr], Acc);
3953iol_to_forms2([], [], Acc) ->
3954    lists:reverse(Acc).
3955
3956
3957
3958load_code(Mod, Code) ->
3959    unload_code(Mod),
3960    {module, Mod} = code:load_binary(Mod, "<nofile>", Code),
3961    ok.
3962
3963unload_code(Mod) ->
3964    code:purge(Mod),
3965    code:delete(Mod),
3966    code:purge(Mod),
3967    code:delete(Mod),
3968    ok.
3969
3970find_unused_module() -> find_unused_module(1).
3971
3972find_unused_module(N) ->
3973    find_unused_module("", N).
3974
3975find_unused_module(Prefix, N) ->
3976    ModNameCandidate = list_to_atom(f("~s~s-tmp-~w", [Prefix, ?MODULE, N])),
3977    case code:is_loaded(ModNameCandidate) of
3978        false    -> ModNameCandidate;
3979        {file,_} -> find_unused_module(Prefix, N+1)
3980    end.
3981
3982id(X) -> X.
3983
3984f(Fmt, Args) -> lists:flatten(io_lib:format(Fmt, Args)).
3985
3986-ifndef(NO_HAVE_RAND).
3987%% Erlang 19 or later
3988rand_uniform(Limit) -> rand:uniform(Limit).
3989rand_seed() -> _ = rand:uniform().
3990-else.
3991%% Erlang 18 or earlier
3992rand_uniform(Limit) -> random:uniform(Limit).
3993rand_seed() ->
3994    {A, B, C} = os:timestamp(),
3995    random:seed(erlang:phash2(A+B+C), erlang:phash2(B+C), erlang:phash2(A+C)).
3996-endif. % NO_HAVE_RAND
3997
3998-ifndef(NO_HAVE_ERL20_STR_FUNCTIONS).
3999
4000string_trim(Str) ->
4001    string:trim(Str).
4002
4003-else.  % NO_HAVE_ERL20_STR_FUNCTIONS
4004
4005string_trim(Str) ->
4006    string:strip(Str).
4007
4008-endif. % NO_HAVE_ERL20_STR_FUNCTIONS
4009