./ct_report/coverage/mongoose_graphql_commands.COVER.html

1 %% @doc Management and execution of administration commands with GraphQL API
2
3 -module(mongoose_graphql_commands).
4
5 %% API
6 -export([start/0, stop/0, process/1]).
7
8 %% Internal API
9 -export([wrap_type/2]).
10
11 %% Only for tests
12 -export([build_specs/1, get_specs/0]).
13
14 -ignore_xref([build_specs/1, get_specs/0]).
15
16 % Needed to get the 'agent' vCard Fields inside a vCard
17 -define(MAX_TYPE_RECURSION_DEPTH, 2).
18
19 % Needed to handle e.g. [String!]!, which has 3 wrapper types: NON_NULL, LIST, NON_NULL
20 -define(MAX_INTROSPECTION_DEPTH, 3).
21
22 -type context() :: #{args := [string()],
23 category => category(),
24 commands => command_map(),
25 command => command(),
26 args_spec => [arg_spec()],
27 doc => doc(),
28 vars => json_map(),
29 reason => atom() | tuple(),
30 result => result(),
31 status => executed | error | usage}.
32 -type result() :: {ok, #{atom() => graphql:json()}} | {error, any()}.
33 -type specs() :: #{category() => category_spec()}.
34 -type category() :: binary().
35 -type category_spec() :: #{desc := binary(), commands := command_map()}.
36 -type command_map() :: #{command() => command_spec()}.
37 -type command() :: binary().
38 -type command_spec() :: #{desc := binary(),
39 op_type := op_type(),
40 args := [arg_spec()],
41 fields := [field_spec()],
42 doc := doc()}.
43 -type arg_spec() :: #{name := binary(), type := binary(), kind := binary(), wrap := [list | required]}.
44 -type field_spec() :: #{name | on := binary(), fields => [field_spec()]}.
45 -type op_type() :: binary().
46 -type doc() :: binary().
47 -type ep() :: graphql:endpoint_context().
48 -type json_map() :: #{binary() => graphql:json()}.
49
50 -export_type([category/0, command/0, command_map/0, arg_spec/0, context/0]).
51
52 %% API
53
54 -spec start() -> ok.
55 start() ->
56 101 Specs = build_specs(admin),
57 101 persistent_term:put(?MODULE, Specs).
58
59 -spec stop() -> ok.
60 stop() ->
61 101 persistent_term:erase(?MODULE),
62 101 ok.
63
64 %% The returned context has 'status' with the following values:
65 %% - 'executed' means that a GraphQL command was called, and 'result' contains the returned value
66 %% - 'error' means that the arguments were incorrect, and 'reason' contains more information
67 %% - 'usage' means that help needs to be displayed
68 -spec process([string()]) -> context().
69 process(Args) ->
70 492 lists:foldl(fun(_, #{status := _} = Ctx) -> Ctx;
71 2426 (StepF, Ctx) -> StepF(Ctx)
72 end, #{args => Args}, steps()).
73
74 %% Internal API
75
76 -spec build_specs(atom()) -> specs().
77 build_specs(EpName) ->
78 149 Ep = mongoose_graphql:get_endpoint(EpName),
79 149 CatSpecs = get_category_specs(Ep),
80 149 lists:foldl(fun({Category, CategorySpec}, Acc) ->
81 4785 insert_category(Category, CategorySpec, Acc)
82 end, #{}, CatSpecs).
83
84 -spec get_specs() -> specs().
85 get_specs() ->
86 494 persistent_term:get(?MODULE).
87
88 %% Internals
89
90 steps() ->
91 492 [fun find_category/1, fun find_command/1, fun parse_args/1, fun check_args/1, fun execute/1].
92
93 -spec find_category(context()) -> context().
94 find_category(CtxIn = #{args := [CategoryStr | Args]}) ->
95 491 Category = list_to_binary(CategoryStr),
96 491 Ctx = CtxIn#{category => Category, args => Args},
97 491 case get_specs() of
98 #{Category := #{commands := Commands}} ->
99 489 Ctx#{commands => Commands};
100 #{} ->
101 2 Ctx#{status => error, reason => unknown_category}
102 end;
103 find_category(Ctx = #{args := []}) ->
104 1 Ctx#{status => error, reason => no_args}.
105
106 -spec find_command(context()) -> context().
107 find_command(CtxIn = #{args := [CommandStr | Args]}) ->
108 488 Command = list_to_binary(CommandStr),
109 488 Ctx = #{commands := Commands} = CtxIn#{command => Command, args => Args},
110 488 case Commands of
111 #{Command := CommandSpec} ->
112 486 #{doc := Doc, args := ArgSpec} = CommandSpec,
113 486 Ctx#{doc => Doc, args_spec => ArgSpec};
114 #{} ->
115 2 Ctx#{status => error, reason => unknown_command}
116 end;
117 find_command(Ctx) ->
118 1 Ctx#{status => usage}.
119
120 -spec parse_args(context()) -> context().
121 parse_args(Ctx = #{args := ["--help"]}) ->
122 1 Ctx#{status => usage};
123 parse_args(Ctx) ->
124 485 parse_args_loop(Ctx#{vars => #{}}).
125
126 parse_args_loop(Ctx = #{vars := Vars,
127 args_spec := ArgsSpec,
128 args := ["--" ++ ArgNameStr, ArgValueStr | Rest]}) ->
129 982 ArgName = list_to_binary(ArgNameStr),
130 982 case lists:filter(fun(#{name := Name}) -> Name =:= ArgName end, ArgsSpec) of
131 [] ->
132 1 Ctx#{status => error, reason => {unknown_arg, ArgName}};
133 [ArgSpec] ->
134 981 ArgValue = list_to_binary(ArgValueStr),
135 981 try parse_arg(ArgValue, ArgSpec) of
136 ParsedValue ->
137 980 NewVars = Vars#{ArgName => ParsedValue},
138 980 parse_args_loop(Ctx#{vars := NewVars, args := Rest})
139 catch _:_ ->
140 1 Ctx#{status => error, reason => {invalid_arg_value, ArgName, ArgValue}}
141 end
142 end;
143 parse_args_loop(Ctx = #{args := []}) ->
144 481 Ctx;
145 parse_args_loop(Ctx) ->
146 2 Ctx#{status => error, reason => invalid_args}.
147
148 -spec parse_arg(binary(), arg_spec()) -> jiffy:json_value().
149 parse_arg(Value, ArgSpec = #{type := Type}) ->
150 981 case is_json_arg(ArgSpec) of
151 true ->
152 79 jiffy:decode(Value, [return_maps]);
153 false ->
154 902 convert_input_type(Type, Value)
155 end.
156
157 %% Used input types that are not parsed from binaries should be handled here
158 convert_input_type(Type, Value) when Type =:= <<"Int">>;
159 Type =:= <<"PosInt">>;
160 44 Type =:= <<"NonNegInt">> -> binary_to_integer(Value);
161 858 convert_input_type(_, Value) -> Value.
162
163 %% Complex argument values should be provided in JSON
164 -spec is_json_arg(arg_spec()) -> boolean().
165 26 is_json_arg(#{kind := <<"INPUT_OBJECT">>}) -> true;
166 is_json_arg(#{kind := Kind, wrap := Wrap}) when Kind =:= <<"SCALAR">>;
167 Kind =:= <<"ENUM">> ->
168 955 lists:member(list, Wrap).
169
170 -spec check_args(context()) -> context().
171 check_args(Ctx = #{args_spec := ArgsSpec, vars := Vars}) ->
172 481 MissingArgs = [Name || #{name := Name, wrap := [required|_]} <- ArgsSpec,
173 806 not maps:is_key(Name, Vars)],
174 481 case MissingArgs of
175 478 [] -> Ctx;
176 3 _ -> Ctx#{status => error, reason => {missing_args, MissingArgs}}
177 end.
178
179 -spec execute(context()) -> context().
180 execute(#{doc := Doc, vars := Vars} = Ctx) ->
181 478 Ctx#{status => executed, result => execute(mongoose_graphql:get_endpoint(admin), Doc, Vars)}.
182
183 -spec get_category_specs(ep()) -> [{category(), category_spec()}].
184 get_category_specs(Ep) ->
185 149 lists:flatmap(fun(OpType) -> get_category_specs(Ep, OpType) end, op_types()).
186
187 get_category_specs(Ep, OpType) ->
188 447 OpTypeName = <<OpType/binary, "Type">>,
189 447 Doc = iolist_to_binary(["{ __schema { ", OpTypeName, " ", category_spec_query(), " } }"]),
190 447 {ok, #{data := #{<<"__schema">> := Schema}}} = mongoose_graphql:execute(Ep, undefined, Doc),
191 447 #{OpTypeName := #{<<"fields">> := Categories}} = Schema,
192 447 get_category_specs(Ep, OpType, Categories).
193
194 op_types() ->
195 149 [<<"query">>, <<"mutation">>, <<"subscription">>].
196
197 -spec get_category_specs(ep(), op_type(), [json_map()]) -> [{category(), category_spec()}].
198 get_category_specs(Ep, OpType, Categories) ->
199 447 [get_category_spec(Ep, OpType, Category) || Category <- Categories, is_category(Category)].
200
201 is_category(#{<<"name">> := <<"checkAuth">>}) ->
202 149 false;
203 is_category(#{}) ->
204 4785 true.
205
206 -spec get_category_spec(ep(), op_type(), json_map()) -> {category(), category_spec()}.
207 get_category_spec(Ep, OpType, #{<<"name">> := Category, <<"description">> := Desc,
208 <<"type">> := #{<<"name">> := CategoryType}}) ->
209 4785 Doc = iolist_to_binary(
210 ["query ($type: String!) { __type(name: $type) "
211 "{name fields {name description args {name type ", arg_type_query(), "} type ",
212 field_type_query(), "}}}"]),
213 4785 Vars = #{<<"type">> => CategoryType},
214 4785 {ok, #{data := #{<<"__type">> := #{<<"fields">> := Commands}}}} = execute(Ep, Doc, Vars),
215 4785 CommandSpecs = [get_command_spec(Ep, Category, OpType, Command) || Command <- Commands],
216 4785 {Category, #{desc => Desc, commands => maps:from_list(CommandSpecs)}}.
217
218 -spec get_command_spec(ep(), category(), op_type(), json_map()) -> {command(), command_spec()}.
219 get_command_spec(Ep, Category, OpType,
220 #{<<"name">> := Name, <<"args">> := Args, <<"type">> := TypeMap} = Map) ->
221 16624 Spec = #{op_type => OpType, args => get_args(Args), fields => get_fields(Ep, TypeMap, [])},
222 16624 Doc = prepare_doc(Category, Name, Spec),
223 16624 {Name, add_description(Spec#{doc => Doc}, Map)}.
224
225 add_description(Spec, #{<<"description">> := Desc}) ->
226 16624 Spec#{desc => Desc};
227 add_description(Spec, #{}) ->
228
:-(
Spec.
229
230 -spec get_args([json_map()]) -> [arg_spec()].
231 get_args(Args) ->
232 16624 lists:map(fun get_arg_info/1, Args).
233
234 -spec get_arg_info(json_map()) -> arg_spec().
235 get_arg_info(#{<<"name">> := ArgName, <<"type">> := Arg}) ->
236 31300 (get_arg_type(Arg, []))#{name => ArgName}.
237
238 get_arg_type(#{<<"kind">> := <<"NON_NULL">>, <<"ofType">> := TypeMap}, Wrap) ->
239 25174 get_arg_type(TypeMap, [required | Wrap]);
240 get_arg_type(#{<<"kind">> := <<"LIST">>, <<"ofType">> := TypeMap}, Wrap) ->
241 2136 get_arg_type(TypeMap, [list | Wrap]);
242 get_arg_type(#{<<"name">> := Type, <<"kind">> := Kind}, Wrap) when Kind =:= <<"SCALAR">>;
243 Kind =:= <<"ENUM">>;
244 Kind =:= <<"INPUT_OBJECT">> ->
245 31300 #{type => Type, kind => Kind, wrap => lists:reverse(Wrap)}.
246
247 -spec get_fields(ep(), json_map(), [binary()]) -> [field_spec()].
248 get_fields(_Ep, #{<<"kind">> := Kind}, _Path)
249 when Kind =:= <<"SCALAR">>;
250 84833 Kind =:= <<"ENUM">> -> [];
251 get_fields(Ep, #{<<"kind">> := <<"UNION">>, <<"possibleTypes">> := TypeMaps}, Path) ->
252 2660 [get_union_type(Ep, TypeMap, Path) || TypeMap <- TypeMaps];
253 get_fields(Ep, #{<<"kind">> := Kind, <<"ofType">> := Type}, Path)
254 when Kind =:= <<"NON_NULL">>;
255 Kind =:= <<"LIST">> ->
256 52225 get_fields(Ep, Type, Path);
257 get_fields(Ep, #{<<"kind">> := <<"OBJECT">>, <<"name">> := Type}, Path) ->
258 23654 case length([T || T <- Path, T =:= Type]) >= ?MAX_TYPE_RECURSION_DEPTH of
259 true ->
260 298 [#{name => <<"__typename">>}]; % inform about the type of the trimmed subtree
261 false ->
262 23356 Fields = get_object_fields(Ep, Type),
263 23356 [get_field(Ep, Field, [Type | Path]) || Field <- Fields]
264 end.
265
266 -spec get_union_type(ep(), json_map(), [binary()]) -> field_spec().
267 get_union_type(Ep, #{<<"kind">> := <<"OBJECT">>, <<"name">> := Type} = M, Path) ->
268 7158 #{on => Type, fields => get_fields(Ep, M, Path)}.
269
270 -spec get_field(ep(), json_map(), [binary()]) -> field_spec().
271 get_field(Ep, #{<<"type">> := Type, <<"name">> := Name}, Path) ->
272 87365 case get_fields(Ep, Type, Path) of
273 76372 [] -> #{name => Name};
274 10993 Fields -> #{name => Name, fields => Fields}
275 end.
276
277 -spec get_object_fields(ep(), binary()) -> [json_map()].
278 get_object_fields(Ep, ObjectType) ->
279 23356 Doc = iolist_to_binary(["query ($type: String!) { __type(name: $type) "
280 "{name fields {name type ", field_type_query(), "}}}"]),
281 23356 Vars = #{<<"type">> => ObjectType},
282 23356 {ok, #{data := #{<<"__type">> := #{<<"fields">> := Fields}}}} = execute(Ep, Doc, Vars),
283 23356 Fields.
284
285 -spec insert_category(category(), category_spec(), specs()) -> specs().
286 insert_category(Category, NewCatSpec = #{commands := NewCommands}, Specs) ->
287 4785 case Specs of
288 #{Category := #{desc := OldDesc, commands := OldCommands}} ->
289 1893 case maps:with(maps:keys(OldCommands), NewCommands) of
290 Common when Common =:= #{} ->
291 1893 Specs#{Category := #{desc => OldDesc,
292 commands => maps:merge(OldCommands, NewCommands)}};
293 Common ->
294
:-(
error(#{what => overlapping_graphql_commands,
295 text => <<"GraphQL query and mutation names are not unique">>,
296 category => Category,
297 commands => maps:keys(Common)})
298 end;
299 _ ->
300 2892 Specs#{Category => NewCatSpec}
301 end.
302
303 -spec prepare_doc(category(), command(), map()) -> doc().
304 prepare_doc(Category, Command, #{op_type := OpType, args := Args, fields := Fields}) ->
305 16624 iolist_to_binary([OpType, " ", declare_variables(Args), "{ ", Category, " { ", Command,
306 use_variables(Args), return_fields(Fields), " } }"]).
307
308 -spec declare_variables([arg_spec()]) -> iolist().
309 1363 declare_variables([]) -> "";
310 declare_variables(Args) ->
311 15261 ["(", lists:join(", ", lists:map(fun declare_variable/1, Args)), ") "].
312
313 -spec declare_variable(arg_spec()) -> iolist().
314 declare_variable(#{name := Name, type := Type, wrap := Wrap}) ->
315 31300 ["$", Name, ": ", wrap_type(Wrap, Type)].
316
317 -spec wrap_type([required | list], binary()) -> iolist().
318 wrap_type([required | Wrap], Type) ->
319 25186 [wrap_type(Wrap, Type), $!];
320 wrap_type([list | Wrap], Type) ->
321 2138 [$[, wrap_type(Wrap, Type), $]];
322 wrap_type([], Type) ->
323 31310 [Type].
324
325 -spec use_variables([arg_spec()]) -> iolist().
326 1363 use_variables([]) -> "";
327 use_variables(Args) ->
328 15261 ["(", lists:join(", ", lists:map(fun use_variable/1, Args)), ")"].
329
330 -spec use_variable(arg_spec()) -> iolist().
331 use_variable(#{name := Name}) ->
332 31300 [Name, ": $", Name].
333
334 -spec return_fields([field_spec()]) -> iolist().
335 8461 return_fields([]) -> "";
336 return_fields(Fields) ->
337 26314 [" { ", lists:join(" ", [return_field(F) || F <- Fields]), " }"].
338
339 -spec return_field(field_spec()) -> iodata().
340 return_field(#{name := Name, fields := Fields}) ->
341 10993 [Name, return_fields(Fields)];
342 return_field(#{name := Name}) ->
343 76670 Name;
344 return_field(#{on := Type, fields := Fields}) ->
345 7158 ["... on ", Type, return_fields(Fields)].
346
347 -spec execute(ep(), doc(), json_map()) -> result().
348 execute(Ep, Doc, Vars) ->
349 28619 mongoose_graphql:execute(Ep, #{document => Doc,
350 operation_name => undefined,
351 vars => Vars,
352 authorized => true,
353 ctx => #{method => cli}}).
354
355 field_type_query() ->
356 28141 nested_type_query("name kind possibleTypes {name kind}").
357
358 arg_type_query() ->
359 4785 nested_type_query("name kind").
360
361 nested_type_query(BasicQuery) ->
362 32926 lists:foldl(fun(_, QueryAcc) -> ["{ ", BasicQuery, " ofType ", QueryAcc, " }"] end,
363 ["{ ", BasicQuery, " }"], lists:seq(1, ?MAX_INTROSPECTION_DEPTH)).
364
365 category_spec_query() ->
366 447 "{name fields {name description type {name fields {name}}}}".
Line Hits Source