1:- module(util, [
    2    make_context/2,     % +Parts, -Context
    3    non_empty/2,        % +Input, +Name
    4    non_empty/3,        % +Input, +Name, +ThrowIfEmpty
    5    extract_param/5     % +Params, -NewParams, +Name, -Value, +DefaultValue
    6]).

Utilities

author
- Hongxin Liang
license
- Apache License Version 2.0 */
   14:- use_module(library(lists)).
 make_context(+Parts, -Context) is det
Create an HTTP context.
   20make_context(Parts, Context) :-
   21    (   is_list(Parts)
   22    ->  Parts1 = Parts
   23    ;   Parts1 = [Parts]
   24    ),
   25    remove_empty_atom(Parts1, Parts2),
   26    atomic_list_concat([''|Parts2], /, Context).
   27
   28remove_empty_atom([], []) :- !.
   29remove_empty_atom([H|T], L) :-
   30    H = '', !,
   31    remove_empty_atom(T, L).
   32remove_empty_atom([H|T], L) :-
   33    remove_empty_atom(T, L0),
   34    L = [H|L0].
 non_empty(+Input, +Name) is det
 non_empty(+Input, +Name, +ThrowIfEmpty) is det
Throw an exception if = Input = is empty atom or empty list and = ThrowIfEmpty = is = true =.
   42non_empty(Input, Name) :-
   43    non_empty(Input, Name, true).
   44
   45non_empty(Input, Name, ThrowIfEmpty) :-
   46    once((Input = ''; Input = [])), !,
   47    (   ThrowIfEmpty
   48    ->  atomic_list_concat(['Empty value passed for a required argument \'',
   49            Name, '\'.'], Message),
   50        throw(error(plasticsearch_exception(na, Message)))
   51    ).
   52
   53non_empty(_, _, _).
 extract_param(+Params, -NewParams, +Name, -Value, +DefaultValue) is det
Extract parameter from dictionary and return = DefaultValue = is the specified parameter does not exist.
   60extract_param(Params, NewParams, Name, Value, DefaultValue) :-
   61    (   del_dict(Name, Params, Value, NewParams)
   62    ->  true
   63    ;   Value = DefaultValue,
   64        NewParams = Params
   65    )