GitLab API helper to obtain releases

This module requests a list of releases from the GitLab API and produces their '.zip' URLs

author
- Sylvain Soliman
license
- BSD-2 */
   11:- module(gitlabci,
   12         [
   13           create_gitlab_releases_page/1,
   14           create_gitlab_releases_page/2,
   15           find_releases/3,
   16           download_file/1,
   17           write_html/3
   18         ]).   19
   20:- use_module(library(http/http_open)).   21:- use_module(library(http/html_write)).   22:- use_module(library(http/json)).
 create_gitlab_releases_page(+OutputFile) is det
Create a release page like create_gitlab_releases_page/2 relying on default options
   28create_gitlab_releases_page(OutputFile) :-
   29  create_gitlab_releases_page(OutputFile, []).
 create_gitlab_releases_page(+OutputFile, +Options) is det
Create a pack releases page using Options and defaulting to Gitlab CI predefined environment variables.
   36create_gitlab_releases_page(OutputFile, Options) :-
   37  get_gitlab_env(Env),
   38  file_directory_name(OutputFile, Dir),
   39  file_base_name(OutputFile, BaseFile),
   40  merge_options(Options, Env, FullOptions),
   41  option(server(Server), FullOptions),
   42  option(id(Id), FullOptions),
   43  option(title(Title), FullOptions),
   44  setup_call_cleanup(
   45    working_directory(Old, Dir),
   46    (
   47      find_releases(Server, Id, Releases),
   48      forall(
   49        member(R, Releases),
   50        download_file(R)
   51      ),
   52      write_html(Title, Releases, BaseFile)
   53    ),
   54    working_directory(Dir, Old)
   55  ).
 git_gitlab_env(-Env) is det
Add in Env a list of all options we get from the environment.
   61get_gitlab_env(Env) :-
   62  get_gitlab_env([], 'CI_SERVER_HOST', server, E1),
   63  get_gitlab_env(E1, 'CI_PROJECT_ID', id, E2),
   64  get_gitlab_env(E2, 'CI_PROJECT_TITLE', title, Env).
 get_gitlab_env(+L, +Var, +Option, -LL) is det
Add to L the option named Option and with value the environment variable Var if it exists.
   71get_gitlab_env(L, Var, Option, [Term | L]) :-
   72  getenv(Var, Value),
   73  !,
   74  Term =.. [Option, Value].
   75
   76get_gitlab_env(L, _, _, L).
 find_releases(+Domain, +ProjectID, -Releases:List) is det
find a list of '.zip' release URLs from GitLab API
   82find_releases(Domain, ProjectID, Releases) :-
   83  atomic_list_concat(['', api, v4, projects, ProjectID, releases], /, Path),
   84  uri_components(ApiUri, uri_components(https, Domain, Path, _, _)),
   85  setup_call_cleanup(
   86    http_open(ApiUri, In, []),
   87    json_read_dict(In, Dicts),
   88    close(In)
   89  ),
   90  findall(
   91    Release,
   92    (
   93      member(Dict, Dicts),
   94      member(R, Dict.assets.sources),
   95      .(R, format, "zip"),
   96      .(R, url, Release)
   97    ),
   98    Releases
   99  ).
 download_file(+ReleaseUrl) is det
Download ReleaseUrl in wget style
  105download_file(Url) :-
  106  basename(Url, BaseName),
  107  setup_call_cleanup(
  108    (
  109      http_open(Url, In, []),
  110      open(BaseName, write, Out, [type(binary)])
  111    ),
  112    copy_stream_data(In, Out),
  113    (
  114      close(In),
  115      close(Out)
  116    )
  117  ).
 basename(+Url, -BaseName) is det
BaseName is the last component of Url
  123basename(Url, BaseName) :-
  124  uri_components(Url, uri_components(_, _, Path, _, _)),
  125  atomic_list_concat(L, /, Path),
  126  last(L, BaseName).
 write_html(+Title, +Releases:List, +OutputFile) is det
Write in OutputFile the HTML document with all links in Releases use Title as Title
  133write_html(Title, Releases, OutputFile) :-
  134  maplist(basename, Releases, Basenames),
  135  maplist(linkify, Basenames, Links),
  136  phrase(page(title(Title), Links), Tokens),
  137  setup_call_cleanup(
  138    open(OutputFile, write, Stream),
  139    print_html(Stream, Tokens),
  140    close(Stream)
  141  ).
 linkify(+X, -Y) is det
Y is an HTML paragraph containing a link to X
  147linkify(X, p(a(href(X), X)))