1:- module(sourcehut_builds,
    2          [sourcehut_builds_version/4,  % -Major, -Minor, -Patch, +Options
    3           sourcehut_builds_jobs/3,     % +UserName, -Jobs, +Options
    4           sourcehut_builds_submit/3,   % +Manifest, -Job, +Options
    5           sourcehut_builds_cancel/3,   % +Id, -Job, +Options
    6           sourcehut_builds_job/3       % +Id, -Job, +Options
    7          ]).    8
    9:- use_module(common).

SourceHut Builds GraphQL API client

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

   20:- predicate_options(sourcehut_builds_version/4,
   21                     4,
   22                     [pass_to(sourcehut_graphql/3, 4)]).   23
   24%% sourcehut_builds_version(-Major, -Minor, -Patch, +Options) is det.
   25%
   26%  Unifies Major, Minor and Patch with the major, minor and patch
   27%  versions of the remote sourcehut builds service, respectively.
   28%  Options are passed to sourcehut_graphql/3.
   29sourcehut_builds_version(Major, Minor, Patch, Options) :-
   30    sourcehut_graphql(query {version {major, minor, patch}},
   31                      Dict,
   32                      [service(builds)|Options]),
   33    get_dict(data, Dict, Data),
   34    get_dict(version, Data, Version),
   35    get_dict(major, Version, Major),
   36    get_dict(minor, Version, Minor),
   37    get_dict(patch, Version, Patch).
   38
   39
   40:- predicate_options(sourcehut_builds_jobs/3,
   41                     3,
   42                     [cursor(+text),
   43                      next(-text),
   44                      pass_to(sourcehut_graphql/4, 4)]).   45
   46%% sourcehut_builds_jobs(+UserName, -Jobs, +Options) is semidet.
   47%
   48%  Unifies Jobs with a list of dicts describing build jobs owned by
   49%  the user UserName on a remote sourcehut builds service.
   50%
   51%  Options processed:
   52%
   53%    - cursor(+Cursor)
   54%      Query the server for jobs starting from Cursor, which
   55%      is a string obtained from the remote SourceHut instance through
   56%      the `next(-Next)` option of the previous call to this predicate.
   57%    - next(-Next)
   58%      Next is unified with the atom `null` if there are no more
   59%      refs to described, otherwise Next is a string that can
   60%      be passed as the `cursor(+Cursor)` argument to a following call
   61%      to this predicate to fetch more results.
   62%
   63%  The rest of the provided Options are passed to sourcehut_graphql/4.
   64sourcehut_builds_jobs(UserName, Jobs, Options) :-
   65    option(cursor(Cursor), Options, null),
   66    sourcehut_graphql(
   67        query {
   68            userByName(username:UserName) {
   69                jobs(cursor:Cursor) {
   70                    cursor,
   71                    results {
   72                        id,
   73                        created,
   74                        updated,
   75                        status,
   76                        note,
   77                        tags,
   78                        image,
   79                        runner,
   80                        tasks {
   81                            id,
   82                            created,
   83                            updated,
   84                            name,
   85                            status
   86                        },
   87                        artifacts {
   88                            id,
   89                            created,
   90                            path,
   91                            size,
   92                            url
   93                        }
   94                    }
   95                }
   96            }
   97        },
   98        Dict,
   99        [service(builds)|Options]),
  100    get_dict(data, Dict, Data),
  101    get_dict(userByName, Data, User),
  102    get_dict(jobs, User, Jobs0),
  103    get_dict(cursor, Jobs0, Next),
  104    option(next(Next), Options, Next),
  105    get_dict(results, Jobs0, Jobs).
  106
  107
  108:- predicate_options(sourcehut_builds_job/3,
  109                     3,
  110                     [pass_to(sourcehut_graphql/4, 4)]).  111
  112%% sourcehut_builds_job(+Id, -Job, +Options) is semidet.
  113%
  114%  Unifies Job with a dict describing the build job with id Id.
  115%
  116%  Options are passed to sourcehut_graphql/4.
  117sourcehut_builds_job(Id, Job, Options) :-
  118    sourcehut_graphql(
  119        query {
  120            job(id:Id) {
  121                id,
  122                created,
  123                updated,
  124                status,
  125                note,
  126                manifest,
  127                tags,
  128                image,
  129                runner,
  130                tasks {
  131                    id,
  132                    created,
  133                    updated,
  134                    name,
  135                    status
  136                },
  137                artifacts {
  138                    id,
  139                    created,
  140                    path,
  141                    size,
  142                    url
  143                }
  144            }
  145        },
  146        Dict,
  147        [service(builds)|Options]),
  148    get_dict(data, Dict, Data),
  149    get_dict(job, Data, Job).
  150
  151
  152:- predicate_options(sourcehut_builds_submit/3,
  153                     3,
  154                     [pass_to(sourcehut_graphql/4, 4)]).  155
  156%% sourcehut_builds_submit(+Manifest, -Job, +Options) is semidet.
  157%
  158%  Submits a new build job with manifest Manifest, which is a YAML
  159%  formatted string. On success, unifies Job with a dict describing
  160%  the newly submitted build job.
  161%
  162%  Options are passed to sourcehut_graphql/4.
  163sourcehut_builds_submit(Manifest, Job, Options) :-
  164    sourcehut_graphql(
  165        mutation {
  166            submit(manifest:Manifest) {
  167                id,
  168                created,
  169                updated,
  170                status,
  171                image,
  172                runner,
  173                tasks {
  174                    id,
  175                    created,
  176                    updated,
  177                    name,
  178                    status
  179                },
  180                artifacts {
  181                    id,
  182                    created,
  183                    path,
  184                    size, url
  185                }
  186            }
  187        },
  188        Dict,
  189        [service(builds)|Options]),
  190    get_dict(data, Dict, Data),
  191    get_dict(submit, Data, Job).
  192
  193:- predicate_options(sourcehut_builds_cancel/3,
  194                     3,
  195                     [pass_to(sourcehut_graphql/4, 4)]).  196
  197%% sourcehut_builds_cancel(+Id, -Job, +Options) is semidet.
  198%
  199%  Cancels the pending build job with id Id.  formatted string. On
  200%  success, unifies Job with a dict describing the new state of the
  201%  canceled build job.
  202%
  203%  Options are passed to sourcehut_graphql/4.
  204sourcehut_builds_cancel(Id, Job, Options) :-
  205    sourcehut_graphql(
  206        mutation