1%%% Copyright (C) 2017  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%%% @doc Transformation of module names and names in parsed
21%%% definitions, such as prefixing and lowercasing of message names etc.
22
23-module(gpb_names).
24
25-export([file_name_to_module_name/2]).
26-export([rename_module/2]).
27-export([rename_defs/2]).
28
29-export([format_error/1]).
30
31-include("../include/gpb.hrl").
32
33-define(f(Fmt, Args), io_lib:format(Fmt, Args)).
34
35%% @doc Given a file name of a proto file, turn it into a module name,
36%% possibly with name transformations, such as prefix or suffix
37%% according to options.
38-spec file_name_to_module_name(string(), gpb_compile:opts()) -> atom().
39file_name_to_module_name(ProtoFileName, Opts) ->
40    Ext = filename:extension(ProtoFileName),
41    BaseNameNoExt = filename:basename(ProtoFileName, Ext),
42    rename_module(BaseNameNoExt, Opts).
43
44%% @doc Given a module name, rename it according to opts, for example
45%% by prefixing it.
46-spec rename_module(atom() | string(), gpb_compile:opts()) -> atom().
47rename_module(Mod, Opts) when is_atom(Mod) ->
48    rename_module(atom_to_list(Mod), Opts);
49rename_module(Mod, Opts) when is_list(Mod) ->
50    list_to_atom(possibly_suffix_mod(
51                   possibly_prefix_mod(
52                     mod_name_from_opts_or_else_filename(Mod, Opts),
53                     Opts),
54                   Opts)).
55
56mod_name_from_opts_or_else_filename(FileBaseName, Opts) ->
57    proplists:get_value(module_name, Opts, FileBaseName).
58
59possibly_prefix_mod(BaseNameNoExt, Opts) ->
60    case proplists:get_value(module_name_prefix, Opts) of
61        undefined ->
62            BaseNameNoExt;
63        Prefix ->
64            lists:concat([Prefix, BaseNameNoExt])
65    end.
66
67possibly_suffix_mod(BaseNameNoExt, Opts) ->
68    case proplists:get_value(module_name_suffix, Opts) of
69        undefined ->
70            BaseNameNoExt;
71        Suffix ->
72            lists:concat([BaseNameNoExt, Suffix])
73    end.
74
75%% @doc Rename definitions according to options, for example
76%% lowercasing message names.
77-spec rename_defs(gpb_parse:defs(), gpb_compile:opts()) ->
78                         {ok, gpb_parse:defs()} |
79                         {error, Reason::term()}.
80rename_defs(Defs, Opts) ->
81    Opts1 = convert_legacy_opts(Opts),
82    case mk_rename_operations(Opts1) of
83        [] ->
84            {ok, Defs};
85        RenameOpFs ->
86            case mk_renamer(RenameOpFs, Defs, Opts1) of
87                {ok, RF} ->
88                    {ok, do_rename(RF, Defs)};
89                {error, Reason} ->
90                    {error, {rename_defs, Reason}}
91            end
92    end.
93
94format_error({error, {rename_defs, Reason}}) -> fmt_err(Reason);
95format_error({rename_defs, Reason}) -> fmt_err(Reason);
96format_error(Reason) -> fmt_err(Reason).
97
98%% Note: do NOT include trailing newline (\n or ~n)
99fmt_err({duplicates, Dups}) ->
100    ["Renaming to same name:\n",
101     gpb_lib:nl_join(
102       lists:append(
103         [[case K of
104               {Service,Rpc} -> ?f("  ~s/~s -> ~s", [Service, Rpc, V]);
105               K             -> ?f("  ~s -> ~s", [K, V])
106           end
107           || K <- Ks]
108          || {Ks, V} <- Dups]))];
109fmt_err(X) ->
110    ?f("Unexpected error ~p", [X]).
111
112%% -- Converting legacy opts ------------------
113
114convert_legacy_opts([Opt | Opts]) ->
115    case Opt of
116        {msg_name_prefix, Prefix} ->
117            l_msg_prefix_opts(Prefix) ++ convert_legacy_opts(Opts);
118        {msg_name_suffix, Suffix} ->
119            l_msg_suffix_opts(Suffix) ++ convert_legacy_opts(Opts);
120        msg_name_to_snake_case ->
121            l_msg_snake_case_opts() ++ convert_legacy_opts(Opts);
122        {msg_name_to_snake_case=OptKey, Bool} ->
123            if Bool -> l_msg_snake_case_opts() ++ convert_legacy_opts(Opts);
124               true -> convert_legacy_opts(drop_opt(OptKey, Opts))
125            end;
126        msg_name_to_lower ->
127            l_msg_lowercase_opts() ++ convert_legacy_opts(Opts);
128        {msg_name_to_lower=OptKey, Bool} ->
129            if Bool -> l_msg_lowercase_opts() ++ convert_legacy_opts(Opts);
130               true -> convert_legacy_opts(drop_opt(OptKey, Opts))
131            end;
132        _ ->
133            [Opt | convert_legacy_opts(Opts)]
134    end;
135convert_legacy_opts([]) ->
136    [].
137
138
139drop_opt(Opt, [Opt | Rest])      -> drop_opt(Opt, Rest);
140drop_opt(Opt, [{Opt, _} | Rest]) -> drop_opt(Opt, Rest);
141drop_opt(Opt, [Other | Rest])    -> [Other | drop_opt(Opt, Rest)];
142drop_opt(_Opt, [])               -> [].
143
144l_msg_prefix_opts({by_proto,_PrefixList}=ByProto) ->
145    [{rename, {msg_fqname, {prefix, ByProto}}}];
146l_msg_prefix_opts(Prefix) ->
147    l_msg_only_opts({prefix, Prefix}).
148
149l_msg_suffix_opts(Suffix) ->
150    l_msg_only_opts({suffix, Suffix}).
151
152l_msg_snake_case_opts() ->
153    l_msg_and_service_and_rpc_opts(snake_case).
154
155l_msg_lowercase_opts() ->
156    l_msg_and_service_and_rpc_opts(lowercase).
157
158l_msg_only_opts(Value) ->
159    [{rename, {pkg_name, Value}},
160     {rename, {msg_fqname, Value}},
161     {rename, {group_fqname, Value}}].
162
163l_msg_and_service_and_rpc_opts(Value) ->
164    [{rename, {pkg_name, Value}},
165     {rename, {service_fqname, Value}},
166     {rename, {rpc_name, Value}},
167     {rename, {msg_fqname, Value}},
168     {rename, {group_fqname, Value}}].
169
170%% -- Renaming opts -> renaming functions ------------------
171
172mk_rename_operations(Opts) ->
173    [{What, mk_rename_op(What, How)} || {rename, {What, How}} <- Opts].
174
175mk_rename_op(pkg_name, How) -> mk_pkg_rename_op(How);
176mk_rename_op(msg_fqname, How) -> mk_msg_rename_op(How);
177mk_rename_op(msg_name, How) -> mk_msg_rename_op(How);
178mk_rename_op(group_fqname, How) -> mk_msg_rename_op(How);
179mk_rename_op(group_name, How) -> mk_group_rename_op(How);
180mk_rename_op(service_fqname, How) -> mk_service_rename_op(How);
181mk_rename_op(service_name, How) -> mk_service_rename_op(How);
182mk_rename_op(rpc_name, How) -> mk_rpc_rename_op(How).
183
184mk_pkg_rename_op(PrimOp) ->
185    fun(Name, _Proto) -> do_prim_op(PrimOp, Name) end.
186
187mk_msg_rename_op({prefix, {by_proto, PrefixList}}) ->
188    fun(Name, Proto) ->
189            ProtoName = list_to_atom(Proto),
190            Prefix = proplists:get_value(ProtoName, PrefixList, ""),
191            list_to_atom(lists:concat([Prefix, Name]))
192    end;
193mk_msg_rename_op(PrimOp) ->
194    fun(Name, _Proto) -> do_prim_op(PrimOp, Name) end.
195
196mk_group_rename_op(PrimOp) ->
197    fun(Name, _Proto) -> do_prim_op(PrimOp, Name) end.
198
199mk_service_rename_op(PrimOp) ->
200    fun(Name, _Proto) -> do_prim_op(PrimOp, Name) end.
201
202mk_rpc_rename_op(PrimOp) ->
203    fun(Name, _Proto) -> do_prim_op(PrimOp, Name) end.
204
205do_prim_op({prefix, Prefix}, Name) ->
206    list_to_atom(lists:concat([Prefix, Name]));
207do_prim_op({suffix, Suffix}, Name) ->
208    list_to_atom(lists:concat([Name, Suffix]));
209do_prim_op(lowercase, Name) ->
210    list_to_atom(gpb_lib:lowercase(atom_to_list(Name)));
211do_prim_op(snake_case, Name) ->
212    list_to_atom(gpb_lib:snake_case(atom_to_list(Name)));
213do_prim_op(dots_to_underscores, Name) ->
214    list_to_atom(do_dot_uscore(atom_to_list(Name)));
215do_prim_op(base_name, Name) ->
216    list_to_atom(lists:last(gpb_lib:string_lexemes(atom_to_list(Name), "."))).
217
218
219do_dot_uscore("."++Rest)  -> "_" ++ do_dot_uscore(Rest);
220do_dot_uscore([C | Rest]) -> [C | do_dot_uscore(Rest)];
221do_dot_uscore("")         -> "".
222
223%% -- Compute old-name -> new name mappings -----------
224%%
225%% This stage is chiefly to call the RenameOp function---which could
226%% possibly be a user-supplied function---only once or twice for every
227%% msg, service or rpc name, but still be able to map all occurrences
228%% of such names, which may be many times more (eg for messages: once
229%% for the message name, again for each field of that type.)
230%%
231
232mk_renamer(RenameOps, Defs, Opts) ->
233    PkgByProto = calc_package_by_proto(Defs),
234    PkgRenamings = pkg_renamings(PkgByProto, RenameOps),
235    MsgRenamings = msg_renamings(PkgByProto, PkgRenamings, Defs, RenameOps),
236    GroupRenamings = group_renamings(PkgByProto, PkgRenamings, Defs,
237                                     RenameOps),
238    ServiceRenamings = service_renamings(PkgByProto, PkgRenamings, Defs,
239                                         RenameOps),
240    RpcRenamings = rpc_renamings(Defs, RenameOps),
241    MostRenamings = [PkgRenamings, MsgRenamings, GroupRenamings,
242                    ServiceRenamings],
243    UsePackages = proplists:get_bool(use_packages, Opts),
244    case check_no_dups(MostRenamings, RpcRenamings) of
245        ok ->
246            RF = fun(package, Name) ->
247                         if UsePackages ->
248                                 dict_fetch(Name, PkgRenamings);
249                            not UsePackages ->
250                                 %% No pkg_containment items present in Defs
251                                 %% when the use_packages option is not set.
252                                 Name
253                         end;
254                    (msg, Name) ->
255                         dict_fetch(Name, MsgRenamings);
256                    (group, Name) ->
257                         dict_fetch(Name, GroupRenamings);
258                    (service, Name) ->
259                         dict_fetch(Name, ServiceRenamings);
260                    ({rpc, ServiceName}, RpcName) ->
261                         dict_fetch({ServiceName, RpcName}, RpcRenamings)
262                 end,
263            {ok, RF};
264        {error, Reason}  ->
265            {error, Reason}
266    end.
267
268calc_package_by_proto(Defs) ->
269    dict:from_list(
270      [{Proto, PkgName}
271       || {{pkg_containment, Proto}, PkgName} <- Defs]).
272
273pkg_renamings(PkgByProto, RenameOps) ->
274    dict:from_list(
275      lists:map(
276        fun({Proto, Pkg}) ->
277                Pkg1 = run_ops(pkg_name, Pkg, Proto, RenameOps),
278                {Pkg, Pkg1}
279        end,
280        dict:to_list(PkgByProto))).
281
282msg_renamings(PkgByProto, PkgRenamings, Defs, RenameOps) ->
283    dict:from_list(
284      lists:append(
285        [begin
286             Pkg = dict_fetch_or_default(Proto, PkgByProto, ''),
287             [begin
288                  Name = drop_prefix(Pkg, FqName),
289                  Name1 = run_ops(msg_name, Name, Proto, RenameOps),
290                  Pkg1 = dict_fetch_or_default(Pkg, PkgRenamings, ''),
291                  FqName1 = prefix(Pkg1, Name1),
292                  FqName2 = run_ops(msg_fqname, FqName1, Proto, RenameOps),
293                  {FqName, FqName2}
294              end
295              || FqName <- MsgNames]
296         end
297         || {{msg_containment, Proto}, MsgNames} <- Defs])).
298
299group_renamings(PkgByProto, PkgRenamings, Defs, RenameOps) ->
300    ProtoByMsg = dict:from_list(
301                   lists:append(
302                     [[{MsgName, Proto} || MsgName <- MsgNames]
303                      || {{msg_containment, Proto}, MsgNames} <- Defs])),
304    dict:from_list(
305      [begin
306           MsgName = group_name_to_msg_name(GroupFqName),
307           Proto = dict:fetch(MsgName, ProtoByMsg),
308           Pkg = dict_fetch_or_default(Proto, PkgByProto, ''),
309           Name = drop_prefix(Pkg, GroupFqName),
310           Name1 = run_ops(group_name, Name, Proto, RenameOps),
311           Pkg1 = dict_fetch_or_default(Pkg, PkgRenamings, ''),
312           FqName1 = prefix(Pkg1, Name1),
313           FqName2 = run_ops(group_fqname, FqName1, Proto, RenameOps),
314           {GroupFqName, FqName2}
315       end
316       || {{group,GroupFqName}, _Fields} <- Defs]).
317
318group_name_to_msg_name(GName) ->
319    Components = gpb_lib:string_lexemes(atom_to_list(GName), "."),
320    [_G | ButLast] = lists:reverse(Components),
321    list_to_atom(gpb_lib:dot_join(lists:reverse(ButLast))).
322
323service_renamings(PkgByProto, PkgRenamings, Defs, RenameOps) ->
324    dict:from_list(
325      lists:append(
326        [begin
327             Pkg = dict_fetch_or_default(Proto, PkgByProto, ''),
328             [begin
329                  Name = drop_prefix(Pkg, FqName),
330                  Name1 = run_ops(service_name, Name, Proto, RenameOps),
331                  Pkg1 = dict_fetch_or_default(Pkg, PkgRenamings, ''),
332                  FqName1 = prefix(Pkg1, Name1),
333                  FqName2 = run_ops(service_fqname, FqName1, Proto, RenameOps),
334                  {FqName, FqName2}
335              end
336              || FqName <- ServiceNames]
337         end
338         || {{service_containment, Proto}, ServiceNames} <- Defs])).
339
340rpc_renamings(Defs, RenameOps) ->
341    dict:from_list(
342      lists:append(
343        [begin
344             [begin
345                  RpcName1 = run_ops(rpc_name, RpcName, Proto, RenameOps),
346                  {{ServiceName, RpcName}, RpcName1}
347              end
348              || {ServiceName, RpcName} <- Rpcs]
349         end
350         || {{rpc_containment, Proto}, Rpcs} <- Defs])).
351
352run_ops(What, Name0, Proto, RenameOps) ->
353    lists:foldl(fun(F, Name) -> F(Name, Proto) end,
354                Name0,
355                [F || {W, F} <- RenameOps,
356                      W =:= What]).
357
358drop_prefix('', Value) when is_atom(Value) ->
359    Value; % fast path (no package)
360drop_prefix(Prefix, Value) when is_atom(Prefix), is_atom(Value) ->
361    P = atom_to_list(Prefix),
362    V = atom_to_list(Value),
363    case lists:sublist(V, length(P) + 1, length(V) - length(P)) of
364        "." ++ Rest -> list_to_atom(Rest);
365        Rest        -> list_to_atom(Rest)
366    end.
367
368prefix('', V) ->
369    V; % fast path (no package)
370prefix(P, '') ->
371    P; % fast path (no remainder)
372prefix(P, V) ->
373    list_to_atom(lists:concat([P, ".", V])).
374
375dict_fetch_or_default(Key, Dict, Default) ->
376    case dict:find(Key, Dict) of
377        {ok, Value} ->
378            Value;
379        error ->
380            Default
381    end.
382
383dict_fetch(Key, Dict) ->
384    case dict:find(Key, Dict) of
385        {ok, Value} ->
386            Value;
387        error ->
388            error({not_found_in_dict, Key, dict:to_list(Dict)})
389    end.
390
391check_no_dups(Renamings, RpcRenamings) ->
392    Errs1 = lists:foldl(fun renaming_dups/2, [], Renamings),
393    Errs2 = renaming_rpc_dups(RpcRenamings, Errs1),
394    if Errs2 == [] ->
395            ok;
396       true ->
397            {error, {duplicates, Errs2}}
398    end.
399
400renaming_dups(Dict, Errs) ->
401    RDict = dict:fold(fun(K, V, RDict) -> dict:append(V, K, RDict) end,
402                      dict:new(),
403                      Dict),
404    DupsDict = dict:filter(fun(_V, [_K1,_K2|_]) -> true; % >= 2 entries
405                              (_V, [_]) -> false
406                           end,
407                           RDict),
408    [{Keys, V} || {V, Keys} <- dict:to_list(DupsDict)] ++ Errs.
409
410%% check for dups on a per service basis
411renaming_rpc_dups(Dict, Errs) ->
412    %% split into dict of dicts, one per service (service name is used as key)
413    Ds = dict:fold(
414           fun({Service,_Rpc}=Entry, NewName, D) ->
415                   ED = case dict:find(Service, D) of
416                            error    -> dict:store(Entry, NewName, dict:new());
417                            {ok,ED0} -> dict:store(Entry, NewName, ED0)
418                        end,
419                   dict:store(Service, ED, D)
420           end,
421           dict:new(),
422           Dict),
423    lists:foldl(fun renaming_dups/2,
424                Errs,
425                [D || {_Service,D} <- dict:to_list(Ds)]).
426
427
428%% -- Traversing defs, doing rename ----------
429
430do_rename(RF, Defs) ->
431    lists:map(
432      fun({{msg,Name}, Fields}) ->
433              {{msg, RF(msg, Name)}, rename_fields(RF, Fields, Defs)};
434         ({{group,Name}, Fields}) ->
435              {{group, RF(group, Name)}, rename_fields(RF, Fields, Defs)};
436         ({{extensions,Name}, Exts}) ->
437              {{extensions, RF(msg, Name)}, Exts};
438         ({{service,Name}, Rpcs}) ->
439              {{service, RF(service, Name)}, rename_rpcs(RF, Name, Rpcs)};
440         ({package,Name}) ->
441              {package, RF(package, Name)};
442         ({proto3_msgs,Names}) ->
443              {proto3_msgs, [RF(msg, Name) || Name <- Names]};
444         ({{msg_containment,Proto}, MsgNames}) ->
445              {{msg_containment,Proto}, [RF(msg, Name) || Name <- MsgNames]};
446         ({{pkg_containment,Proto}, PkgName}) ->
447              {{pkg_containment,Proto}, RF(package, PkgName)};
448         ({{service_containment,Proto}, ServiceNames}) ->
449              {{service_containment,Proto},
450               [RF(service, Name) || Name <- ServiceNames]};
451         ({{rpc_containment,Proto}, Rpcs}) ->
452              {{rpc_containment,Proto},
453               [{RF(service, SvcName), RF({rpc, SvcName}, RpcName)}
454                || {SvcName, RpcName} <- Rpcs]};
455         (OtherElem) ->
456              OtherElem
457      end,
458      Defs).
459
460rename_fields(RF, Fields, Defs) ->
461    lists:map(
462      fun(#?gpb_field{type={msg,MsgName}}=F) ->
463              F#?gpb_field{type={msg, RF(msg, MsgName)}};
464         (#?gpb_field{type={map,KeyType,{msg,MsgName}}}=F) ->
465              F#?gpb_field{type={map,KeyType,{msg, RF(msg, MsgName)}}};
466         (#?gpb_field{type={group,MsgName}}=F) ->
467              F#?gpb_field{type={group, RF(group, MsgName)}};
468         (#gpb_oneof{fields=Fs}=F) ->
469              F#gpb_oneof{fields=rename_fields(RF, Fs, Defs)};
470         (#?gpb_field{}=F) ->
471              F
472      end,
473      Fields).
474
475rename_rpcs(RF, ServiceName, RPCs) ->
476    lists:map(
477      fun(#?gpb_rpc{name=RpcName, input=Arg, output=Return}=R) ->
478              R#?gpb_rpc{name=RF({rpc, ServiceName}, RpcName),
479                         input=RF(msg, Arg),
480                         output=RF(msg, Return)}
481      end,
482      RPCs).
483