1:- module(sourcehut_common,
    2          [op(100, xf, {}),
    3           sourcehut_graphql/3,
    4           sourcehut_graphql/4,
    5           sourcehut_graphql/5
    6          ]).    7
    8:- use_module(library(http/json)).    9:- use_module(library(http/http_client)).

SourceHut GraphQL API client

This module provides an interface for interacting with a SourceHut (https://sourcehut.org/) instance, such as https://sr.ht/ */

 user:sourcehut_token(+Host:string, -Token:String) is nondet
Multifile predicate that can be defined by the user to set a default OAuth2 token to be used when interacting with Host.
   23:- multifile user:sourcehut_token/2.   24
   25:- predicate_options(sourcehut_graphql/3,
   26                     3,
   27                     [pass_to(sourcehut_graphql/4, 4)]).
 sourcehut_graphql(+Query, -Result, +Options) is semidet
Calls sourcehut_graphql/4 with no query variables.
   33sourcehut_graphql(Query, Result, Options) :-
   34    sourcehut_graphql(Query, null, [map=null], Result, Options).
   35
   36
   37:- predicate_options(sourcehut_graphql/4,
   38                     4,
   39                     [pass_to(sourcehut_graphql/5, 5)]).
 sourcehut_graphql(+Query, +Variables, -Result, +Options) is semidet
Performs a GraphQL query specified by the string Query with a remote SourceHut instance. Variables is a dict which assigns values to GraphQL variables that appear in Query.

Result is unified with a dict translated from the server's JSON-formatted response.

Options processed:

scheme(+Scheme),service(+Service),domain(+Domain),port(+Port),path(+Path)
These options are combined to obtain the URL of the remote SourceHut instance. The default values are Scheme=https, service="git", Host="sr.ht", Port=443 and Path="/query"
token(+Token)
Token is an OAuth2 token to be used for authenticating with the remote SourceHut instance. If this option is not provided, sourcehut_token/2 is called as sourcehut_token(Host, Token) to obtain a token. If sourcehut_token/2 fails, the environment variables SOURCEHUT_PL_TOKEN and OAUTH2_TOKEN are consulted for a token. If no token can found, the call fails.
   63sourcehut_graphql(Query, Variables, Result, Options) :-
   64    sourcehut_graphql(Query, Variables, [map=null], Result, Options).
   65
   66
   67:- predicate_options(sourcehut_graphql/5,
   68                     5,
   69                     [scheme(+text),
   70                      service(+text),
   71                      domain(+text),
   72                      token(+text),
   73                      port(+integer),
   74                      path(+text)]).   75
   76sourcehut_graphql(Query, Variables, ExtraFromData, Result, Options) :-
   77    option(scheme(Scheme), Options, "https"),
   78    option(service(Service), Options, "git"),
   79    option(host(Host0), Options, "sr.ht"),
   80    (   atom(Host0)
   81    ->  atom_string(Host0, Host)
   82    ;   Host = Host0
   83    ),
   84    (   option(token(Token), Options), nonvar(Token)
   85    ->  true
   86    ;   user:sourcehut_token(Host, Token)
   87    ->  true
   88    ;   getenv('SOURCEHUT_PL_TOKEN', Token)
   89    ->  true
   90    ;   getenv('OAUTH2_TOKEN', Token)
   91    ),
   92    option(port(Port), Options, 443),
   93    option(path(Path), Options, "/query"),
   94    atomic_list_concat([Service, '.', Host, ':', Port], HostPort),
   95    uri_components(URI, uri_components(Scheme, HostPort, Path, _, _)),
   96    phrase(graphql(Query), Codes),
   97    string_codes(Text, Codes),
   98    atom_json_dict(Operations, _{query: Text, variables: Variables}, []),
   99    http_post(URI,
  100              form_data([operations=Operations|ExtraFromData]),
  101              Atom,
  102              [authorization(bearer(Token))]),
  103    atom_json_dict(Atom, Result, []).
  104
  105
  106graphql(L {R}) -->
  107    !,
  108    graphql_root(L),
  109    [32],
  110    [123, 32],
  111    {   comma_list(R, C)   },
  112    graphql_children(C),
  113    [125].
  114graphql(L) --> graphql_root(L).
  115
  116graphql_root(L) -->
  117    {   L =.. [A|T]   },
  118    graphql_literal(A),
  119    graphql_arguments(T).
  120
  121graphql_literal(A) -->
  122    {   atom(A)   },
  123    !,
  124    {   format(codes(C), "~w", [A])   },
  125    C.
  126graphql_literal(A) -->
  127    {   format(codes(C), "~p", [A])   },
  128    C.
  129
  130graphql_arguments([]) --> !, [].
  131graphql_arguments(Ss) --> [40, 32], graphql_pairs(Ss), [41].
  132
  133graphql_pairs([K:V|T]) -->
  134    !,
  135    graphql_literal(K),
  136    [58, 32],
  137    graphql_value(V),
  138    [32],
  139    graphql_pairs(T).
  140graphql_pairs([]) --> [].
  141
  142graphql_children([H|T]) -->
  143    !,
  144    graphql(H),
  145    [32],
  146    graphql_children(T).
  147graphql_children([]) --> [].
  148
  149graphql_value({I}) -->
  150    !,
  151    [123, 32],
  152    {   comma_list(I, C)   },
  153    graphql_pairs(C),
  154    [125].
  155graphql_value(A) -->
  156    graphql_literal(A)