1/* Part of SWI-Prolog 2 3 Author: Eshel Yaron 4 E-mail: eshel@swi-prolog.org 5 Copyright (c) 2022, SWI-Prolog Solutions B.V. 6 All rights reserved. 7 8 Redistribution and use in source and binary forms, with or without 9 modification, are permitted provided that the following conditions 10 are met: 11 12 1. Redistributions of source code must retain the above copyright 13 notice, this list of conditions and the following disclaimer. 14 15 2. Redistributions in binary form must reproduce the above copyright 16 notice, this list of conditions and the following disclaimer in 17 the documentation and/or other materials provided with the 18 distribution. 19 20 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 21 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 22 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 23 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 24 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 25 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 26 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 27 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 28 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 29 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 30 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 31 POSSIBILITY OF SUCH DAMAGE. 32*/ 33 34:- module(graphql, 35 [ graphql_read_document/3, % +Source, -Document, +Options 36 graphql_execute_document/4, % +URI, +Document, -Result, +Options 37 graphql_document_to_string/3, % +Document, -String, +Options 38 graphql_document_to_codes/3, % +Document, -Codes, +Options 39 graphql/4 % Quasi-quotation syntax 40 ]).
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), []).
Document is a Prolog term representing the abstract syntax tree of the GraphQL document, as obtained from e.g. graphql_read_document/3 or graphql/4 quasi-quotation. Result is unified with a dict representing the JSON formatted response received from the server.
The following example shows how graphql_execute_document/4 can be used to expose a simple GraphQL interface to Prolog:
sourcehut_repository_description(Owner, Repo, Desc) :- graphql_execute_document("https://git.sr.ht/query", {| graphql(Owner, Repo) || { user(username: <Owner>) { repository(name: <Repo>) { description } } } |}, Dict, [token(...)]), Desc = Dict.get(data/user/repository/description). ?- sourcehut_repository_description("eshel", "sourcehut.pl", Desc). Desc = "SWI-Prolog package implementing a SourceHut GraphQL API client.".
Options is a list whose elements are one of the following:
$key
.
Variables is sent to the remote to the GraphQL endpoint in
JSON format for server-side interpolation.
For more information about GraphQL variables, see
https://spec.graphql.org/draft/#sec-Language.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 !.
150:- multifile graphql_auth_token_hook/2. 151:- dynamic graphql_auth_token_hook/2.
variable_names(+VarNames)
in graphql_read_document/3.
Result is a term representing the given GraphQL document in the same format as used by graphql_read_document/3.
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, !.
Document is a list of terms representing GraphQL executable definitions, each being one of:
VariableDefinitions is a list of terms of the form
variable_definition(VarName, VarType, VarDefault, VarDirs)
where VarName is a string denoting the name of the variable,
VarType is a term denoting the GraphQL type of the defined
variable in the format described below, VarDefault is a term
denoting a default GraphQL value associated with the defined
variable, and VarDirs is a possibly empty list of GraphQL
directives, each of which a term DirName-DirArgs where DirName
is the string name of the directive and DirArgs is a Prolog
dict denoting the directive arguments.
Directives is a possibly empty list of GraphQL directives associated with the given GraphQL operation.
SelectionSet is a list of GraphQL selections, each selection
is one of field(FieldAlias, FieldName, FieldArgs, FieldDirs,
FieldSelection)
, in which case FieldAlias is either null or
a string denoting the alias of the field, FieldName is a
string denoting the name of the field, FieldArgs is a dict
denoting the field arguments, FieldDirs is a list of GraphQL
directives and FieldSelection is a list of GraphQL
selections nested below the given field. Otherwise, each
selection can have the from fragment_spread(FragName,
FragDirs)
where FragName is a string denoting the name of
the fragment and FragDirs is a possibly empty list of GraphQL
directives. Lastly, each selection can have the form
inline_fragment(IFragTypeCondition, IFragDirs,
IFragSelectionSet)
where IFragTypeCondition is a string
denoting a type condition associated with the inline fragment,
IFragDirs denotes GraphQL directives associated with it,
and IFragSelectionSet is a list of GraphQL selections
specified by the fragment.
A GraphQL type is represented as one of:
A GraphQL value is represented as one of:
true
value.false
value.null
value.Source can be one of:
codes(Codes, [])
.Options is a list whose elements can be one of:
Occurrences of the special lexical construct "<Name>" (that is, ASCII 60, then the codes of the atom Name, then ASCII 62) in Source are expanded in Document to the GraphQL value Value. This option can be used to interpolate GraphQL documents with values given in Prolog representation.
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=[]}).
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) --> [].
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 }.
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 --> [].
608graphql_white_space --> graphql_white_space(_). 609 610 611graphql_white_space(0' ) --> " ", !. 612graphql_white_space(0'\t) --> "\t".
618graphql_line_terminator --> "\n". 619graphql_line_terminator --> "\r".
625graphql_comment --> "#", graphql_comment_chars.
629graphql_comment_chars --> graphql_comment_char, !, graphql_comment_chars. 630graphql_comment_chars --> [].
636graphql_comment_char --> graphql_line_terminator, !, { false }. 637graphql_comment_char --> [_], !.
643graphql_comma --> ",".
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('|') --> "|", !.
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_([]) --> [].
684graphql_name_start(L) --> graphql_letter(L). 685graphql_name_start(0'_) --> "_".
691graphql_name_continue(L) --> graphql_letter(L). 692graphql_name_continue(D) --> digit(D). 693graphql_name_continue(0'_) --> "_".
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 --> "\"\"\"".
Options are passed on to graphql_document_to_codes/3.
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).
Options are a list whose elements are one of:
separator(`, `)
.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 . 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 format('~s', [N]). 1124graphql_write_value(variable(V), _Options) --> 1125 !, 1126 format('$~s', [V]). 1127graphql_write_value(Atom, _Options) --> 1128 { atom(Atom) 1129 }, 1130 !, 1131 format('~a', [Atom]). 1132graphql_write_value(String, Options) --> 1133 { string(String), 1134 !, 1135 string_codes(String, Codes) 1136 }, 1137 "\"", 1138 graphql_write_string(Codes, Options), 1139 "\"". 1140graphql_write_value(Number, _Options) --> 1141 { number(Number) 1142 }, 1143 !, 1144 format('~w', [Number]). 1145graphql_write_value(List, Options) --> 1146 { is_list(List) }, 1147 !, 1148 "[", 1149 graphql_write_list_value(List, Options), 1150 "]". 1151graphql_write_value(Dict, Options) --> 1152 { is_dict(Dict), 1153 !, 1154 dict_pairs(Dict, _, Object) 1155 }, 1156 "{", 1157 graphql_write_pairs(Object, Options), 1158 "}". 1159 1160 1161graphql_write_pairs([H|T], Options) --> 1162 !, 1163 graphql_write_pair(H, Options), 1164 graphql_write_pairs_(T, Options). 1165graphql_write_pairs([], _) --> []. 1166 1167 1168graphql_write_pairs_([H|T], Options) --> 1169 graphql_write_separator(Options), 1170 graphql_write_pair(H, Options), 1171 graphql_write_pairs_(T, Options). 1172graphql_write_pairs_([], _) --> []. 1173 1174 1175graphql_write_pair(N-V, Options) --> 1176 graphql_write_name(N, Options), 1177 ":", 1178 graphql_write_value(V, Options).
1185graphql_write_string([], _Options) --> !, []. 1186graphql_write_string([0'\"|T], Options) --> 1187 !, 1188 "\\\"", 1189 graphql_write_string(T, Options). 1190graphql_write_string([0'\\|T], Options) --> 1191 !, 1192 "\\\\", 1193 graphql_write_string(T, Options). 1194graphql_write_string([0'\n|T], Options) --> 1195 !, 1196 "\\n", 1197 graphql_write_string(T, Options). 1198graphql_write_string([0'\r|T], Options) --> 1199 !, 1200 "\\r", 1201 graphql_write_string(T, Options). 1202graphql_write_string([H|T], Options) --> 1203 [H], 1204 graphql_write_string(T, Options). 1205 1206 1207graphql_write_list_value([], _Options) --> !, []. 1208graphql_write_list_value([H|T], Options) --> 1209 graphql_write_value(H, Options), 1210 graphql_write_list_value_(T, Options). 1211 1212 1213graphql_write_list_value_([], _Options) --> !, []. 1214graphql_write_list_value_([H|T], Options) --> 1215 graphql_write_separator(Options), 1216 graphql_write_value(H, Options), 1217 graphql_write_list_value_(T, Options). 1218 1219 1220graphql_write_type(non_null_type(Type), Options) --> 1221 !, 1222 graphql_write_type(Type, Options), 1223 "!". 1224graphql_write_type(named_type(Name), Options) --> 1225 !, 1226 graphql_write_name(Name, Options). 1227graphql_write_type(list_type(Type), Options) --> 1228 "[", 1229 graphql_write_type(Type, Options), 1230 "]". 1231 1232 1233graphql_write_directives([ ], _Options) --> [], !. 1234graphql_write_directives([H|T], Options) --> 1235 graphql_write_separator(Options), 1236 graphql_write_directive(H, Options), 1237 graphql_write_directives(T, Options). 1238 1239 1240graphql_write_directive(Name-Arguments, Options) --> 1241 graphql_write_name(Name, Options), 1242 graphql_write_arguments(Arguments, Options). 1243 1244 1245graphql_write_arguments(_{}, _Options) --> !, []. 1246graphql_write_arguments(Args, Options) --> 1247 { dict_pairs(Args, _, Pairs) }, 1248 "(", 1249 graphql_write_pairs(Pairs, Options), 1250 ")". 1251 1252 1253graphql_write_selection_set([ ], _Options) --> [], !. 1254graphql_write_selection_set([H|T], Options) --> 1255 "{", 1256 graphql_write_selection(H, Options), 1257 graphql_write_selection_set_(T, Options), 1258 "}". 1259 1260 1261graphql_write_selection_set_([ ], _Options) --> [], !. 1262graphql_write_selection_set_([H|T], Options) --> 1263 graphql_write_separator(Options), 1264 graphql_write_selection(H, Options), 1265 graphql_write_selection_set_(T, Options). 1266 1267 1268graphql_write_selection(field(Alias, 1269 Name, 1270 Args, 1271 Directives, 1272 SelectionSet), 1273 Options) --> 1274 graphql_write_field(Alias, 1275 Name, 1276 Args, 1277 Directives, 1278 SelectionSet, 1279 Options). 1280graphql_write_selection(fragment_spread(Name, Directives), 1281 Options) --> 1282 graphql_write_fragment_spread(Name, Directives, Options). 1283graphql_write_selection(inline_fragment(Type, 1284 Directives, 1285 SelectionSet), 1286 Options) --> 1287 graphql_write_inline_fragment(Type, 1288 Directives, 1289 SelectionSet, 1290 Options). 1291 1292 1293graphql_write_field(null, 1294 Name, 1295 Arguments, 1296 Directives, 1297 SelectionSet, 1298 Options) --> 1299 !, 1300 graphql_write_field_(Name, 1301 Arguments, 1302 Directives, 1303 SelectionSet, 1304 Options). 1305graphql_write_field(Alias, 1306 Name, 1307 Arguments, 1308 Directives, 1309 SelectionSet, 1310 Options) --> 1311 graphql_write_name(Alias, Options), 1312 ": ", 1313 graphql_write_field_(Name, 1314 Arguments, 1315 Directives, 1316 SelectionSet, 1317 Options). 1318 1319 1320graphql_write_field_(Name, 1321 Arguments, 1322 Directives, 1323 SelectionSet, 1324 Options) --> 1325 graphql_write_name(Name, Options), 1326 graphql_write_arguments(Arguments, Options), 1327 graphql_write_directives_and_selection_set(Directives, 1328 SelectionSet, 1329 Options). 1330 1331 1332graphql_write_directives_and_selection_set(Directives, 1333 SelectionSet, 1334 Options) --> 1335 graphql_write_directives(Directives, Options), 1336 graphql_write_selection_set(SelectionSet, Options). 1337 1338 1339graphql_write_separator(Options) --> 1340 { option(separator(Sep), Options, [0' ]) }, 1341 . 1342 1343 1344graphql_write_fragment_spread(Name, Directives, Options) --> 1345 "...", 1346 graphql_write_separator(Options), 1347 graphql_write_name(Name, Options), 1348 graphql_write_directives(Directives, Options). 1349 1350 1351graphql_write_inline_fragment(TypeCondition, 1352 Directives, 1353 SelectionSet, 1354 Options) --> 1355 "...", 1356 graphql_write_separator(Options), 1357 graphql_write_type_condition(TypeCondition, Options), 1358 graphql_write_directives_and_selection_set(Directives, 1359 SelectionSet, 1360 Options). 1361 1362 1363graphql_write_type_condition(TypeCondition, Options) --> 1364 "on ", graphql_write_name(TypeCondition, Options). 1365 1366format(Format, Args, Head, Tail) :- 1367 format(codes(Head, Tail), Format, Args)
GraphQL interface
This module provides predicates for working with GraphQL, a query language for HTTP-based APIs.
*/