1:- module(response,[
    2    body/2,
    3    content_type/2,
    4    exists/1,
    5    exists/2,
    6    status_code/2,
    7    well_formed/1
    8]).    9
   10
   11:- use_module(library(error), []).   12:- use_module(library(record)).   13
   14:- multifile error:has_type/2.   15error:has_type(response, Response) :-
   16    response:well_formed(Response).
   17
   18:- record response(    status_code:integer,    content_type:atom,    body:stream).
 exists(-Response:response) is det
Unifies Response with an empty response term.
   27exists(Response) :-
   28    default_response(Response).
 exists(-Response:response, +Attributes:list(pair)) is det
Unifies Response with a fresh response term that has the given named Attributes.
   34exists(Response,Attributes) :-
   35    maplist(term_pair,Terms,Attributes),
   36    make_response(Terms,Response).
   37
   38term_pair(Term,Name-Value) :-
   39    Term =.. [Name, Value].
 well_formed(+Response) is semidet
True if Response is a proper response term.
   45well_formed(Response) :-
   46    is_response(Response).
 body(+Response:response, -Stream:stream) is det
body(?Response:response, +Stream:stream) is semidet
True if Response body can be read from Stream.
   53body(Response, Stream) :-
   54    response_body(Response,Stream).
 content_type(+Response:response, -ContentType:atom) is det
content_type(?Response:response, +ContentType:atom) is semidet
True if Response includes a Content-Type header whose value is ContentType.
   61content_type(Response, Type) :-
   62    response_content_type(Response,Type).
 status_code(+Response:response, -Code:integer) is det
status_code(?Response:response, +Code:integer) is semidet
True if Response has the HTTP status Code.
   69status_code(Response,Code) :-
   70    response_status_code(Response,Code)