33
34:- module(graphql,
35 [ graphql_read_document/3, 36 graphql_execute_document/4, 37 graphql_document_to_string/3, 38 graphql_document_to_codes/3, 39 graphql/4 40 ]). 41
48
49:- autoload(library(quasi_quotations),
50 [phrase_from_quasi_quotation/2, quasi_quotation_syntax/1]). 51:- autoload(library(dcg/basics),
52 [ prolog_var_name//1,
53 digit//1,
54 digits//1,
55 xdigit//1,
56 xinteger//1
57 ]). 58:- autoload(library(dcg/high_order), [optional//2, sequence//2]). 59:- autoload(library(http/json), [atom_json_dict/3]). 60:- autoload(library(http/http_client), [http_post/4]). 61:- autoload(library(apply), [include/3]). 62:- autoload(library(lists), [member/2, append/3]). 63:- autoload(library(option), [option/3, option/2]). 64:- autoload(library(pure_input), [phrase_from_stream/2]). 65:- use_module(library(http/http_json), []). 66
67
108
109
110:- predicate_options(graphql_execute_document/4, 4,
111 [variables(list),
112 data(list),
113 pass_to(graphql_auth_token/3, 3),
114 pass_to(graphql_document_to_string/3, 3)]). 115
116
117graphql_execute_document(URI,
118 Document,
119 Result,
120 Options) :-
121 option(variables(Variables), Options, null),
122 option(data(Data), Options, [map=null]),
123 graphql_auth_token(URI, Token, Options),
124 graphql_document_to_string(Document, Text, Options),
125 atom_json_dict(Operations,
126 _{query: Text, variables: Variables},
127 []),
128 http_post(URI,
129 form_data([operations=Operations|Data]),
130 Result,
131 [json_object(dict), authorization(bearer(Token))]).
132
133
134:- predicate_options(graphql_auth_token/3, 3,
135 [token(string)]). 136
137
138graphql_auth_token(_URI, Token, Options) :-
139 option(token(Token), Options),
140 !.
141graphql_auth_token(URI, Token, _Options) :-
142 graphql_auth_token_hook(URI, Token),
143 !.
144
145
150:- multifile graphql_auth_token_hook/2. 151:- dynamic graphql_auth_token_hook/2. 152
153
154
155
166
167:- quasi_quotation_syntax(graphql). 168
169graphql(Content, Args, VariableNames0, Result) :-
170 include(qq_var(Args), VariableNames0, VariableNames),
171 phrase_from_quasi_quotation(graphql_tokens(Tokens,
172 [variable_names(VariableNames)]),
173 Content),
174 phrase(graphql_executable_document(Result), Tokens).
175
176
177qq_var(Vars, _=Var) :- member(V, Vars), V == Var, !.
178
179
292
293:- predicate_options(graphql_read_document/3, 3,
294 [variable_names(list)]). 295
296graphql_read_document(codes(Codes, Rest), Document, Options) =>
297 phrase(graphql_tokens(Tokens, Options), Codes, Rest),
298 phrase(graphql_executable_document(Document), Tokens).
299graphql_read_document(codes(Codes), Document, Options) =>
300 phrase(graphql_tokens(Tokens, Options), Codes),
301 phrase(graphql_executable_document(Document), Tokens).
302graphql_read_document(string(String), Document, Options) =>
303 string_codes(String, Codes),
304 phrase(graphql_tokens(Tokens, Options), Codes),
305 phrase(graphql_executable_document(Document), Tokens).
306graphql_read_document(Stream, Document, Options) =>
307 phrase_from_stream(graphql_tokens(Tokens, Options), Stream),
308 phrase(graphql_executable_document(Document), Tokens).
309
310
311graphql_executable_document([H|T]) -->
312 graphql_executable_definition(H),
313 graphql_executable_definitions(T).
314
315
316graphql_executable_definitions([H|T]) -->
317 graphql_executable_definition(H),
318 !,
319 graphql_executable_definitions(T).
320graphql_executable_definitions([]) --> [].
321
322
323graphql_executable_definition(operation(Type,
324 Name,
325 VariableDefinitions,
326 Directives,
327 SelectionSet)) -->
328 graphql_operation_definition(Type,
329 Name,
330 VariableDefinitions,
331 Directives,
332 SelectionSet),
333 !.
334graphql_executable_definition(fragment(Name,
335 Type,
336 Directives,
337 SelectionSet)) -->
338 [name("fragment"), name(Name), name("on"), name(Type)],
339 graphql_inline_fragment(Directives, SelectionSet).
340
341
342graphql_operation_definition(T, N, V, D, S) -->
343 graphql_operation_type(T),
344 !,
345 graphql_query(N, V, D, S).
346graphql_operation_definition(query, null, [], [], S) -->
347 graphql_selection_set(S).
348
349
350graphql_operation_type(query) -->
351 [name("query")],
352 !.
353graphql_operation_type(mutation) -->
354 [name("mutation")],
355 !.
356graphql_operation_type(subscription) -->
357 [name("subscription")],
358 !.
359
360
361graphql_query(N, V, D, S) -->
362 optional([name(N)],
363 {N=null}),
364 optional(graphql_variables_definition(V),
365 {V=[]}),
366 optional(graphql_directives(D),
367 {D=[]}),
368 graphql_selection_set(S).
369
370
371graphql_variables_definition([H|T]) -->
372 ['('],
373 graphql_variable_definition(H),
374 sequence(graphql_variable_definition, T),
375 [')'].
376
377
378graphql_variable_definition(variable_definition(Var, Type, Def, Dirs)) -->
379 graphql_variable(Var),
380 [':'],
381 graphql_type(Type),
382 optional(graphql_default_value(Def),
383 {Def=null}),
384 optional(graphql_directives(Dirs),
385 {Dirs=[]}).
386
387
388graphql_type(T) -->
389 graphql_type_(T0),
390 graphql_type_nullable(T0, T).
391
392
393graphql_type_(named_type(N)) -->
394 [name(N)],
395 !.
396graphql_type_(list_type(T)) -->
397 ['['],
398 !,
399 graphql_type(T),
400 [']'].
401
402
403graphql_type_nullable(T, non_null_type(T)) -->
404 ['!'],
405 !.
406graphql_type_nullable(T, T) -->
407 [].
408
409graphql_variable(V) -->
410 ['$', name(V)].
411
412
413graphql_default_value(V) -->
414 graphql_value([const(true)], V).
415
416
417graphql_value(_, V) -->
418 [prolog(V)],
419 !.
420graphql_value(Options, variable(V)) -->
421 { \+ option(const(true), Options) },
422 graphql_variable(V),
423 !.
424graphql_value(_, N) -->
425 [integer(N)],
426 !.
427graphql_value(_, F) -->
428 [float(F)],
429 !.
430graphql_value(_, S) -->
431 [string(S)],
432 !.
433graphql_value(_, V) -->
434 [name(N)],
435 !,
436 { graphql_name_value(N, V) }.
437graphql_value(Options, L) -->
438 graphql_list_value(Options, L),
439 !.
440graphql_value(Options, O) -->
441 graphql_object_value(Options, O),
442 !.
443
444
445graphql_name_value("true" , true ) :- !.
446graphql_name_value("false", false ) :- !.
447graphql_name_value("null" , null ) :- !.
448graphql_name_value(N , enum(N)).
449
450
451graphql_list_value(Options, L) -->
452 ['['],
453 sequence(graphql_value(Options), L),
454 [']'].
455
456
457graphql_object_value(Options, O) -->
458 ['{'],
459 sequence(graphql_object_field(Options), O0),
460 ['}'],
461 { dict_pairs(O, _, O0) }.
462
463
464graphql_object_field(Options, Name-Value) -->
465 [name(Name0), ':'],
466 { atom_string(Name, Name0) },
467 graphql_value(Options, Value).
468
469
470graphql_directives([H|T]) -->
471 graphql_directive(H),
472 graphql_directives_(T).
473
474
475graphql_directives_([H|T]) -->
476 graphql_directive(H),
477 !,
478 graphql_directives_(T).
479graphql_directives_([]) --> [].
480
481
482graphql_directive(N-A) -->
483 ['@', name(N)],
484 optional(graphql_arguments(A),
485 {A=_{}}).
486
487
488graphql_arguments(A) -->
489 ['('],
490 graphql_argument(H),
491 sequence(graphql_argument, T),
492 [')'],
493 { dict_pairs(A, _, [H|T]) }.
494
495
496graphql_argument(N-V) -->
497 [name(N0), ':'],
498 { atom_string(N, N0) },
499 graphql_value([], V).
500
501
502graphql_selection_set([H|T]) -->
503 ['{'],
504 graphql_selection(H),
505 sequence(graphql_selection, T),
506 ['}'].
507
508graphql_selection(field(A, N, R, D, S)) -->
509 graphql_field(A, N, R, D, S),
510 !.
511graphql_selection(F) -->
512 ['...'],
513 graphql_selection_(F).
514
515
516graphql_selection_(F) -->
517 [name(N)],
518 !,
519 graphql_selection__(N, F).
520graphql_selection_(inline_fragment(null, D, S)) -->
521 graphql_inline_fragment(D, S).
522
523
524graphql_selection__("on", inline_fragment(T, D, S)) -->
525 !,
526 [name(T)],
527 graphql_inline_fragment(D, S).
528graphql_selection__(N, fragment_spread(N, D)) -->
529 optional(graphql_directives(D),
530 {D=[]}).
531
532
533graphql_inline_fragment(D, S) -->
534 optional(graphql_directives(D),
535 {D=[]}),
536 graphql_selection_set(S).
537
538
539graphql_field(Alias, Name, Args, Directives, SelectionSet) -->
540 [name(Name0)],
541 graphql_field_(Name0, Alias, Name, Args, Directives, SelectionSet).
542
543
544graphql_field_(Alias, Alias, Name, Args, Directives, SelectionSet) -->
545 [':'],
546 !,
547 [name(Name)],
548 graphql_field__(Args, Directives, SelectionSet).
549graphql_field_(Name, null, Name, Args, Directives, SelectionSet) -->
550 graphql_field__(Args, Directives, SelectionSet).
551
552
553graphql_field__(Args, Directives, SelectionSet) -->
554 optional(graphql_arguments(Args),
555 {Args=[]}),
556 optional(graphql_directives(Directives),
557 {Directives=[]}),
558 optional(graphql_selection_set(SelectionSet),
559 {SelectionSet=[]}).
560
561
563graphql_tokens(Ts, Options) -->
564 graphql_ignored,
565 graphql_tokens_(Ts, Options).
566
567
568graphql_tokens_([H|T], Options) -->
569 graphql_token(H, Options),
570 !,
571 graphql_tokens(T, Options).
572graphql_tokens_([ ], _Options) --> [].
573
574
578graphql_token(P, _Options) --> graphql_punctuator(P).
579graphql_token(name(N), _Options) --> graphql_name(N).
580graphql_token(N, _Options) --> graphql_numeric_value(N).
581graphql_token(string(S), _Options) --> graphql_string_value(S).
582graphql_token(prolog(E), Options) --> graphql_prolog(E, Options).
583
584
585graphql_prolog(V, Options) -->
586 "<",
587 prolog_var_name(N),
588 ">",
589 { option(variable_names(VarNames), Options, []),
590 memberchk(N=V, VarNames)
591 }.
592
593
594
598graphql_ignored --> graphql_white_space , !, graphql_ignored.
599graphql_ignored --> graphql_line_terminator, !, graphql_ignored.
600graphql_ignored --> graphql_comment , !, graphql_ignored.
601graphql_ignored --> graphql_comma , !, graphql_ignored.
602graphql_ignored --> [].
603
604
608graphql_white_space --> graphql_white_space(_).
609
610
611graphql_white_space(0' ) --> " ", !.
612graphql_white_space(0'\t) --> "\t".
613
614
618graphql_line_terminator --> "\n".
619graphql_line_terminator --> "\r".
620
621
--> "#", graphql_comment_chars.
626
627
--> graphql_comment_char, !, graphql_comment_chars.
630graphql_comment_chars --> [].
631
632
--> graphql_line_terminator, !, { false }.
637graphql_comment_char --> [_], !.
638
639
643graphql_comma --> ",".
644
645
649graphql_punctuator('!') --> "!", !.
650graphql_punctuator('$') --> "$", !.
651graphql_punctuator('&') --> "&", !.
652graphql_punctuator('(') --> "(", !.
653graphql_punctuator(')') --> ")", !.
654graphql_punctuator('...') --> "...", !.
655graphql_punctuator(':') --> ":", !.
656graphql_punctuator('=') --> "=", !.
657graphql_punctuator('@') --> "@", !.
658graphql_punctuator('[') --> "[", !.
659graphql_punctuator(']') --> "]", !.
660graphql_punctuator('{') --> "{", !.
661graphql_punctuator('}') --> "}", !.
662graphql_punctuator('|') --> "|", !.
663
664
668graphql_name(N) -->
669 graphql_name_start(H),
670 graphql_name_(T),
671 { string_codes(N, [H|T]) }.
672
673
674graphql_name_([H|T]) -->
675 graphql_name_continue(H),
676 !,
677 graphql_name_(T).
678graphql_name_([]) --> [].
679
680
684graphql_name_start(L) --> graphql_letter(L).
685graphql_name_start(0'_) --> "_".
686
687
691graphql_name_continue(L) --> graphql_letter(L).
692graphql_name_continue(D) --> digit(D).
693graphql_name_continue(0'_) --> "_".
694
695
699graphql_letter(L) -->
700 [L],
701 { ( 0'A =< L, L =< 0'Z
702 -> true
703 ; 0'a =< L, L =< 0'z
704 )
705 }.
706
707
708graphql_numeric_value(N) -->
709 graphql_integer_part(I),
710 graphql_numeric_value_(I, N).
711
712
713graphql_numeric_value_(I, N) -->
714 graphql_fractional_part(F),
715 !,
716 graphql_numeric_value__(I, F, N).
717graphql_numeric_value_(I, N) -->
718 graphql_numeric_value__(I, [], N).
719
720
721graphql_fractional_part([0'., H|T]) -->
722 ".",
723 !,
724 digits([H|T]).
725
726
727graphql_exponent_part([E|T]) -->
728 graphql_exponent_indicator(E),
729 !,
730 graphql_exponent_part_(T).
731
732
733graphql_exponent_part_([S,H|T]) -->
734 graphql_sign(S),
735 digits([H|T]).
736graphql_exponent_part_([H|T]) -->
737 digits([H|T]).
738
739
740graphql_exponent_indicator(0'e) --> "e", !.
741graphql_exponent_indicator(0'E) --> "E".
742
743
744graphql_sign(0'-) --> "-", !.
745graphql_sign(0'+) --> "+".
746
747
748graphql_numeric_value__(I, F, float(N)) -->
749 graphql_exponent_part(E),
750 !,
751 { append(I, F, H),
752 append(H, E, C),
753 number_codes(N, C)
754 }.
755graphql_numeric_value__(I, [], integer(N)) -->
756 !,
757 { number_codes(N, I)
758 }.
759graphql_numeric_value__(I, F, float(N)) -->
760 { append(I, F, C),
761 number_codes(N, C)
762 }.
763
764
765graphql_integer_part([0'-|T]) -->
766 "-",
767 !,
768 graphql_natural_part(T).
769graphql_integer_part(T) -->
770 graphql_natural_part(T).
771
772graphql_natural_part([0'0]) -->
773 "0",
774 !.
775graphql_natural_part([H|T]) -->
776 graphql_non_zero_digit(H),
777 digits(T).
778
779
780graphql_non_zero_digit(D) -->
781 [D],
782 { 0'1 =< D, D =< 0'9 }.
783
784
785graphql_string_value(S) -->
786 "\"",
787 graphql_string_value_(S).
788
789
790graphql_string_value_(S) -->
791 "\"",
792 !,
793 graphql_string_value__(S).
794graphql_string_value_(S) -->
795 graphql_string_body(S).
796
797
798graphql_string_value__(S) -->
799 "\"",
800 !,
801 graphql_block_string(S).
802graphql_string_value__("") --> [].
803
804
805graphql_string_body(S) -->
806 graphql_string_character(H),
807 graphql_string_body_(H, S).
808
809graphql_string_body_(H, S) -->
810 graphql_string_characters(T),
811 { string_codes(S, [H|T]) }.
812
813
814graphql_string_characters([]) --> "\"", !.
815graphql_string_characters([H|T]) -->
816 graphql_string_character(H),
817 graphql_string_characters(T).
818
819
820graphql_string_character(C) -->
821 "\\",
822 !,
823 graphql_string_escape_sequence(C).
824graphql_string_character(C) -->
825 [C].
826
827
828graphql_string_escape_sequence(U) -->
829 "u",
830 !,
831 graphql_string_escape_hex(U).
832graphql_string_escape_sequence(C) -->
833 [C],
834 { memberchk(C, `\"\\/bfnrt`) }.
835
836graphql_string_escape_hex(U) -->
837 "{",
838 !,
839 xinteger(U),
840 "}".
841graphql_string_escape_hex(U) -->
842 xdigit(A),
843 xdigit(B),
844 xdigit(C),
845 xdigit(D),
846 { U is (A << 12) + (B << 8) + (C << 4) + D }.
847
848
849graphql_block_string("") -->
850 graphql_block_string_quote,
851 !.
852graphql_block_string(S) -->
853 graphql_line_terminator,
854 !,
855 graphql_block_string(S).
856graphql_block_string(S) -->
857 graphql_white_space(C),
858 !,
859 graphql_block_string_empty_initial_line([C|T]-T, 1, S).
860graphql_block_string(S) -->
861 graphql_block_string_characters(C),
862 { append(C, T, H) },
863 graphql_block_string_first_line(H-T, S).
864
865
866graphql_block_string_empty_initial_line(_, _, "") -->
867 graphql_block_string_quote,
868 !.
869graphql_block_string_empty_initial_line(_, _, S) -->
870 graphql_line_terminator,
871 !,
872 graphql_block_string(S).
873graphql_block_string_empty_initial_line(H-[C|T], I0, S) -->
874 graphql_white_space(C),
875 !,
876 { I is I0 + 1 },
877 graphql_block_string_empty_initial_line(H-T, I, S).
878graphql_block_string_empty_initial_line(H-T0, I, S) -->
879 graphql_block_string_characters(C),
880 { append(C, T, T0),
881 length(C, N0),
882 N is N0 + I
883 },
884 graphql_block_string_initial_line(H-T, N, I, S).
885
886
887graphql_block_string_first_line(L, S) -->
888 graphql_block_string_quote,
889 !,
890 { graphql_block_string_close(L, [], 0, S) }.
891graphql_block_string_first_line(L, S) -->
892 graphql_line_terminator,
893 !,
894 graphql_block_string_line_indent(L, M-M, C-C, 0, 1.0Inf, S).
895graphql_block_string_first_line(H-T0, S) -->
896 graphql_block_string_characters(C),
897 { append(C, T, T0) },
898 graphql_block_string_first_line(H-T, S).
899
900
901graphql_block_string_initial_line(CH-CT, N, I, S) -->
902 graphql_block_string_quote,
903 !,
904 { graphql_block_string_close(F-F, [line(CH, CT, N)], I, S) }.
905graphql_block_string_initial_line(CH-CT, N, I, S) -->
906 graphql_line_terminator,
907 !,
908 graphql_block_string_line_indent(F-F, [line(CH,CT,N)|MoreLines]-MoreLines, L-L, 0, I, S).
909graphql_block_string_initial_line(H-T0, N0, I, S) -->
910 graphql_block_string_characters(C),
911 { append(C, T, T0),
912 length(C, N1),
913 N is N0 + N1
914 },
915 graphql_block_string_initial_line(H-T, N, I, S).
916
917
918graphql_block_string_characters([34,34,34]) -->
919 "\\",
920 graphql_block_string_quote,
921 !.
922graphql_block_string_characters([C]) -->
923 [C].
924
925
926graphql_block_string_line_indent(F, MH-[], _, _, I, S) -->
927 graphql_block_string_quote,
928 !,
929 { graphql_block_string_close(F, MH, I, S) }.
930graphql_block_string_line_indent(F, M, LH-LT, N, I, S) -->
931 graphql_line_terminator,
932 !,
933 graphql_block_string_maybe_trailing_empty_line(F, M, [line(LH, LT, N)|T]-T, C-C, 0, I, S).
934graphql_block_string_line_indent(F, M, H-[C|T], N0, I, S) -->
935 graphql_white_space(C),
936 !,
937 { N is N0 + 1 },
938 graphql_block_string_line_indent(F, M, H-T, N, I, S).
939graphql_block_string_line_indent(F, M, H-T0, N0, I0, S) -->
940 graphql_block_string_characters(C),
941 { append(C, T, T0),
942 I is min(N0, I0),
943 length(C, N1),
944 N is N0 + N1
945 },
946 graphql_block_string_line(F, M, H-T, N, I, S).
947
948
949graphql_block_string_maybe_trailing_empty_line(F, MH-[], _W, _C, _N, I, S) -->
950 graphql_block_string_quote,
951 !,
952 { graphql_block_string_close(F, MH, I, S) }.
953graphql_block_string_maybe_trailing_empty_line(F, M, WH-[line(CH0,CT0,N)|WT], CH0-CT0, N, I, S) -->
954 graphql_line_terminator,
955 !,
956 graphql_block_string_maybe_trailing_empty_line(F, M, WH-WT, C-C, 0, I, S).
957graphql_block_string_maybe_trailing_empty_line(F, M, W, CH-[C|CT], N0, I, S) -->
958 graphql_white_space(C),
959 !,
960 { N is N0 + 1 },
961 graphql_block_string_maybe_trailing_empty_line(F, M, W, CH-CT, N, I, S).
962graphql_block_string_maybe_trailing_empty_line(F, MH-WH, WH-WT, H-T0, N0, I0, S) -->
963 graphql_block_string_characters(C),
964 { append(C, T, T0),
965 I is min(N0, I0),
966 length(C, N1),
967 N is N0 + N1
968 },
969 graphql_block_string_line(F, MH-WT, H-T, N, I, S).
970
971
972graphql_block_string_line(F, MH-[line(CH, CT, N)], CH-CT, N, I, S) -->
973 graphql_block_string_quote,
974 !,
975 { graphql_block_string_close(F, MH, I, S) }.
976graphql_block_string_line(F, MH-[line(CH, CT, N)|MT], CH-CT, N, I, S) -->
977 graphql_line_terminator,
978 !,
979 graphql_block_string_maybe_trailing_empty_line(F, MH-MT, W-W, C-C, 0, I, S).
980graphql_block_string_line(F, M, H-T0, N0, I, S) -->
981 graphql_block_string_characters(C),
982 { append(C, T, T0),
983 length(C, N1),
984 N is N0 + N1
985 },
986 graphql_block_string_line(F, M, H-T, N, I, S).
987
988
989graphql_block_string_close(FirstLineH-FirstLineT, [line(H0, T, L)|MoreLines], Indent, String) :-
990 FirstLineH == FirstLineT,
991 !,
992 graphql_block_string_dedent_line(H0, L, Indent, H),
993 graphql_block_string_combine_more_lines(MoreLines, Indent, T),
994 string_codes(String, H).
995graphql_block_string_close(FirstLineH-FirstLineT, MoreLines, Indent, String) :-
996 graphql_block_string_combine_more_lines(MoreLines, Indent, FirstLineT),
997 string_codes(String, FirstLineH).
998
999graphql_block_string_combine_more_lines([], _, []) :-
1000 !.
1001graphql_block_string_combine_more_lines([line(H0, T, L)|MoreLines],
1002 Indent,
1003 [0'\n|H]) :-
1004 graphql_block_string_dedent_line(H0, L, Indent, H),
1005 graphql_block_string_combine_more_lines(MoreLines, Indent, T).
1006
1007
1008graphql_block_string_dedent_line(Line0, Length, Indent, Line) :-
1009 PrefixLength is min(Length, Indent),
1010 length(Prefix, PrefixLength),
1011 append(Prefix, Line, Line0).
1012
1013
1014graphql_block_string_quote --> "\"\"\"".
1015
1016
1017
1018
1025
1026:- predicate_options(graphql_document_to_string/3, 3,
1027 [pass_to(graphql_document_to_codes/3, 3)]). 1028
1029graphql_document_to_string(Document, String, Options) :-
1030 graphql_document_to_codes(Document, Codes, Options),
1031 string_codes(String, Codes).
1032
1033
1048
1049:- predicate_options(graphql_document_to_codes/3, 3,
1050 [separator(list)]). 1051
1052graphql_document_to_codes(Document, Codes, Options) :-
1053 phrase(graphql_write_document(Document, Options), Codes).
1054
1055
1056graphql_write_document([H|T], Options) -->
1057 graphql_write_definition(H, Options),
1058 graphql_write_document(T, Options).
1059graphql_write_document([], _Options) --> [], !.
1060
1061
1062graphql_write_definition(operation(Type,
1063 Name,
1064 VariableDefinitions,
1065 Directives,
1066 SelectionSet), Options) -->
1067 graphql_write_name(Type, Options),
1068 graphql_write_name_maybe(Name, Options),
1069 graphql_write_variable_definitions(VariableDefinitions, Options),
1070 graphql_write_directives_and_selection_set(Directives,
1071 SelectionSet,
1072 Options).
1073
1074
1075graphql_write_name(Name, _Options) -->
1076 { string_codes(Name, Codes) },
1077 Codes.
1078
1079
1080graphql_write_name_maybe(null, _Options) --> [], !.
1081graphql_write_name_maybe(Name, Options) -->
1082 graphql_write_separator(Options),
1083 graphql_write_name(Name, Options).
1084
1085
1086graphql_write_variable_definitions([ ], _Options) --> [], !.
1087graphql_write_variable_definitions([H|T], Options) -->
1088 "(",
1089 graphql_write_variable_definition(H, Options),
1090 graphql_write_variable_definitions_(T, Options),
1091 ")".
1092
1093
1094graphql_write_variable_definitions_([ ], _Options) --> [], !.
1095graphql_write_variable_definitions_([H|T], Options) -->
1096 graphql_write_separator(Options),
1097 graphql_write_variable_definition(H, Options),
1098 graphql_write_variable_definitions_(T, Options).
1099
1100
1101graphql_write_variable_definition(variable_definition(Name,
1102 Type,
1103 Default,
1104 Directives),
1105 Options) -->
1106 `$`,
1107 graphql_write_name(Name, Options),
1108 `:`,
1109 graphql_write_type(Type, Options),
1110 graphql_write_value_maybe(Default, Options),
1111 graphql_write_directives(Directives, Options).
1112
1113
1114graphql_write_value_maybe(null, _Options) -->
1115 !,
1116 [].
1117graphql_write_value_maybe(Value, Options) -->
1118 graphql_write_separator(Options),
1119 graphql_write_value(Value, Options).
1120
1121graphql_write_value(enum(N), _Options) -->
1122 !,
1123 { string_codes(N, Codes) },
1124 Codes.
1125graphql_write_value(variable(V), _Options) -->
1126 !,
1127 { string_codes(V, Codes) },
1128 [0'$|Codes].
1129graphql_write_value(Atom, _Options) -->
1130 { atom(Atom),
1131 !,
1132 atom_codes(Atom, Codes)
1133 },
1134 Codes.
1135graphql_write_value(String, Options) -->
1136 { string(String),
1137 !,
1138 string_codes(String, Codes)
1139 },
1140 "\"",
1141 graphql_write_string(Codes, Options),
1142 "\"".
1143graphql_write_value(Number, _Options) -->
1144 { number(Number),
1145 !,
1146 number_codes(Number, Codes)
1147 },
1148 Codes.
1149graphql_write_value(List, Options) -->
1150 { is_list(List) },
1151 !,
1152 "[",
1153 graphql_write_list_value(List, Options),
1154 "]".
1155graphql_write_value(Dict, Options) -->
1156 { is_dict(Dict),
1157 !,
1158 dict_pairs(Dict, _, Object)
1159 },
1160 "{",
1161 graphql_write_pairs(Object, Options),
1162 "}".
1163
1164
1165graphql_write_pairs([H|T], Options) -->
1166 !,
1167 graphql_write_pair(H, Options),
1168 graphql_write_pairs_(T, Options).
1169graphql_write_pairs([], _) --> [].
1170
1171
1172graphql_write_pairs_([H|T], Options) -->
1173 graphql_write_separator(Options),
1174 graphql_write_pair(H, Options),
1175 graphql_write_pairs_(T, Options).
1176graphql_write_pairs_([], _) --> [].
1177
1178
1179graphql_write_pair(N-V, Options) -->
1180 graphql_write_name(N, Options),
1181 ":",
1182 graphql_write_value(V, Options).
1183
1184
1189graphql_write_string([], _Options) --> !, [].
1190graphql_write_string([0'\"|T], Options) -->
1191 !,
1192 "\\\"",
1193 graphql_write_string(T, Options).
1194graphql_write_string([0'\\|T], Options) -->
1195 !,
1196 "\\\\",
1197 graphql_write_string(T, Options).
1198graphql_write_string([0'\n|T], Options) -->
1199 !,
1200 "\\n",
1201 graphql_write_string(T, Options).
1202graphql_write_string([0'\r|T], Options) -->
1203 !,
1204 "\\r",
1205 graphql_write_string(T, Options).
1206graphql_write_string([H|T], Options) -->
1207 [H],
1208 graphql_write_string(T, Options).
1209
1210
1211graphql_write_list_value([], _Options) --> !, [].
1212graphql_write_list_value([H|T], Options) -->
1213 graphql_write_value(H, Options),
1214 graphql_write_list_value_(T, Options).
1215
1216
1217graphql_write_list_value_([], _Options) --> !, [].
1218graphql_write_list_value_([H|T], Options) -->
1219 graphql_write_separator(Options),
1220 graphql_write_value(H, Options),
1221 graphql_write_list_value_(T, Options).
1222
1223
1224graphql_write_type(non_null_type(Type), Options) -->
1225 !,
1226 graphql_write_type(Type, Options),
1227 "!".
1228graphql_write_type(named_type(Name), Options) -->
1229 !,
1230 graphql_write_name(Name, Options).
1231graphql_write_type(list_type(Type), Options) -->
1232 "[",
1233 graphql_write_type(Type, Options),
1234 "]".
1235
1236
1237graphql_write_directives([ ], _Options) --> [], !.
1238graphql_write_directives([H|T], Options) -->
1239 graphql_write_separator(Options),
1240 graphql_write_directive(H, Options),
1241 graphql_write_directives(T, Options).
1242
1243
1244graphql_write_directive(Name-Arguments, Options) -->
1245 graphql_write_name(Name, Options),
1246 graphql_write_arguments(Arguments, Options).
1247
1248
1249graphql_write_arguments(_{}, _Options) --> !, [].
1250graphql_write_arguments(Args, Options) -->
1251 { dict_pairs(Args, _, Pairs) },
1252 "(",
1253 graphql_write_pairs(Pairs, Options),
1254 ")".
1255
1256
1257graphql_write_selection_set([ ], _Options) --> [], !.
1258graphql_write_selection_set([H|T], Options) -->
1259 "{",
1260 graphql_write_selection(H, Options),
1261 graphql_write_selection_set_(T, Options),
1262 "}".
1263
1264
1265graphql_write_selection_set_([ ], _Options) --> [], !.
1266graphql_write_selection_set_([H|T], Options) -->
1267 graphql_write_separator(Options),
1268 graphql_write_selection(H, Options),
1269 graphql_write_selection_set_(T, Options).
1270
1271
1272graphql_write_selection(field(Alias,
1273 Name,
1274 Args,
1275 Directives,
1276 SelectionSet),
1277 Options) -->
1278 graphql_write_field(Alias,
1279 Name,
1280 Args,
1281 Directives,
1282 SelectionSet,
1283 Options).
1284graphql_write_selection(fragment_spread(Name, Directives),
1285 Options) -->
1286 graphql_write_fragment_spread(Name, Directives, Options).
1287graphql_write_selection(inline_fragment(Type,
1288 Directives,
1289 SelectionSet),
1290 Options) -->
1291 graphql_write_inline_fragment(Type,
1292 Directives,
1293 SelectionSet,
1294 Options).
1295
1296
1297graphql_write_field(null,
1298 Name,
1299 Arguments,
1300 Directives,
1301 SelectionSet,
1302 Options) -->
1303 !,
1304 graphql_write_field_(Name,
1305 Arguments,
1306 Directives,
1307 SelectionSet,
1308 Options).
1309graphql_write_field(Alias,
1310 Name,
1311 Arguments,
1312 Directives,
1313 SelectionSet,
1314 Options) -->
1315 graphql_write_name(Alias, Options),
1316 ": ",
1317 graphql_write_field_(Name,
1318 Arguments,
1319 Directives,
1320 SelectionSet,
1321 Options).
1322
1323
1324graphql_write_field_(Name,
1325 Arguments,
1326 Directives,
1327 SelectionSet,
1328 Options) -->
1329 graphql_write_name(Name, Options),
1330 graphql_write_arguments(Arguments, Options),
1331 graphql_write_directives_and_selection_set(Directives,
1332 SelectionSet,
1333 Options).
1334
1335
1336graphql_write_directives_and_selection_set(Directives,
1337 SelectionSet,
1338 Options) -->
1339 graphql_write_directives(Directives, Options),
1340 graphql_write_selection_set(SelectionSet, Options).
1341
1342
1343graphql_write_separator(Options) -->
1344 { option(separator(Sep), Options, [0' ]) },
1345 Sep.
1346
1347
1348graphql_write_fragment_spread(Name, Directives, Options) -->
1349 "...",
1350 graphql_write_separator(Options),
1351 graphql_write_name(Name, Options),
1352 graphql_write_directives(Directives, Options).
1353
1354
1355graphql_write_inline_fragment(TypeCondition,
1356 Directives,
1357 SelectionSet,
1358 Options) -->
1359 "...",
1360 graphql_write_separator(Options),
1361 graphql_write_type_condition(TypeCondition, Options),
1362 graphql_write_directives_and_selection_set(Directives,
1363 SelectionSet,
1364 Options).
1365
1366
1367graphql_write_type_condition(TypeCondition, Options) -->
1368 "on ", graphql_write_name(TypeCondition, Options)