1:- module(
    2  http_pagination,
    3  [
    4    http_pagination_header/1, % +Page
    5    http_pagination_json/1,   % +Page
    6    http_pagination_link/3,   % +Page, +Relation, -Uri
    7    http_pagination_links/2   % +Page, -Links
    8  ]
    9).

Support for HTTP pagination

*/

   15:- use_module(library(http/json)).   16:- use_module(library(settings)).   17
   18:- use_module(library(dict)).   19:- use_module(library(pagination)).   20:- use_module(library(rest_server), []). % HTTP parameter hook
   21:- use_module(library(uri_ext)).   22
   23:- multifile
   24    http:param/2.   25
   26http:param(page, [
   27  default(1),
   28  description("The page number from the results set."),
   29  positive_integer
   30]).
   31http:param(page_size, [
   32  between(1, MaxPageSize),
   33  default(DefaultPageSize),
   34  description("The number of results per full result set page.")
   35]) :-
   36  setting(pagination:default_page_size, DefaultPageSize),
   37  setting(pagination:maximum_page_size, MaxPageSize).
 http_pagination_header(+Page:dict) is semidet
   45http_pagination_header(Page) :-
   46  http_pagination_links(Page, Links),
   47  format("Link: "),
   48  http_pagination_header_values(Links),
   49  nl.
   50
   51http_pagination_header_values([]) :- !.
   52http_pagination_header_values([H]) :- !,
   53  http_pagination_header_value(H).
   54http_pagination_header_values([H|T]) :- !,
   55  http_pagination_header_value(H),
   56  format(", "),
   57  http_pagination_header_values(T).
   58
   59http_pagination_header_value(Relation-Uri) :-
   60  format('<~a>; rel="~a"', [Uri,Relation]).
 http_pagination_json(+Page:dict) is det
   66http_pagination_json(Page) :-
   67  format("Content-Type: application/json; charset=UTF-8\n"),
   68  http_pagination_header(Page),
   69  nl,
   70  json_write_dict(current_output, Page.results).
 http_pagination_link(+Page:dict, +Relation:atom, -Uri:atom) is semidet
http_pagination_link(+Page:dict, -Relation:atom, -Uri:atom) is nondet
   77http_pagination_link(Page, Relation, Uri) :-
   78  pagination_page(Page, Relation, PageNumber),
   79  dict_get(query, Page, [], Query1),
   80  (   dict_get(page_size, Page, PageSize)
   81  ->  Query2 = [page_size(PageSize)|Query1]
   82  ;   Query2 = Query1
   83  ),
   84  uri_comps(Page.uri, uri(Scheme,Auth,Segments,_,_)),
   85  uri_comps(Uri, uri(Scheme,Auth,Segments,[page(PageNumber)|Query2],_)).
 http_pagination_links(+Page:dict, -Links:list(pair(atom))) is det
Returns the Page for the given pagination Page.
Arguments:
Pairs- are of the form `Relation-Uri'.
   95http_pagination_links(Page, Links) :-
   96  findall(
   97    Relation-Uri,
   98    http_pagination_link(Page, Relation, Uri),
   99    Links
  100  )