1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2018-2024, VU University Amsterdam
    7                              CWI, Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(openapi,
   38          [ openapi_dispatch/1,                 % :Request
   39            openapi_server/2,                   % +File, +Options
   40            openapi_client/2,                   % +File, +Options
   41
   42            openapi_doc/3,                      % +File, +Mode, +Options
   43            openapi_arg/4                       % :PredName, ?Index, ?Name, ?Type
   44          ]).   45:- use_module(library(apply)).   46:- use_module(library(apply_macros), []).   47:- use_module(library(debug)).   48:- use_module(library(option)).   49:- use_module(library(error)).   50:- use_module(library(base64)).   51:- use_module(library(sgml)).   52:- use_module(library(lists)).   53:- use_module(library(pairs)).   54:- use_module(library(yaml)).   55:- use_module(library(uri)).   56:- use_module(library(dcg/basics)).   57:- use_module(library(http/json)).   58:- use_module(library(http/http_json)).   59:- use_module(library(http/http_parameters)).   60:- use_module(library(http/http_header)).   61:- use_module(library(listing), [portray_clause/2, portray_clause/1]).   62:- use_module(library(pprint), [print_term/2]).   63:- use_module(library(http/http_open)).   64:- use_module(library(pcre), [re_match/3]).   65:- use_module(library(dcg/high_order), [sequence/5]).   66
   67                                                % generated code.

OpenAPI (Swagger) library

This library implements generating server and client code from an OpenAPI specification. The generated code generates or extracts parameters from the path, request or request body and type-checks parameters as well as responses. */

   77:- meta_predicate
   78    openapi_dispatch(:),
   79    openapi_arg(:, ?, ?, ?).
 openapi_server(+File, +Options)
Instantiate a REST server given the OpenAPI specification in File. Normally, use `swipl-openapi --server=server.pl spec.yaml` to create a file that uses this directive and generates documentation for the server operations as well as a skeleton predicate.
   88openapi_server(File, Options) :-
   89    throw(error(context_error(nodirective, openapi_server(File, Options)), _)).
   90
   91expand_openapi_server(File, Options,
   92                      [ (:- discontiguous((openapi_handler/11,
   93                                           openapi_doc/2))),
   94                        (:- multifile((openapi_error_hook/3)))
   95                      | Clauses
   96                      ]) :-
   97    read_openapi_spec(File, Spec, Options, Options1),
   98    phrase(server_clauses(Spec, Options1), Clauses).
 openapi_client(+File, +Options)
Instantiate a REST client given the OpenAPI specification in File. Normally use `swipl-openapi --client=client.pl spec.yaml` to create a file that uses this directive and contains documentation for the generated predicates.
  107openapi_client(File, Options) :-
  108    throw(error(context_error(nodirective,
  109                              openapi_client(File, Options)), _)).
 expand_openapi_client(+File, +Options, -Clauses)
Generate clauses for the client. Currently also generates the server specification as this allows us to use the same code for generating the documentation.
  117expand_openapi_client(File, Options, AllClauses) :-
  118    AllClauses = [ (:- discontiguous(openapi_type/1))
  119                 | Clauses
  120                 ],
  121    read_openapi_spec(File, Spec, Options, Options1),
  122    phrase(client_clauses(Spec, Options1), Clauses).
 read_openapi_spec(+File, -Spec, +Options0, -Options) is det
  126read_openapi_spec(File, Spec, Options0, [yaml(Spec)|Options]) :-
  127    (   prolog_load_context(directory, Dir)
  128    ->  true
  129    ;   Dir = '.'
  130    ),
  131    absolute_file_name(File, Path,
  132                       [ relative_to(Dir),
  133                         extensions(['',json,yaml]),
  134                         access(read)
  135                       ]),
  136    uri_file_name(BaseURI, Path),
  137    openapi_read(Path, Spec),
  138    merge_options(Options0, [base_uri(BaseURI)], Options).
 openapi_read(+File, -Term) is det
Read an OpenAPI specification file.
  144openapi_read(File, Term) :-
  145    file_name_extension(_, yaml, File),
  146    !,
  147    setup_call_cleanup(
  148        open(File, read, In, [encoding(utf8)]),
  149        yaml_read(In, Term),
  150        close(In)).
  151openapi_read(File, Term) :-
  152    setup_call_cleanup(
  153        open(File, read, In, [encoding(utf8)]),
  154        json_read_dict(In, Term),
  155        close(In)).
  156
  157		 /*******************************
  158		 *       SERVER COMPILER	*
  159		 *******************************/
 server_clauses(+JSONTerm, +Options)//
Grammar to generate clauses that control openapi/1. Options processed:
base_uri(+URI)
Base URI for resolving types.
type_check_response(+Boolean)
Check the response JSON against the schema (default true)
format_response(+Boolean)
If true (default false), generate JSON with a nice layout.
  174server_clauses(JSONTerm, Options) -->
  175    { dict_pairs(JSONTerm.paths, _, Paths)
  176    },
  177    root_clause(JSONTerm.servers, Options),
  178    server_config_clauses(Options),
  179    server_path_clauses(Paths, Options),
  180    json_schema_clauses(JSONTerm, Options).
  181
  182root_clause(_, Options) -->
  183    { option(server_url(ServerURL), Options),
  184      !,
  185      uri_components(ServerURL, Components),
  186      uri_data(path, Components, Root)
  187    },
  188    !,
  189    [ openapi_root(Root) ].
  190root_clause([Server|_], _Options) -->
  191    { uri_components(Server.url, Components),
  192      uri_data(path, Components, Root)
  193    },
  194    [ openapi_root(Root) ].
  195
  196server_config_clauses(Options) -->
  197    { findall(Clause, server_config(Clause, Options), Clauses) },
  198    string(Clauses).
  199
  200server_config(openapi_server_config(type_check_response(Mode)), Options) :-
  201    option(type_check_response(Mode), Options, true).
  202server_config(openapi_server_config(reply_json_options(Opts)), Options) :-
  203    (   option(format_response(false), Options, false)
  204    ->  Opts = [width(0)]
  205    ;   Opts = []
  206    ).
  207
  208server_path_clauses([], _) --> [].
  209server_path_clauses([H|T], Options) -->
  210    (   server_path_clause(H, Options)
  211    ->  []
  212    ;   { error(openapi(path_failed, H), Options),
  213          start_debugger
  214        }
  215    ),
  216    server_path_clauses(T, Options).
  217
  218server_path_clause(Path-Spec, Options) -->
  219    { dict_pairs(Spec, _, Methods0),
  220      (   selectchk(parameters-Parms0, Methods0, Methods)
  221      ->  deref(Parms0, Parms, Options),
  222          Options1 = [parameters(Parms)|Options]
  223      ;   Methods = Methods0,
  224          Options1 = Options
  225      )
  226    },
  227    path_handlers(Methods, Path, Options1).
  228
  229path_handlers([], _Path, _) --> [].
  230path_handlers([Method-Spec|T], Path, Options) -->
  231    { path_handler(Path, Method, Spec, Fact, Options),
  232      path_docs(Method, Path, Spec, Docs, Options)
  233    },
  234    [Fact, Docs],
  235    path_handlers(T, Path, Options).
 path_handler(+Path, +Method, +Spec, -Handler, +Options) is det
Gather information about Method for Path from the YAML term Spec that describes this pair.
  242path_handler(Path, Method, Spec,
  243             openapi_handler(Method, PathList, SegmentMatches,
  244                             Request, HdrParams, AsOption, OptionParam,
  245                             Content, Responses, Security, Handler),
  246             Options) :-
  247    path_vars(Path, PathList, PathBindings),
  248    (   spec_parameters(Spec, ParamSpecs, Options)
  249    ->  server_parameters(ParamSpecs, PathBindings, SegmentMatches,
  250                          Request, AsOption, TypeAndArgs0, HdrParams,
  251                          [ path(Path),
  252                            method(Method)
  253                          | Options
  254                          ]),
  255        (   AsOption == []
  256        ->  OptionParams = []
  257        ;   OptionParams = [OptionParam]
  258        )
  259    ;   PathBindings == []
  260    ->  SegmentMatches = [],
  261        TypeAndArgs0 = [],
  262        HdrParams = [],
  263        Request = [],
  264        AsOption = [],
  265        OptionParams = []
  266    ;   error(openapi(not_covered_path_vars(Method, Path, PathBindings)),
  267              Options),
  268        fail
  269    ),
  270    content_parameter(Method, Spec, Content, TypeAndArgs0, TypeAndArgs, Options),
  271    maplist(arg(1), TypeAndArgs, Args),
  272    append(Args, [Result|OptionParams], AllArgs),
  273    dict_pairs(Spec.responses, _, ResPairs),
  274    maplist(response(Result, Options), ResPairs, Responses),
  275    spec_security(Spec, Security, Options),
  276    handler_predicate(Method, Path, Spec, PredName, Options),
  277    Handler =.. [PredName|AllArgs].
  278
  279spec_parameters(Spec, Parameters, Options) :-
  280    option(parameters(Common), Options, []),
  281    (   Me0 = Spec.get(parameters)
  282    ->  deref(Me0, Me, Options)
  283    ;   Me = []
  284    ),
  285    append(Common, Me, Parameters),
  286    Parameters \== [].
 server_parameters(+ParamSpecs, +PathBindings, -SegmentMatches, -RequestParams, -RequestOptions, -HandlerArgs, -HeaderOptions, +Options) is det
Arguments:
HandlerArgs- is a list of a(Var,Name,Type) for the positional input arguments of the server handler predicates.
  295server_parameters([], _, [], [], [], [], [], _).
  296server_parameters([H|T], PathB, Segs, Request, AsOption, Args, HdrOpts, Options) :-
  297    _{name:NameS, in:"query"} :< H,
  298    !,
  299    phrase(http_param_options(H, Options), Opts),
  300    atom_string(Name, NameS),
  301    R0 =.. [Name,P0,Opts],
  302    (   Opts = [optional(true)|_],
  303        \+ option(optional(unbound), Options)
  304    ->  AsOption = [R0|AsOpts],
  305        server_parameters(T, PathB, Segs, Request, AsOpts, Args, HdrOpts, Options)
  306    ;   Request = [R0|Req],
  307        param_type(H, Type, Options),
  308        Args  = [a(P0,Name,Type)|MoreArgs],
  309        server_parameters(T, PathB, Segs, Req, AsOption, MoreArgs, HdrOpts, Options)
  310    ).
  311server_parameters([H|T], PathB, [segment(Type, Seg, A0, Name, Descr)|Segs],
  312                  Req, AsOption, [a(A0,Name,Type)|Args], HdrOpts, Options) :-
  313    _{name:NameS, in:"path"} :< H,
  314    !,
  315    atom_string(Name, NameS),
  316    (   memberchk(Name=Seg, PathB)
  317    ->  param_type(H, Type, Options),
  318        param_description(H, Descr)
  319    ;   option(path(Path), Options),
  320        option(method(Method), Options),
  321        error(openapi(missing_path_parameter(Method, Name, Path)), Options),
  322        fail
  323    ),
  324    server_parameters(T, PathB, Segs, Req, AsOption, Args, HdrOpts, Options).
  325server_parameters([H|T], PathB, Segs, Req, AsOption, Args, [R0|HdrOpts], Options) :-
  326    _{name:NameS, in:"header"} :< H,
  327    !,
  328    phrase(http_param_options(H, Options), Opts),
  329    atom_string(Name, NameS),
  330    R0 =.. [Name,A0,Opts],
  331    (   Opts = [optional(true)|_],
  332        \+ option(optional(unbound), Options)
  333    ->  AsOption = [R0|AsOpts],
  334        server_parameters(T, PathB, Segs, Req, AsOpts, Args, HdrOpts, Options)
  335    ;   param_type(H, Type, Options),
  336        Args  = [a(A0,Name,Type)|MoreArgs],
  337        server_parameters(T, PathB, Segs, Req, AsOption, MoreArgs, HdrOpts, Options)
  338    ).
  339server_parameters([H|T], PathB, Segs, Request, AsOption, Args, HdrOpts, Options) :-
  340    deref(H, Param, Options),
  341    !,
  342    server_parameters([Param|T], PathB, Segs, Request, AsOption, Args, HdrOpts, Options).
  343server_parameters([H|_], _PathB, _Segments, _Req, _AsOption, _, _HdrOpts, Options) :-
  344    error(openapi(parameter_failed(H)), Options),
  345    fail.
  346
  347http_param_options(Spec, Options) -->
  348    hp_optional(Spec),
  349    hp_type(Spec, Options),
  350    hp_description(Spec).
  351
  352hp_optional(Spec) -->
  353    { param_optional(Spec, optional) },
  354    !,
  355    [optional(true)].
  356hp_optional(_) --> [].
  357
  358hp_type(Spec, Options) -->
  359    hp_schema(Spec.get(schema), Options),
  360    !.
  361hp_type(_, _) --> [].
  362
  363hp_schema(Spec, Options) -->
  364    { json_type(Spec, Type, Options),
  365      json_param_type(Type, ParmType)
  366    },
  367    !,
  368    [ ParmType ].
  369hp_schema(_Spec, _Options) -->
  370    { start_debugger_fail }.
  371
  372json_param_type(array(Type, _), list(openapi(Type))) :- !.
  373json_param_type(Type, openapi(Type)).
  374
  375hp_description(Spec) -->
  376    { Descr = Spec.get(description) },
  377    !,
  378    [ description(Descr) ].
  379hp_description(_) --> [].
  380
  381deref(Spec, Yaml, Options) :-
  382    is_dict(Spec),
  383    _{'$ref':URLS} :< Spec,
  384    sub_atom(URLS, 0, _, _, './'),
  385    !,
  386    option(base_uri(Base), Options),
  387    uri_normalized(URLS, Base, URL),
  388    url_yaml(URL, Yaml).
  389deref(Spec, Yaml, Options) :-
  390    is_dict(Spec),
  391    _{'$ref':Ref} :< Spec,
  392    atomic_list_concat(Segments, /, Ref),
  393    !,
  394    option(yaml(Doc), Options),
  395    yaml_subdoc(Segments, Doc, Yaml).
  396deref(Yaml, Yaml, _).
  397
  398yaml_subdoc([], Doc, Doc).
  399yaml_subdoc([H|T], Doc, Sub) :-
  400    (   (H == '' ; H == '#')
  401    ->  Sub0 = Doc
  402    ;   Sub0 = Doc.H
  403    ),
  404    yaml_subdoc(T, Sub0, Sub).
 path_docs(+Method, +Path, +Spec, -Docs) is det
Generate documentation clauses for an operationId
  410path_docs(Method, Path, Spec,
  411          openapi_doc(OperationID, [path(Path)|Docs]),
  412          Options) :-
  413    handler_predicate(Method, Path, Spec, OperationID, [warn(false)|Options]),
  414    phrase(path_doc(Spec), Docs).
 path_doc(+Spec)//
Generate a list of documentation properties for Path
  420path_doc(Spec) -->
  421    path_doc(summary, Spec),
  422    path_doc(description, Spec),
  423    path_doc(tags, Spec).
  424
  425path_doc(Key, Spec) -->
  426    { Value = Spec.get(Key),
  427      !,
  428      Attr =.. [Key,Value]
  429    },
  430    [Attr].
  431path_doc(_, _) --> [].
 path_vars(+PathSpec, -Segments, -Bindings) is det
Convert a path specification holding {Name} into a list of Segments, where each Segment is an atom or a variable. Bindings is a list of Name=Var, e.g.
?- path_vars('/aap/{noot}/mies', Segs, B).
Segs = ['/aap/', _A, '/mies'],
B = [noot=_A].
  444path_vars(PathSpec, Segments, Bindings) :-
  445    string_codes(PathSpec, Codes),
  446    phrase(path_vars(Segments, Bindings), Codes).
  447
  448path_vars([Segment,Var|Segments], [VarName=Var|Bindings]) -->
  449    string(SegCodes), "{", string(VarCodes), "}",
  450    !,
  451    { atom_codes(Segment, SegCodes),
  452      atom_codes(VarName, VarCodes)
  453    },
  454    path_vars(Segments, Bindings).
  455path_vars(Segments, []) -->
  456    remainder(Codes),
  457    {   Codes == []
  458    ->  Segments = []
  459    ;   atom_codes(Segment, Codes),
  460        Segments = [Segment]
  461    }.
 match_path_list(+PathList, +Path) is semidet
Where PathList is a list of atoms and variables and Path is an atom. Bind the variables such that the concatenation of PathList results in Path. Each variable is bound to a string.
  469match_path_list([], "").
  470match_path_list([Path], Path) :-
  471    !.
  472match_path_list([Atom], String) :-
  473    !,
  474    atom_string(Atom, String).
  475match_path_list([H|T], Path) :-
  476    nonvar(H),
  477    !,
  478    string_concat(H, Rest, Path),
  479    match_path_list(T, Rest).
  480match_path_list([V,H|T], Path) :-
  481    assertion(nonvar(H)),
  482    sub_string(Path, B, _, A, H),
  483    sub_string(Path, 0, B, _, V),
  484    sub_string(Path, _, A, 0, Rest),
  485    match_path_list(T, Rest),
  486    !.
 content_parameter(+Method, +Spec, -Content, +ArgAndTypes0, -ArgAndTypes, +Options) is det
If there is a request body, add it to the parameter list and return a specification for openapi_dispatch/1 in Content.
  494content_parameter(Method, Spec, content(MediaType, Schema, Var, Descr),
  495                  Args, AllArgs, Options) :-
  496    has_content(Method),
  497    !,
  498    request_content_type(Spec, MediaType, Schema, Options),
  499    content_description(Spec, Descr),
  500    append(Args, [a(Var,'RequestBody',Schema)], AllArgs).
  501content_parameter(_, _, -, Args, Args, _).
  502
  503has_content(post).
  504has_content(put).
  505
  506content_description(JSON, Descr) :-
  507    Descr = JSON.get(requestBody).get(description),
  508    !.
  509content_description(_JSON, "").
  510
  511request_content_type(Spec, MediaType, Schema, Options) :-
  512    (   Body = Spec.get(requestBody)
  513    ->  true
  514    ;   Body = _{}
  515    ),
  516    !,
  517    content_type(Body, MediaType, Schema, Options).
 response(+ResultVar, +Options, +ResponsePair, -Response) is det
Describe the valid responses. Response is a term
response(Code, As, MediaType, Type, Result, Descr)
Where
  • Code is the numeric HTTP status code or a variable for default
  • As describes how to handle the code. Currently one of data or error
  • MediaType is the expected response type
  • Type is the (JSON) schema describing a JSON result
  • Result is the result variable
  • Descr is the description of the response body.
  534response(Result, Options, CodeA-Spec,
  535         response(Code, As, MediaType, Type, Result, Descr)) :-
  536    response_code(CodeA, Code, As),
  537    response_description(Spec, Descr),
  538    content_type(Spec, MediaType, Type, Options).
  539
  540response_code(default, _, error) :- !.
  541response_code(A, N, data) :-
  542    to_number(A, N).
  543
  544response_description(Spec, Descr) :-
  545    Descr = Spec.get(description),
  546    !.
  547response_description(_, "") .
 content_type(+Sec, -BodyType, -Schema, +Options) is det
Find the ContentType for the request body and, if applicable, its schema.
  554content_type(_Spec, media(application/json, []), Type, Options) :-
  555    option(type_check_request(false), Options),
  556    !,
  557    Type = (-).
  558content_type(Spec, media(application/json, []), Type, Options) :-
  559    Content = Spec.get(content),
  560    Media = Content.get('application/json'),
  561    !,
  562    (   Schema = Media.get(schema)
  563    ->  json_type(Schema, Type, Options)
  564    ;   Type = (-)
  565    ).
  566content_type(_Spec, media(Type, []), -, Options) :-
  567    option(default_request_body_type(Type0), Options),
  568    !,
  569    to_content_type(Type0, Type).
  570content_type(_Spec, media(application/json, []), -, _).
  571
  572to_content_type(Type0, Main/Sub) :-
  573    atomic(Type0),
  574    atomic_list_concat([Main,Sub], /, Type0),
  575    !.
  576to_content_type(Type, Type) :-
  577    Type = Main/Sub,
  578    must_be(atom, Main),
  579    must_be(atom, Sub).
  580to_content_type(Type, _) :-
  581    type_error(content_type, Type).
  582
  583
  584		 /*******************************
  585		 *       CLIENT COMPILER	*
  586		 *******************************/
 client_clauses(+JSONTerm, +Options)//
Generate clauses for the client. The generated clauses are:
  604client_clauses(JSONTerm, Options) -->
  605    { dict_pairs(JSONTerm.paths, _, Paths)
  606    },
  607    server_url_clauses(JSONTerm.servers, Options),
  608    client_path_clauses(Paths, Options),
  609    json_schema_clauses(JSONTerm, Options).
  610
  611server_url_clauses(_Servers, Options) -->
  612    { option(server_url(ServerURL), Options)
  613    },
  614    !,
  615    [ openapi_server(ServerURL) ].
  616server_url_clauses(Servers, _Options) -->
  617    server_url_clauses(Servers).
  618
  619server_url_clauses([]) --> [].
  620server_url_clauses([H|T]) --> server_url_clauses(H), server_url_clauses(T).
  621
  622server_url_clauses(Server) -->
  623    [ openapi_server(Server.get(url)) ].
  624
  625client_path_clauses([], _) --> [].
  626client_path_clauses([H|T], Options) -->
  627    (   client_path_clause(H, Options)
  628    ->  []
  629    ;   { error(openapi(path_failed, H), Options) }
  630    ),
  631    client_path_clauses(T, Options).
  632
  633client_path_clause(Path-Spec, Options) -->
  634    { dict_pairs(Spec, _, Methods0),
  635      (   selectchk(parameters-Parms, Methods0, Methods)
  636      ->  Options1 = [parameters(Parms)|Options]
  637      ;   Methods = Methods0,
  638          Options1 = Options
  639      )
  640    },
  641    client_handlers(Methods, Path, Options1).
  642
  643client_handlers([], _, _) --> [].
  644client_handlers([H|T], Path, Options) -->
  645    { client_handler(H, Path, Clause, TypeClause, Options) },
  646    [Clause, TypeClause],
  647    client_handlers(T, Path, Options).
  648
  649:- det(client_handler/5).  650client_handler(Method-Spec, PathSpec, (Head :- Body), openapi_type(TypeHead), Options) :-
  651    path_vars(PathSpec, PathList, PathBindings),
  652    handler_predicate(Method, PathSpec, Spec, PredName, Options),
  653    (   spec_parameters(Spec, ParamSpecs, Options)
  654    ->  client_parameters(ParamSpecs, PathBindings,
  655                          ArgAndTypes, HdrParams, Query, Optional,
  656                          CheckParams,
  657                          [ path(PathSpec),
  658                            method(Method)
  659                          | Options
  660                          ]),
  661        (   Optional == []
  662        ->  ClientOptionArgs = []
  663        ;   ClientOptionArgs = [ClientOptions]
  664        )
  665    ;   PathBindings == []
  666    ->  ArgAndTypes = [],
  667        Query = [],
  668        CheckParams = true,
  669        Optional = [],
  670        ClientOptionArgs = [],
  671        HdrParams = []
  672    ;   error(openapi(not_covered_path_vars(Method, PathSpec, PathBindings)),
  673              Options),
  674        fail
  675    ),
  676    content_parameter(Method, Spec, Content, ArgAndTypes, ArgAndTypes1, Options),
  677    maplist(arg(1), ArgAndTypes1, Args),
  678    maplist(client_arg, ArgAndTypes1, ClientArgs),
  679    TypeHead =.. [PredName|ClientArgs],
  680    request_body(Method, PathSpec, Module, Content, ContentGoal, RequestOptions),
  681    dict_pairs(Spec.responses, _, ResPairs),
  682    maplist(response(Result, Options), ResPairs, Responses),
  683    (   response_has_data(Responses)
  684    ->  ResultArgs = [Result]
  685    ;   ResultArgs = []
  686    ),
  687    append([ Args,
  688             ResultArgs,
  689             ClientOptionArgs
  690           ], AllArgs),
  691    spec_security(Spec, Security, Options),
  692    prolog_load_context(module, Module),
  693    (   PathBindings == []
  694    ->  Path = PathSpec,
  695        PathGoal = true
  696    ;   PathGoal = atomic_list_concat(PathList, Path)
  697    ),
  698    Head =.. [PredName|AllArgs],
  699    Body = ( CheckParams, PathGoal, ContentGoal,
  700             openapi:assemble_query(Module, Method, Path,
  701                                    HdrParams, Query, Optional, ClientOptions,
  702                                    URL, HdrOptions),
  703             context_module(CM),
  704             openapi:assemble_security(Security, CM, SecOptions),
  705             append([ SecOptions,
  706                      RequestOptions,
  707                      HdrOptions
  708                    ], OpenOptions),
  709             debug(openapi(client), '~w ~w', [Method, URL]),
  710             setup_call_cleanup(
  711                 openapi:http_open(URL, In,
  712                           [ status_code(Status),
  713                             method(Method),
  714                             header(content_type, ContentType),
  715                             request_header(accept = 'application/json')
  716                           | OpenOptions
  717                           ]),
  718                 openapi:openapi_read_reply(Status, ContentType, Responses,
  719                                            In, Result),
  720                 close(In))
  721           ).
  722
  723:- det(client_arg/2).  724client_arg(a(_, Name, Type), ArgName:Type) :-
  725    camel_case(Name, ArgName).
 handler_predicate(+Method, +Path, +Spec, -PredicateName, +Options) is det
Generate a predicate name from a specification. Prefers the operationId.
  732handler_predicate(_, _, Spec, PredicateName, _Options) :-
  733    uncamel_case(Spec.get(operationId), PredicateName),
  734    !.
  735handler_predicate(Method, Path, _Spec, PredicateName, Options) :-
  736    atomic_list_concat(Segments, /, Path),
  737    reverse(Segments, RevSegments),
  738    member(Segment, RevSegments),
  739    \+ sub_atom(Segment, _, _, _, '{'),
  740    !,
  741    file_name_extension(Name, _, Segment),
  742    atomic_list_concat([Method, '_', Name], PredicateName),
  743    (   option(warn(true), Options, true)
  744    ->  warning(openapi(no_operation_id, Method, Path, PredicateName), Options)
  745    ;   true
  746    ).
 response_has_data(+Responses) is semidet
True if the request (may) return data. This is not the case if the only responses are 204 (no content) or error codes that are mapped to exceptions.
  755response_has_data(Responses) :-
  756    maplist(arg(1), Responses, Codes),
  757    member(Code, Codes),
  758    \+ code_has_no_data(Code), !.
  759
  760code_has_no_data(Code) :-
  761    var(Code).                                  % errors
  762code_has_no_data(204).                          % No content
 client_parameters(+Spec, +PathBindings, -ArgsAndTypes, -HdrParams, -Required, -Optional, -Check:callable, +Options)
Arguments:
Args- is a list of pairs a(Var,Name,Type) for required arguments of the client predicate.
Required- is a list of qparam(Name,P0,Type,Opt) used for adding query parameters for required parameters to the URL
Optional- is a list of qparam(Name,P0,Type,optional) used for adding query parameters for optional parameters to the URL
Check- is a callable term for validating the arguments,
  776client_parameters([], _, [], [], [], [], true, _).
  777client_parameters([H|T], PathBindings, [a(A0,Name,Type)|Args], HdrParams,
  778                  [qparam(Name,A0,Type,Opt)|Qs], Optional, Check, Options) :-
  779    _{name:NameS, in:"query"} :< H,
  780    param_optional(H, Opt),
  781    \+ ( Opt == optional,
  782         \+ option(optional(unbound), Options)
  783       ),
  784    !,
  785    param_type(H, Type, Options),
  786    atom_string(Name, NameS),
  787    client_parameters(T, PathBindings, Args, HdrParams, Qs, Optional, Check, Options).
  788client_parameters([H|T], PathBindings, [a(A0,Name,Type)|Args],
  789                  [hparam(Name,A0,Type,Opt)|HdrParams],
  790                  Query, Optional, Check, Options) :-
  791    _{name:NameS, in:"header"} :< H,
  792    param_optional(H, Opt),
  793    \+ ( Opt == optional,
  794         \+ option(optional(unbound), Options)
  795       ),
  796    !,
  797    param_type(H, Type, Options),
  798    atom_string(Name, NameS),
  799    client_parameters(T, PathBindings, Args, HdrParams, Query, Optional, Check, Options).
  800client_parameters([H|T], PathBindings,
  801                  Params, HdrParams, Query, [qparam(Name,_,Type,optional)|OptT],
  802                  Check, Options) :-
  803    _{name:NameS, in:"query"} :< H,
  804    !,
  805    param_type(H, Type, Options),
  806    atom_string(Name, NameS),
  807    client_parameters(T, PathBindings, Params, HdrParams,
  808                      Query, OptT, Check, Options).
  809client_parameters([H|T], PathBindings, Args,
  810                  [hparam(Name,_,Type,optional)|HdrParams], Query, Optional,
  811                  Check, Options) :-
  812    _{name:NameS, in:"header"} :< H,
  813    !,
  814    param_type(H, Type, Options),
  815    atom_string(Name, NameS),
  816    client_parameters(T, PathBindings, Args, HdrParams,
  817                      Query, Optional, Check, Options).
  818client_parameters([H|T], PathBindings, [a(A0,Name,Type)|Args],
  819                  HdrParams, Query, Opt, Check, Options) :-
  820    _{name:NameS, in:"path"} :< H,
  821    !,
  822    atom_string(Name, NameS),
  823    param_type(H, Type, Options),
  824    (   memberchk(Name=Segment, PathBindings)
  825    ->  Check1 = openapi:segment_value(Type, Segment, A0)
  826    ;   option(path(Path), Options),
  827        option(method(Method), Options),
  828        error(openapi(missing_path_parameter(Method, Name, Path)), Options),
  829        fail
  830    ),
  831    client_parameters(T, PathBindings, Args, HdrParams,
  832                      Query, Opt, Check0, Options),
  833    mkconj(Check0, Check1, Check).
  834client_parameters([H|T], PathBindings, Args, HdrParams,
  835                  Query, Opt, Check, Options) :-
  836    deref(H, Param, Options),
  837    !,
  838    client_parameters([Param|T], PathBindings, Args, HdrParams,
  839                      Query, Opt, Check, Options).
  840
  841param_optional(Spec, Optional) :-
  842    (   Spec.get(required) == false
  843    ->  Optional = optional
  844    ;   _Default = Spec.get(schema).get(default)
  845    ->  Optional = optional
  846    ;   Optional = required
  847    ).
  848
  849param_type(Spec, Type, Options) :-
  850    json_type(Spec.get(schema), Type, Options),
  851    !.
  852param_type(_Spec, any, _Options).
  853
  854param_description(Spec, Description) :-
  855    Description = Spec.get(description),
  856    !.
  857param_description(_Spec, "").
  858
  859mkconj(true, G, G) :- !.
  860mkconj(G, true, G) :- !.
  861mkconj(G1, G2,  (G1,G2)).
 request_body(+Method, +Path, +Module, +ContentSpec, -Goal, -HTTPOPenOptions) is det
Translate the request body into options for http_open/3.
  868request_body(Method, Path, Module,
  869	     content(media(application/json,_), Schema, InVar, _Descr),
  870             openapi:assemble_content(Module, Method, Path,
  871                                      json, Schema, InVar, OutVar),
  872             [ post(json(OutVar))
  873             ]) :-
  874    !.
  875request_body(Method, Path, Module,
  876	     content(media(multipart/'form-data',_), Schema, InVar, _Descr),
  877             openapi:assemble_content(Module, Method, Path,
  878                                      form_data, Schema, InVar, OutVar),
  879             [ post(form_data(OutVar))
  880             ]) :-
  881    !.
  882request_body(_, _, _, content(MediaType, _Schema, _Var, _Descr), _, _) :-
  883    !,
  884    domain_error(openapi(content_type), MediaType).
  885request_body(_, _, _, _, true, []).
  886
  887
  888		 /*******************************
  889		 *           SECURITY		*
  890		 *******************************/
 spec_security(+MethodSpec, -Security:list, +Options) is det
Decode the required authentication for sending a request. Security is a list of admissible authentication methods and has the following possible values:
public
No authentication needed. This is (with a warning) also emitted for schemes we do not yet support.
http(Scheme, Name, Args)
For http basic and http bearer authentications. Name is the name of the security scheme from the OpenAPI document.
api_key(header(Header),Name,Args)
We need to provide an api key in an additional header named Header. Name is the name of the security scheme from the OpenAPI document.
To be done
- Currently only deals with authorization we need in dealing with the hypothesis API.
  912spec_security(Spec, Security, Options) :-
  913    maplist(security(Options), Spec.get(security), Security),
  914    Security \== [],
  915    !.
  916spec_security(_, [public], _).
  917
  918security(Options, Sec, Security) :-
  919    dict_pairs(Sec, _, [Scheme-Args]),
  920    option(yaml(Doc), Options),
  921    yaml_subdoc([components, securitySchemes,Scheme], Doc, SchemeObj),
  922    security_scheme(Scheme, SchemeObj, Args, Security, Options).
  923security(_Options, Sec, public) :-
  924    dict_pairs(Sec, _, []),
  925    !.
  926
  927security_scheme(SchemeName, Dict, Args,
  928                http(Scheme, SchemeName, Args), _Options) :-
  929    _{type: "http", scheme: SchemeS} :< Dict,
  930    !,
  931    atom_string(Scheme, SchemeS).
  932security_scheme(SchemeName, Dict, Args,
  933                api_key(header(Name), SchemeName, Args), _Options) :-
  934    _{type: "apiKey", in: "header", name: NameS} :< Dict,
  935    !,
  936    atom_string(Name, NameS).
  937security_scheme(SchemeName, Dict, _, public, Options) :-
  938    warning(openapi(unknown_security_scheme(SchemeName, Dict)), Options).
  939
  940
  941		 /*******************************
  942		 *       RUNTIME SUPPORT	*
  943		 *******************************/
  944
  945:- public
  946    assemble_query/9,
  947    assemble_content/7.
 assemble_query(+Module, +Method, +Path, +HeaderParams, +QParams, +QOptional, +QOptions, -URL, -OpenOptions) is det
Arguments:
QOptions- is the option list of the client predicate.
  954assemble_query(Module, Method, Path, HeaderParams, QParams, QOptional, QOptions,
  955               URL, OpenOptions) :-
  956    call(Module:openapi_server(ServerBase)),
  957    convlist(client_query_param, QParams, QueryFromArgs),
  958    optional_query_params(QOptional, QOptions, QueryFromOptions),
  959    application_extra_query_parameters(Module, Method, Path, Extra),
  960    append([Extra, QueryFromArgs, QueryFromOptions], Query),
  961    (   Query == []
  962    ->  atomics_to_string([ServerBase, Path], URL)
  963    ;   phrase(array_query(Query), ArrayQuery),
  964        uri_query_components(QueryString, ArrayQuery),
  965        atomics_to_string([ServerBase, Path, "?", QueryString], URL)
  966    ),
  967    convlist(client_header_param(QOptions), HeaderParams, OpenOptions).
  968
  969assemble_content(Module, Method, Path, Format, Schema, In, Content) :-
  970    (   Schema == (-)
  971    ->  Content0 = In
  972    ;   json_check(Schema, Content0, In)
  973    ),
  974    (   current_predicate(Module:extend_content/5),
  975        Module:extend_content(Method, Path, json, Content0, Content1)
  976    ->  true
  977    ;   Content1 = Content0
  978    ),
  979    output_format(Format, Content1, Content).
  980
  981output_format(json, Content, Content).
  982output_format(form_data, Dict, Form) :-
  983    dict_pairs(Dict, _, FormPairs),
  984    maplist(form_entry, FormPairs, Form).
  985
  986form_entry(Name-Value, Name=Value).
 application_extra_query_parameters(+Module, +Method, +Path, -Extra) is det
Allow a client to specify additional query parameters that do not appear in the OpenAPI spec but apply to all methods. This is sometimes used to supply credentials.
  994application_extra_query_parameters(Module, Method, Path, Extra) :-
  995    current_predicate(Module:extra_query_parameters/3),
  996    Module:extra_query_parameters(Method, Path, Extra),
  997    !,
  998    must_be(list, Extra).
  999application_extra_query_parameters(_, _, _, []).
 array_query(Query)//
Rewrite Name=List into Name=E1, Name=E2, ... to support array(Type, Opts) for parameters passed as queries.
 1008array_query([]) --> [].
 1009array_query([Name=Value|T]) -->
 1010    (   {is_list(Value)}
 1011    ->  repeat_query(Value, Name)
 1012    ;   [Name=Value]
 1013    ),
 1014    array_query(T).
 1015
 1016repeat_query([], _) --> [].
 1017repeat_query([H|T], Name) -->
 1018    [ Name=H ],
 1019    repeat_query(T, Name).
 client_query_param(+Spec, -QueryElement) is det
Perform type validation and transformation for the client Prolog value to something suitable to pass onto uri_query_components/2.
 1026client_query_param(qparam(Name, PlValue, Type, _Required),
 1027                   Name = Value) :-
 1028    nonvar(PlValue),
 1029    !,
 1030    (   Type == any
 1031    ->  Value = PlValue
 1032    ;   json_check(Type, Value, PlValue)
 1033    ).
 1034client_query_param(qparam(_Name, _PlValue, _Type, optional), _) :-
 1035    !, fail.                                    % leave to convlist/3.
 1036client_query_param(qparam(_Name, PlValue, Type, required), _) :-
 1037    type_error(Type, PlValue).
 1038
 1039optional_query_params([], _, []).
 1040optional_query_params([qparam(Name, PlValue, Type, optional)|T0], Options, Q) :-
 1041    Term =.. [Name,PlValue],
 1042    option(Term, Options),
 1043    !,
 1044    json_check(Type, Value, PlValue),
 1045    Q = [Name=Value|QT],
 1046    optional_query_params(T0, Options, QT).
 1047optional_query_params([_|T0], Options, Q) :-
 1048    optional_query_params(T0, Options, Q).
 client_header_param(+QOptions, +HeaderParam, -Header) is semidet
 1054client_header_param(_QOptions, hparam(Name, PlValue, Type, _Required),
 1055                    request_header(Name=Value)) :-
 1056    nonvar(PlValue),
 1057    !,
 1058    (   Type == any
 1059    ->  Value = PlValue
 1060    ;   json_check(Type, Value, PlValue)
 1061    ).
 1062client_header_param(QOptions, hparam(Name, _PlValue, Type, _Required),
 1063                    request_header(Name=Value)) :-
 1064    Opt =.. [Name,PlValue],
 1065    option(Opt, QOptions),
 1066    !,
 1067    json_check(Type, Value, PlValue).
 1068client_header_param(_QOptions, hparam(Name, _PlValue, _Type, required),
 1069                    _) :-
 1070    existence_error(openapi_option, Name).
 segment_value(+Type, ?Segment, ?Prolog) is det
Transform between a Segment string and the Prolog value according to Type.
 1077segment_value(Type, Segment, Prolog) :-
 1078    nonvar(Segment),
 1079    !,
 1080    uri_encoded(segment, Value, Segment),
 1081    json_check(Type, Value, Prolog).
 1082segment_value(Type, Segment, Prolog) :-
 1083    json_check(Type, Value, Prolog),
 1084    uri_encoded(segment, Value, Segment).
 openapi_read_reply(+Code, +ContentType, +Responses, +In, -Result) is det
Handle the reply at the client side.
 1090:- public openapi_read_reply/5. 1091
 1092openapi_read_reply(Code, _ContentType, Responses, _In, Result) :-
 1093    no_content(Code),
 1094    !,
 1095    (   memberchk(response(Code, _As, _ExpectedContentType, _Type, _Result, _Comment),
 1096                  Responses)
 1097    ->  Result = true
 1098    ;   maplist(arg(1), Responses, ExCodes),
 1099        throw(error(openapi_invalid_reply(Code, ExCodes, ""), _))
 1100    ).
 1101openapi_read_reply(Code, ContentType, Responses, In, Result) :-
 1102    debug(openapi(reply), 'Got code ~p; type: ~p; response schemas: ~p',
 1103          [Code, ContentType, Responses]),
 1104    http_parse_header_value(content_type, ContentType, ParsedContentType),
 1105    (   memberchk(response(Code, As, ExpectedContentType, Type, _Result, _Comment),
 1106                  Responses)
 1107    ->  true
 1108    ;   read_reply(ParsedContentType, -, data, Code, In, Error),
 1109        maplist(arg(1), Responses, ExCodes),
 1110        throw(error(openapi_invalid_reply(Code, ExCodes, Error), _))
 1111    ),
 1112    content_matches(ExpectedContentType, ParsedContentType, ProcessType),
 1113    read_reply(ProcessType, Type, As, Code, In, Result).
 1114
 1115no_content(204).
 1116
 1117content_matches(ContentType, ContentType, ContentType) :- !.
 1118content_matches(media(Type, _), media(Type, Attrs), media(Type, Attrs)) :- !.
 1119content_matches(Expected, Got, _) :-
 1120    type_error(media(Expected), Got).
 1121
 1122read_reply(media(application/json, _), Type, As, Code, In, Result) :-
 1123    json_read_dict(In, Result0, []),
 1124    (   debugging(openapi(reply_object))
 1125    ->  print_term(Result0, [])
 1126    ;   true
 1127    ),
 1128    (   Type = (-)
 1129    ->  Result = Result0
 1130    ;   json_check(Type, Result0, Result1)
 1131    ),
 1132    reply_result(As, Code, Result1, Result).
 1133
 1134reply_result(data,  _Code, Result, Result).
 1135reply_result(error, Code, Result, _ ) :-
 1136    throw(error(rest_error(Code, Result), _)).
 assemble_security(+Security, +ClientModule, -HTTPOptions)
Assemble additional HTTP options from the security description.
 1142:- public assemble_security/3. 1143assemble_security(Security, CM, SecOptions) :-
 1144    current_predicate(CM:security_options/2),
 1145    CM:security_options(Security, SecOptions), !.
 1146assemble_security(Security, _, []) :-
 1147    memberchk(public, Security),
 1148    !.
 1149assemble_security(Security, _, _) :-
 1150    existence_error(security_data, Security).
 security_options(+Security:list, -SecOptions:list)
Multifile hook to provide additional HTTP options for realizing a specific security/authentication. The application must define this hook for dealing with authentication. The possible Security inputs are described with spec_security/3. If this hook fails and the API handler may be accessed without security access without additional options is tried. If this hook fails and authentication is required the client call raises an existence_error for security_data.
 1164		 /*******************************
 1165		 *          DISPATCHER		*
 1166		 *******************************/
 openapi_dispatch(:Request) is semidet
Generic HTTP handler to deal with OpenAPI REST requests.
To be done
-
  • validate types
  • handle errors
  • different replies formats
  • different reply codes
 1177openapi_dispatch(M:Request) :-
 1178    memberchk(path(FullPath), Request),
 1179    memberchk(method(Method), Request),
 1180    M:openapi_root(Root),
 1181    atom_concat(Root, Path, FullPath),
 1182    M:openapi_handler(Method, PathList, Segments,
 1183                      Required, HdrParams, AsOption, OptionParam, Content,
 1184                      Responses, _Security,
 1185                      Handler),
 1186    match_path_list(PathList, Path),
 1187    !,
 1188    (   catch(openapi_run(M:Request,
 1189                          Segments,
 1190                          Required, HdrParams, AsOption, OptionParam, Content,
 1191                          Responses,
 1192                          Handler),
 1193              Error,
 1194              openapi_error(M, Error, Responses))
 1195    ->  true
 1196    ;   openapi_error(M, failed, Responses)
 1197    ).
 1198
 1199openapi_run(Module:Request,
 1200            Segments,
 1201            Required, HdrParams, AsOption, OptionParam, Content,
 1202            Responses,
 1203            Handler) :-
 1204    append(Required, AsOption, RequestParams),
 1205    catch(( maplist(segment_parameter, Segments),
 1206            maplist(header_parameter(Request), HdrParams),
 1207            http_parameters([method(get)|Request], RequestParams),
 1208            request_body(Content, Request),
 1209            server_handler_options(AsOption, OptionParam)
 1210          ), IE, input_error(IE, RequestParams)),
 1211    call(Module:Handler),
 1212    catch(openapi_reply(Module, Responses), OE,
 1213          output_error(OE)).
 input_error(+Error, +RequestParams)
 output_error(+Error)
Handle errors while converting the input and output parameters. Currently maps error context from http_parameters/2 to rest(Param, query, Type) context.
 1222input_error(error(Formal, Context), RequestParams) :-
 1223    subsumes_term(context(_, http_parameter(_)), Context),
 1224    Context = context(_, http_parameter(Param)),
 1225    debug(rest(error), 'Error in ~p; request = ~p', [Param, RequestParams]),
 1226    member(ReqParam, RequestParams),
 1227    ReqParam =.. [Param, _Value, Options],
 1228    http_param_type(Options, Type),
 1229    !,
 1230    throw(error(Formal, rest(Param, request, Type))).
 1231input_error(E, _RequestParams) :- throw(E).
 1232
 1233http_param_type(Options, Type) :-
 1234    memberchk(openapi(Type), Options),
 1235    !.
 1236http_param_type(Options, array(Type, _)) :-
 1237    memberchk(list(openapi(Type)), Options),
 1238    !.
 1239
 1240output_error(E) :- throw(E).
 1241
 1242:- meta_predicate
 1243    add_error_context(0, +). 1244
 1245add_error_context(Goal, C) :-
 1246    catch(Goal, error(Formal, _), throw(error(Formal, C))).
 segment_parameter(?Segment)
Fill a segment parameter
 1252segment_parameter(segment(Type, Segment, Value, Name, _Description)) :-
 1253    add_error_context(
 1254        segment_value(Type, Segment, Value),
 1255        rest(Name, path, Type)).
 1256
 1257server_handler_options([], []).
 1258server_handler_options([H|T], Options) :-
 1259    arg(1, H, Value),
 1260    (   var(Value)
 1261    ->  server_handler_options(T, Options)
 1262    ;   functor(H, Name, _),
 1263        Opt =.. [Name,Value],
 1264        Options = [Opt|OptT],
 1265        server_handler_options(T, OptT)
 1266    ).
 header_parameter(+Request, +HdrParam)
Extract a parameter through the header. @tbd Deal with name normalization? Deal with optional and missing required values.
 1274header_parameter(Request, HdrParam) :-
 1275    HdrParam =.. [Name, Arg, _Opts],
 1276    Header =.. [Name,Arg],
 1277    (   memberchk(Header, Request)
 1278    ->  true
 1279    ;   print_message(warning, error(rest_error(missing_header(Name)), _))
 1280    ).
 request_body(+ContentSpec, +Request) is det
Read the specified request body.
 1286request_body(-, _).
 1287request_body(content(media(application/json,_), -, Body, _Descr), Request) :-
 1288    !,
 1289    add_error_context(
 1290        http_read_json_dict(Request, Body),
 1291        rest(body, request_body, json)).
 1292request_body(content(media(application/json,_), Type, Body, _Descr), Request) :-
 1293    add_error_context(
 1294        http_read_json_dict(Request, Body0),
 1295        rest(body, request_body, json)),
 1296    add_error_context(
 1297        json_check(Type, Body0, Body),
 1298        rest(body, request_body, Type)).
 openapi_reply(+Module, +Responses) is det
Formulate the HTTP request from a term. The user handler binds the response parameter to one of:
status(Code)
Reply using an HTTP header with status Code and no body.
status(Code, Data)
Use Code as HTTP status code and generate the body from Data. Currently this only supports responses of the type application/json and Data must be suitable for json_write_dict/3.
Arguments:
Responses- is a list response(Code, MediaType, Type, Reply, Description), where Reply is the variable that is bound by the user supplied handler.
 1317:- det(openapi_reply/2). 1318openapi_reply(Module, Responses) :-
 1319    Responses = [R0|_],
 1320    arg(5, R0, Reply),
 1321    reply_status(Reply, Code, Data),
 1322    memberchk(response(Code, _As, MediaType, Type, _, _Descr), Responses),
 1323    openapi_reply(Code, MediaType, Type, Data, Module).
 1324
 1325reply_status(Var, _, _) :-
 1326    var(Var), !,
 1327    instantiation_error(Var).
 1328reply_status(status(Code, Data), Code, Data) :- !.
 1329reply_status(status(Code), Code, '') :- !.
 1330reply_status(Data, 200, Data).
 openapi_reply(+HTTPCode, +MediaType, +Type, +Data, +Module) is det
 1334:- det(openapi_reply/5). 1335openapi_reply(Code, _, _, '', _) :-
 1336    !,
 1337    format('Status: ~d~n~n', [Code]).
 1338openapi_reply(Code, media(application/json,_), -, Data, Module) :-
 1339    !,
 1340    Module:openapi_server_config(reply_json_options(Options)),
 1341    reply_json_dict(Data, [status(Code)|Options]).
 1342openapi_reply(Code, media(application/json,_), Type, Data, Module) :-
 1343    !,
 1344    (   Module:openapi_server_config(type_check_response(true))
 1345    ->  json_check(Type, Out, Data)
 1346    ;   Out = Data
 1347    ),
 1348    Module:openapi_server_config(reply_json_options(Options)),
 1349    reply_json_dict(Out, [status(Code)|Options]).
 openapi_error(+Module, +Error, +Responses) is det
An error happened while converting the input arguments, running the implementation or converting the output arguments.
Arguments:
Module- is the (server) module
Error- is the exception or the atom failed if the body execution failed.
Responses- are the declared valid responses.
 1361openapi_error(Module, Error, Responses) :-
 1362    map_error(Module, Error, Responses, Reply),
 1363    Responses = [R0|_],
 1364    arg(5, R0, Reply),
 1365    openapi_reply(Module, Responses),
 1366    !.
 1367openapi_error(_Module, Error, _Responses) :-
 1368    throw(Error).
 1369
 1370map_error(Module, Error, Responses, Reply) :-
 1371    call(Module:openapi_error_hook(Error, Responses, Reply)),
 1372    !.
 1373map_error(_Module, Error, _Responses, Reply) :-
 1374    Error = error(_, Context),
 1375    nonvar(Context),
 1376    http_error_status(Context, Error, Status),
 1377    message_to_string(Error, Message),
 1378    Reply = status(Status, _{code:Status, message:Message}).
 1379
 1380http_error_status(rest(_,_,_), _, 400).
 openapi_error_hook(+Error, +Responses, -Reply) is semidet
Hook called in the server module if an error was encountered while processing the REST request. If the error was thrown while extracting and converting the request parameters, the context of the exception (2nd argument of the error/2 term) has the following shape:
rest(Parameter, Location, Type)
Where Parameter is the parameter name or body, Location is path, query or request_body, and Type is the translated JSON schema type if the parameter. The generated error is typically a type_error, domain_error or syntax_error.
Arguments:
Responses- contains a description of the valid response types and codes.
Reply- is typically bound to a term status(Code, Object), where Object is a dict describing the error.
 1402		 /*******************************
 1403		 *            TYPES		*
 1404		 *******************************/
 api_type(?Type, ?Format, ?TypeID) is semidet
 1410api_type(Type, Format, TypeID) :-
 1411    api_type(_Name, Type, Format, TypeID), !.
 1412api_type(string, Format, string) :-
 1413    !,
 1414    print_message(warning, openapi(unknown_string_format, Format)).
 1415api_type(Type, Format, _TypeID) :-
 1416    print_message(error, openapi(unknown_type, Type, Format)),
 1417    fail.
 api_type(?Name, ?Type, ?Format, ?TypeID)
The formats defined by the OAS are:
 1424api_type(integer,  integer,    int32,       int32).
 1425api_type(long,     integer,    int64,       int64).
 1426api_type(long,     integer,    -,           integer).
 1427api_type(float,    number,     float,       float).
 1428api_type(double,   number,     double,      float).
 1429api_type(double,   number,     -,           float).
 1430api_type(string,   string,     -,           string).
 1431api_type(byte,     string,     byte,        base64).
 1432api_type(binary,   string,     binary,      binary).
 1433api_type(boolean,  boolean,    -,           boolean).
 1434api_type(date,     string,     date,        date).
 1435api_type(dateTime, string,     'date-time', date_time).
 1436api_type(password, string,     password,    password).
 1437api_type(string,   string,     string,      string). % Not in OAS
 1438api_type(uri,      string,     uri,         uri).    % Not in OAS
 1439api_type(uuid,     string,     uuid,        uuid).   % Not in OAS
 oas_type(+Type, ?In, ?Out) is det
Arguments:
Out- is the Prolog view
In- is the JSON dict view.
 1446oas_type(int32, In, Out) :-
 1447    cvt_integer(In, Out),
 1448    must_be(between(-2147483648, 2147483647), Out).
 1449oas_type(int64, In, Out) :-
 1450    cvt_integer(In, Out),
 1451    must_be(between(-9223372036854775808, 9223372036854775807), Out).
 1452oas_type(integer, In, Out) :-
 1453    cvt_integer(In, Out).
 1454oas_type(number, In, Out) :-
 1455    cvt_number(In, Out).
 1456oas_type(float, In, Out) :-
 1457    (   nonvar(In)
 1458    ->  cvt_number(In, Out0),
 1459        Out is float(Out0)
 1460    ;   cvt_number(In0, Out),
 1461        In is float(In0)
 1462    ).
 1463oas_type(string, In, Out) :-
 1464    (   var(In)
 1465    ->  to_string(Out, In)
 1466    ;   to_atom(In, Out)
 1467    ).
 1468oas_type(uri, In, Out) :-
 1469    (   var(In)
 1470    ->  to_atom(Out, In)
 1471    ;   to_atom(In, Out)
 1472    ).
 1473oas_type(uuid, In, Out) :-
 1474    (   var(In)
 1475    ->  to_atom(Out, In)
 1476    ;   to_atom(In, Out)
 1477    ).
 1478oas_type(binary, In, Out) :-
 1479    (   var(In)
 1480    ->  to_string(Out, In)
 1481    ;   to_string(In, Out)
 1482    ).
 1483oas_type(base64, In, Out) :-
 1484    base64(In, Out).
 1485oas_type(boolean, In, Out) :-
 1486    (   var(In)
 1487    ->  to_boolean(Out, In)
 1488    ;   to_boolean(In, Out)
 1489    ).
 1490oas_type(date, In, Out) :-
 1491    cvt_date_time(date, In, Out).
 1492oas_type(date_time, In, Out) :-
 1493    cvt_date_time(date_time, In, Out).
 1494oas_type(password, In, Out) :-
 1495    (   var(In)
 1496    ->  to_string(Out, In)
 1497    ;   to_string(In, Out)
 1498    ).
 cvt_date_time(+Format, ?In, ?Out) is det
Convert between wire (xsd) dateTime and Prolog. As Prolog input we accept a term (date(Y,M,D) or date_time(Y,M,D,H,Mn,S,0)), a time stamp or an xsd dateTime string.
 1506cvt_date_time(Format, In, Out) :-
 1507    (   var(In)
 1508    ->  (   (   atom(Out)
 1509            ->  to_string(Out, In)
 1510            ;   string(Out)
 1511            ->  In = Out
 1512            )
 1513        ->  valid_date_time(Format, In, _)
 1514        ;   compound(Out)
 1515        ->  valid_date_time(Format, In, Out)
 1516        ;   number(Out)
 1517        ->  stamp_date_time(Out, date(Y,M,D,H,Mn,S,0,_Tz,_Dst), 'UTC'),
 1518            (   Format = date_time
 1519            ->  valid_date_time(Format, In, date_time(Y,M,D,H,Mn,S,0))
 1520            ;   valid_date_time(Format, In, date(Y,M,D))
 1521            )
 1522        )
 1523    ;   valid_date_time(Format, In, Out) % creating a date/6 struct
 1524    ).
 1525
 1526valid_date_time(date, String, Date) :-
 1527    xsd_time_string(Date,  % date(Y,M,D)
 1528                    'http://www.w3.org/2001/XMLSchema#date',
 1529                    String).
 1530valid_date_time(date_time, String, DateTime) :-
 1531    xsd_time_string(DateTime,  % date_time(Y,M,D,H,Mi,S[,TZ])
 1532                    'http://www.w3.org/2001/XMLSchema#dateTime',
 1533                    String).
 1534
 1535cvt_integer(In, Out) :-
 1536    cvt_number(In, Out),
 1537    must_be(integer, Out).
 1538
 1539cvt_number(In, Out) :- nonvar(In), !, to_number(In, Out).
 1540cvt_number(N, N)    :- must_be(number, N).
 1541
 1542to_number(In, Out) :-
 1543    (   number(In)
 1544    ->  Out = In
 1545    ;   atom_number(In, Out0)
 1546    ->  Out = Out0
 1547    ;   type_error(number, In)
 1548    ).
 1549
 1550to_string(Val, String) :-
 1551    atom_string(Val, String).
 1552
 1553to_atom(Val, Atom) :-
 1554    atom_string(Atom, Val).
 1555
 1556to_boolean(Var, _) :-
 1557    var(Var),
 1558    !,
 1559    instantiation_error(Var).
 1560to_boolean(false,   false).
 1561to_boolean(true,    true).
 1562to_boolean('FALSE', false).
 1563to_boolean('TRUE',  true).
 1564to_boolean(0,       false).
 1565to_boolean(1,       true).
 1566to_boolean(no,      false).
 1567to_boolean(yes,     true).
 1568to_boolean('NO',    false).
 1569to_boolean('YES',   true).
 1570to_boolean(off,     false).
 1571to_boolean(on,      true).
 1572to_boolean('OFF',   false).
 1573to_boolean('ON',    true).
 json_check(+Spec, ?JSONIn, ?JSONOut) is det
Validate a JSON object.
Errors
- type_error(Expected, Value)
- existence_error(json_schema, URL)
 1582json_check(url(URL), In, Out) :-
 1583    !,
 1584    (   json_schema(URL, Type)
 1585    ->  json_check(Type, In, Out)
 1586    ;   existence_error(json_schema, URL)
 1587    ).
 1588json_check(object, In, Out) :-
 1589    !,
 1590    In = Out,
 1591    (   is_json_object(In)
 1592    ->  true
 1593    ;   type_error(object, In)
 1594    ).
 1595json_check(object(Properties), In, Out) :-
 1596    !,
 1597    (   nonvar(In)
 1598    ->  json_object_pairs(In, InPairs),
 1599        obj_properties_in(InPairs, Properties, OutPairs),
 1600        dict_pairs(Out, _, OutPairs)
 1601    ;   json_object_pairs(Out, OutPairs),
 1602        obj_properties_out(OutPairs, Properties, InPairs),
 1603        dict_pairs(In, _, InPairs)
 1604    ).
 1605json_check(array(Type, Opts), In, Out) :-
 1606    !,
 1607    (   is_list(In)
 1608    ->  check_array_length(In, Opts),
 1609        maplist(json_check(Type), In, Out)
 1610    ;   is_list(Out)
 1611    ->  check_array_length(Out, Opts),
 1612        maplist(json_check(Type), In, Out)
 1613    ;   must_be(list, In, Out)
 1614    ),
 1615    check_array_unique(In, Opts).
 1616json_check(oneOf(Types), In, Out) :-
 1617    !,
 1618    Error = error(_,_),
 1619    (   nonvar(In)
 1620    ->  candidate_types(Types, In, Candidates, Best),
 1621        (   Candidates = []                        % no candidate, best error
 1622        ->  json_check(Best, In, Out)
 1623        ;   Candidates = [Type]                    % one candidate, check
 1624        ->  json_check(Type, In, Out)
 1625        ;   append(_, [Type|Rest], Types),         % find type and verify no 2nd
 1626            catch(json_check(Type, In, Out), Error, fail)
 1627        ->  (   member(T2, Rest),
 1628                catch(json_check(T2, In, _), Error, fail)
 1629            ->  type_error(oneOf(Types), In)
 1630            ;   true
 1631            )
 1632        ;   type_error(oneOf(Types), In)
 1633        )
 1634    ;   candidate_types(Types, Out, Candidates, Best),
 1635        (   Candidates = []
 1636        ->  json_check(Best, In, Out)
 1637        ;   Candidates = [Type]
 1638        ->  json_check(Type, In, Out)
 1639        ;   append(_, [Type|Rest], Candidates),
 1640            catch(json_check(Type, In, Out), Error, fail)
 1641        ->  (   member(T2, Rest),
 1642                catch(json_check(T2, _, Out), Error, fail)
 1643            ->  type_error(oneOf(Types), Out)
 1644            ;   true
 1645            )
 1646        ;   type_error(oneOf(Types), Out)
 1647        )
 1648    ).
 1649json_check(allOf(Types), In, Out) :-
 1650    !,
 1651    (   nonvar(In)
 1652    ->  maplist(json_check_in_out_type(In), Outs, Types),
 1653        join_dicts(Outs, Out)
 1654    ;   maplist(json_check_out_in_type(Out), Ins, Types),
 1655        join_dicts(Ins, In)
 1656    ).
 1657json_check(anyOf(Types), In, Out) :-
 1658    !,
 1659    (   member(Type, Types),
 1660        catch(json_check(Type, In, Out), _, fail)
 1661    ->  true
 1662    ;   nonvar(In)
 1663    ->  type_error(oneOf(Types), In)
 1664    ;   type_error(oneOf(Types), Out)
 1665    ).
 1666json_check(not(Type), In, Out) :-
 1667    !,
 1668    (   \+ catch(json_check(Type, In, Out), _, fail)
 1669    ->  In = Out
 1670    ;   (   nonvar(In)
 1671        ->  type_error(not(Type), In)
 1672        ;   type_error(not(Type), Out)
 1673        )
 1674    ).
 1675json_check(enum(Values, CaseSensitive, Case), In, Out) :-
 1676    Enum = enum(Values, CaseSensitive, Case),
 1677    !,
 1678    (   var(In)                                    % Out -> In
 1679    ->  enum_find_ex(Out, Enum, Value),
 1680        to_string(Value, In)
 1681    ;   enum_find_ex(In, Enum, Value),
 1682        enum_case(Case, Value, Out)
 1683    ).
 1684json_check(numeric(Type, Domain), In, Out) :-
 1685    !,
 1686    oas_type(Type, In, Out),
 1687    (   number_in_domain(Domain, Out)
 1688    ->  true
 1689    ;   domain_error(Domain, Out)
 1690    ).
 1691json_check(any, In, Out) :-
 1692    !,
 1693    In = Out.
 1694json_check(string(Restrictions), In, Out) :-
 1695    !,
 1696    oas_type(string, In, Out),
 1697    maplist(check_string_restriction(In), Restrictions).
 1698json_check(Type, In, Out) :-
 1699    oas_type(Type, In, Out).
 1700
 1701json_check_in_out_type(In, Out, Type) :- json_check(Type, In, Out).
 1702json_check_out_in_type(Out, In, Type) :- json_check(Type, In, Out).
 candidate_types(+Types, +Data, -Candidates:list(type), -Best:type)
True when Candidates is a list of types that may match and Best is the closest matching candidate.
 1709:- det(candidate_types/4). 1710candidate_types(Types, Data, Candidates, Best) :-
 1711    maplist(candidate_type(Data), Types, Scores),
 1712    pairs_keys_values(Best0, Types, Scores),
 1713    sort(2, @>=, Best0, Best1),
 1714    Best1 = [Best-_|_],
 1715    convlist(is_candidate, Best1, Candidates).
 1716
 1717is_candidate(Type-(_-0), Type).
 candidate_type(+Data, +Type, -Score:pair(Match,Mismatch)) is det
Check whether Data may satisfy Type. If Mismatch is zero, all required values are present and all enums are satisfied. Mismatch is incremented on each missing required property or missing enum value.
 1725candidate_type(Data, Type, Match-Mismatch) :-
 1726    State = state(0,0),
 1727    candidate_type_(Type, Data, State),
 1728    State = state(Match, Mismatch).
 1729
 1730candidate_type_(object(Props), Data, State) :-
 1731    !,
 1732    (   is_dict(Data)
 1733    ->  (   member(p(Name, Type, Opts), Props),
 1734            (   Field = Data.get(Name)
 1735            ->  incr_match(State),
 1736                candidate_type_(Type, Field, State)
 1737            ;   memberchk(required, Opts)
 1738            ->  incr_mismatch(State)
 1739            ;   true
 1740            ),
 1741            fail
 1742        ;   true
 1743        )
 1744    ;   incr_mismatch(State)
 1745    ).
 1746candidate_type_(Type, Data, State) :-
 1747    Type = enum(_, _, _),
 1748    !,
 1749    (   (   atom(Data)
 1750        ->  true
 1751        ;   string(Data)
 1752        ),
 1753        (   enum_find(Data, Type, _Value)
 1754        ->  incr_match(State)
 1755        ;   incr_mismatch(State)
 1756        )
 1757    ;   incr_mismatch(State)
 1758    ).
 1759candidate_type_(_, _, _).
 1760
 1761incr_match(State) :-
 1762    arg(1, State, M0),
 1763    M1 is M0+1,
 1764    nb_setarg(1, State, M1).
 1765incr_mismatch(State) :-
 1766    arg(2, State, M0),
 1767    M1 is M0-1,
 1768    nb_setarg(2, State, M1).
 number_in_domain(+Domain, +Value) is semidet
True if Value satisfies Domain. @see type_restrictions/4 creates Domain
 1775number_in_domain(Domain, Value) :-
 1776    number_in_domain_(Domain, Value),
 1777    arg(3, Domain, MultipleOf),
 1778    (   MultipleOf == (-)
 1779    ->  true
 1780    ;   Times is Value/MultipleOf,
 1781        round(Times) =:= Times
 1782    ).
 1783
 1784number_in_domain_(domain(between(Min, Max), ExclMin-ExclMax, _), Value) =>
 1785    satisfies_min(Min, Value, ExclMin),
 1786    satisfies_max(Max, Value, ExclMax).
 1787number_in_domain_(domain(max(Max), ExclMax, _), Value) =>
 1788    satisfies_max(Max, Value, ExclMax).
 1789number_in_domain_(domain(min(Min), ExclMin, _), Value) =>
 1790    satisfies_min(Min, Value, ExclMin).
 1791
 1792satisfies_max(Max, Value, false) =>
 1793    Value =< Max.
 1794satisfies_max(Max, Value, true) =>
 1795    Value < Max.
 1796
 1797satisfies_min(Min, Value, false) =>
 1798    Value >= Min.
 1799satisfies_min(Min, Value, true) =>
 1800    Value > Min.
 enum_find(+From, +EnumSpec, -Value:atom) is semidet
 enum_find_ex(+From, +EnumSpec, -Value:atom) is det
Find the intended enum value from the atom or string From. Deals with whether or not the enum is specified as case sensitive.
Errors
- domain_error(oneof(Values))
 1810enum_find(From, enum(Values, CaseSensitive, _Case), Value) :-
 1811    to_atom(From, V0),
 1812    (   memberchk(V0, Values)
 1813    ->  Value = V0
 1814    ;   CaseSensitive == false,
 1815        downcase_atom(V0, VL),
 1816        member(V1, Values),
 1817        downcase_atom(V1, VL)
 1818    ->  Value = V1
 1819    ).
 1820
 1821enum_find_ex(From, Enum, Value) :-
 1822    (   enum_find(From, Enum, Value)
 1823    ->  true
 1824    ;   arg(1, Enum, Values),
 1825        domain_error(oneof(Values), From)
 1826    ).
 1827
 1828enum_case(preserve, Out0, Out) => Out = Out0.
 1829enum_case(lower,    Out0, Out) => downcase_atom(Out0, Out).
 1830enum_case(upper,    Out0, Out) => upcase_atom(Out0, Out).
 1831
 1832check_string_restriction(String, min_length(MinLen)) =>
 1833    string_length(String, Len),
 1834    (   Len >= MinLen
 1835    ->  true
 1836    ;   domain_error(string(minLength>=MinLen), String)
 1837    ).
 1838check_string_restriction(String, max_length(MaxLen)) =>
 1839    string_length(String, Len),
 1840    (   Len =< MaxLen
 1841    ->  true
 1842    ;   domain_error(string(maxLength=<MaxLen), String)
 1843    ).
 1844check_string_restriction(String, pattern(Pattern)) =>
 1845    re_match(Pattern, String, []).
 is_json_object(@Term) is semidet
True when Term can be used as a JSON object mapping.
 1851is_json_object(Dict) :-
 1852    is_dict(Dict, _), !.
 1853is_json_object(json(Attrs)) :-
 1854    is_list(Attrs),
 1855    maplist(name_value, Attrs).
 1856
 1857name_value(Name = _Value) :- atomic(Name).
 1858name_value(Term) :- compound(Term), compound_name_arity(Term, _, 1).
 1859
 1860json_object_pairs(Dict, Pairs) :-
 1861    is_dict(Dict, _),
 1862    !,
 1863    dict_pairs(Dict, _, Pairs).
 1864json_object_pairs(json(List), Pairs) :-
 1865    is_list(List),
 1866    maplist(name_value, List, Keys, Values),
 1867    !,
 1868    pairs_keys_values(Pairs0, Keys, Values),
 1869    keysort(Pairs0, Pairs).
 1870json_object_pairs(Obj, _) :-
 1871    type_error(json_object, Obj).
 1872
 1873name_value(Name - Value, Name, Value) :- !.
 1874name_value(Name = Value, Name, Value) :- !.
 1875name_value(Term, Name, Value) :- Term =.. [Name,Value].
 obj_properties_in(+InPairs, +Spec, -OutPairs) is det
Type check the Name-Value pairs of an object against Spec. Spec is a list of p(Name,Type,Opts). Input that does not appear in the schema is removed. If a Value is null and the property is not required, this is accepted. Should we delete the property instead?
 1884obj_properties_in([], Spec, []) :-
 1885    !,
 1886    check_missing(Spec).
 1887obj_properties_in(List, [], List) :-
 1888    !.
 1889obj_properties_in([NV|T0], PL, [NV|T]) :-
 1890    PL = [p(P,_,_)|_],
 1891    NV = N-_,
 1892    N @< P,
 1893    !,
 1894    obj_properties_in(T0, PL, T).
 1895obj_properties_in([N-V0|T0], [p(N,Type,Opts)|PT], [N-V|T]) :-
 1896    !,
 1897    (   V0 == null,
 1898        (   memberchk(nullable, Opts)
 1899        ;   \+ memberchk(required, Opts)
 1900        )
 1901    ->  V = V0
 1902    ;   json_check(Type, V0, V)
 1903    ),
 1904    obj_properties_in(T0, PT, T).
 1905obj_properties_in(T0, [p(N,_Type,Opts)|PT], T) :-
 1906    (   memberchk(required, Opts)
 1907    ->  existence_error(json_property, N)
 1908    ;   obj_properties_in(T0, PT, T)
 1909    ).
 1910
 1911check_missing([]).
 1912check_missing([p(N,_Type,Opts)|T]) :-
 1913    (   memberchk(required, Opts)
 1914    ->  existence_error(json_property, N)
 1915    ;   check_missing(T)
 1916    ).
 obj_properties_out(+OutPairs, +Spec, -InPairs)
 1920obj_properties_out([], Spec, []) :-
 1921    !,
 1922    check_missing(Spec).
 1923obj_properties_out(List, [], List) :-
 1924    !.
 1925obj_properties_out([NV|T0], PL, [NV|T]) :-
 1926    PL = [p(P,_,_)|_],
 1927    NV = N-_,
 1928    N @< P,
 1929    !,
 1930    obj_properties_out(T0, PL, T).
 1931obj_properties_out([N-V0|T0], [p(N,Type,_Opts)|PT], [N-V|T]) :-
 1932    !,
 1933    json_check(Type, V, V0),
 1934    obj_properties_out(T0, PT, T).
 1935obj_properties_out(T0, [p(N,_Type,Opts)|PT], T) :-
 1936    (   memberchk(required, Opts)
 1937    ->  existence_error(json_property, N)
 1938    ;   obj_properties_out(T0, PT, T)
 1939    ).
 join_dicts(+Dicts, -Dict) is det
Create a dict from a list of dicts, containing the joined keys. If there are key duplicates, the last remains.
 1946join_dicts([One], One) :- !.
 1947join_dicts([H1,H2|T], Dict) :-
 1948    H = H1.put(H2),
 1949    join_dicts([H|T], Dict).
 must_be(+Type, ?In, ?Out) is det
Support bi-directional type check for json_check/3.
 1955must_be(Type, In, Out) :-
 1956    (   nonvar(In)
 1957    ->  must_be(Type, In)
 1958    ;   must_be(Type, Out)
 1959    ).
 1960
 1961:- multifile
 1962    http:convert_parameter/3. 1963
 1964http:convert_parameter(openapi(Type), In, Out) :-
 1965    json_check(Type, In, Out).
 json_schema(?URL, ?Spec)
Spec is one of
 1980:- multifile
 1981    json_schema/2.
 json_schema_clauses(+JSONTerm, +Options)//
 1985json_schema_clauses(JSONTerm, Options) -->
 1986    { Schemas = JSONTerm.get(components).get(schemas),
 1987      dict_pairs(Schemas, _, SchemaPairs)
 1988    },
 1989    !,
 1990    schema_clauses(SchemaPairs, Options).
 1991json_schema_clauses(_, _) --> [].
 schema_clauses(+Specs, +Options)//
Compile the OpenAPI schema definitions into json_schema/2 clauses.
 1998schema_clauses([], _) --> [].
 1999schema_clauses([H|T], Options) -->
 2000    schema_clause(H, Options),
 2001    schema_clauses(T, Options).
 2002
 2003schema_clause(Schema-Spec, Options) -->
 2004    { json_type(Spec, Type, Options),
 2005      option(base_uri(Base), Options),
 2006      file_directory_name(Base, Dir),
 2007      atomic_list_concat([Dir, '#/components/schemas/', Schema], URL)
 2008    },
 2009    [ openapi:json_schema(URL, Type) ].
 json_type(+Spec, -Type, -TypeOpts, +Options) is det
True when Type is the type representation for the JSON type description Spec.
Arguments:
Spec- is an OpenAPI type specification as JSON or YAML term.
Type- is a term that is handled by json_check/3.
TypeOpts- is a list that may hold nullable or required.
 2020json_type(Spec, Type, TypeOpts, Options) :-
 2021    _{'$ref':URLS} :< Spec,
 2022    !,
 2023    option(base_uri(Base), Options),
 2024    uri_normalized(URLS, Base, URL),
 2025    (   url_yaml(URL, Spec2)
 2026    ->  atom_string(NewBase, URL),
 2027        json_type(Spec2, Type, TypeOpts, [base_uri(NewBase)|Options])
 2028    ;   Type = url(URL),
 2029        TypeOpts = []
 2030    ).
 2031json_type(Spec, Type, TypeOpts, Options) :-
 2032    json_type(Spec, Type, Options),
 2033    (   Spec.get(nullable) == true
 2034    ->  TypeOpts = [nullable]
 2035    ;   TypeOpts = []
 2036    ).
 json_type(+Spec, -Type, +Options) is det
 2040json_type(Spec, Type, _) :-
 2041    _{type:TypeS, format:FormatS} :< Spec,
 2042    !,
 2043    atom_string(Type0, TypeS),
 2044    atom_string(Format, FormatS),
 2045    api_type(Type0, Format, Type1),
 2046    type_restrictions(Spec, Type0, Type1, Type).
 2047json_type(Spec, object(Props), Options) :-
 2048    _{properties:PropSpecs} :< Spec,
 2049    !,
 2050    dict_pairs(PropSpecs, _, Pairs),
 2051    (   maplist(atom_string, Req, Spec.get(required))
 2052    ->  true
 2053    ;   Req = []
 2054    ),
 2055    maplist(schema_property(Req, Options), Pairs, Props0),
 2056    sort(Props0, Props).
 2057json_type(Spec, array(Type, Opts), Options) :-
 2058    _{type:"array", items:IType} :< Spec,
 2059    !,
 2060    array_restrictions(Spec, Opts),
 2061    json_type(IType, Type, Options).
 2062json_type(Spec, oneOf(Types), Options) :-
 2063    _{oneOf:List} :< Spec,
 2064    !,
 2065    maplist(opts_json_type(Options), List, Types).
 2066json_type(Spec, allOf(Types), Options) :-
 2067    _{allOf:List} :< Spec,
 2068    !,
 2069    maplist(opts_json_type(Options), List, Types).
 2070json_type(Spec, anyOf(Types), Options) :-
 2071    _{anyOf:List} :< Spec,
 2072    !,
 2073    maplist(opts_json_type(Options), List, Types).
 2074json_type(Spec, not(Type), Options) :-
 2075    _{not:NSpec} :< Spec,
 2076    !,
 2077    json_type(NSpec, Type, Options).
 2078json_type(Spec, object, _Options) :-
 2079    _{type:"object"} :< Spec,
 2080    !.
 2081json_type(Spec, enum(Values, CaseSensitive, Case), Options) :-
 2082    _{type:"string", enum:ValuesS} :< Spec,
 2083    !,
 2084    option(enum_case_sensitive(CaseSensitive), Options, true),
 2085    option(enum_case(Case), Options, preserve),
 2086    maplist(atom_string, Values, ValuesS).
 2087json_type(Spec, Type, _) :-
 2088    _{type:TypeS} :< Spec,
 2089    !,
 2090    atom_string(Type0, TypeS),
 2091    api_type(Type0, -, Type1),
 2092    type_restrictions(Spec, Type0, Type1, Type).
 2093json_type(Spec, Type, Options) :-
 2094    _{'$ref':URLS} :< Spec,
 2095    !,
 2096    option(base_uri(Base), Options),
 2097    uri_normalized(URLS, Base, URL),
 2098    (   url_yaml(URL, Spec2)
 2099    ->  atom_string(NewBase, URL),
 2100        json_type(Spec2, Type, [base_uri(NewBase)|Options])
 2101    ;   Type = url(URL)
 2102    ).
 2103json_type(_{properties:_{}}, Type, _Options) :-
 2104    !,
 2105    Type = (-).
 2106json_type(_Spec, _Type, _Options) :-
 2107    start_debugger_fail.
 2108
 2109opts_json_type(Options, Spec, Type) :-
 2110    json_type(Spec, Type, Options).
 2111
 2112schema_property(Reqs, Options, Name-Spec, p(Name, Type, TypeOpts)) :-
 2113    (   memberchk(Name, Reqs)
 2114    ->  TypeOpts = [ required | TypeOpts1 ]
 2115    ;   TypeOpts = TypeOpts1
 2116    ),
 2117    json_type(Spec, Type, TypeOpts1, Options).
 type_restrictions(+Spec, +Type0, +ApiType, -Type)
 2121type_restrictions(Spec, Type0, Type1, Type) :-
 2122    numeric_type(Type0),
 2123    !,
 2124    (   _{minimum:Min, maximum:Max} :< Spec
 2125    ->  Type = numeric(Type1, domain(between(Min,Max), ExclMin-ExclMax, MultipleOf))
 2126    ;   _{minimum:Min} :< Spec
 2127    ->  Type = numeric(Type1, domain(min(Min), ExclMin, MultipleOf))
 2128    ;   _{maximum:Max} :< Spec
 2129    ->  Type = numeric(Type1, domain(max(Max), ExclMax, MultipleOf))
 2130    ;   Type = Type1
 2131    ),
 2132    (   _{ exclusiveMinimum: ExclMin} :< Spec
 2133    ->  true
 2134    ;   ExclMin = false
 2135    ),
 2136    (   _{ exclusiveMaximum: ExclMax} :< Spec
 2137    ->  true
 2138    ;   ExclMax = false
 2139    ),
 2140    (   _{ multipleOf: MultipleOf} :< Spec
 2141    ->  true
 2142    ;   MultipleOf = (-)
 2143    ).
 2144type_restrictions(Spec, string, string, Type) :-
 2145    setof(Restrict, string_restriction(Spec, Restrict), Restrictions),
 2146    !,
 2147    Type = string(Restrictions).
 2148type_restrictions(_, _Type0, Type, Type).
 2149
 2150numeric_type(integer).
 2151numeric_type(number).
 2152
 2153string_restriction(Spec, max_length(Len)) :-
 2154    Len = Spec.get(maxLength).
 2155string_restriction(Spec, min_length(Len)) :-
 2156    Len = Spec.get(minLength).
 2157string_restriction(Spec, pattern(Regex)) :-
 2158    atom_string(Regex, Spec.get(pattern)).
 2159
 2160array_restrictions(Spec, Options) :-
 2161    findall(Opt, array_restriction(Spec, Opt), Options).
 2162
 2163array_restriction(Spec, min_items(Min)) :-
 2164    Min = Spec.get(minItems).
 2165array_restriction(Spec, max_items(Max)) :-
 2166    Max = Spec.get(minItems).
 2167array_restriction(Spec, unique_items(true)) :-
 2168    true == Spec.get(uniqueItems).
 2169
 2170check_array_length(List, Opts) :-
 2171    memberchk(max_items(Max), Opts),
 2172    !,
 2173    (   memberchk(min_items(Min), Opts)
 2174    ->  true
 2175    ;   Min = 0
 2176    ),
 2177    length(List, Len),
 2178    (   between(Min, Max, Len)
 2179    ->  true
 2180    ;   domain_error(array_length(Min,Max), List)
 2181    ).
 2182check_array_length(List, Opts) :-
 2183    memberchk(min_items(Min), Opts),
 2184    !,
 2185    length(List, Len),
 2186    (   Len >= Min
 2187    ->  true
 2188    ;   domain_error(array_length(Min,infinite), List)
 2189    ).
 2190check_array_length(_, _).
 2191
 2192check_array_unique(List, Opts) :-
 2193    memberchk(unique_items(true), Opts),
 2194    !,
 2195    (   length(List, Len),
 2196        sort(List, Sorted),
 2197        length(Sorted, Len)
 2198    ->  true
 2199    ;   domain_error(unique_array, List)
 2200    ).
 2201check_array_unique(_, _).
 url_yaml(+URL, -Yaml:json) is semidet
Assuming URL points to a local file and fragment thereof that specifies a type, Type is the JSON/YAML representation of this type.
 2208url_yaml(URL, Yaml) :-
 2209    uri_components(URL, Components),
 2210    uri_data(scheme, Components, file),
 2211    uri_data(path, Components, FileEnc),
 2212    uri_data(fragment, Components, Fragment),
 2213    uri_encoded(path, File, FileEnc),
 2214    openapi_read(File, Yaml0),
 2215    (   var(Fragment)
 2216    ->  Yaml = Yaml0
 2217    ;   atomic_list_concat(Segments, /, Fragment),
 2218        yaml_subdoc(Segments, Yaml0, Yaml)
 2219    ).
 2220
 2221
 2222		 /*******************************
 2223		 *        DOC GENERATION	*
 2224		 *******************************/
 openapi_doc(+File, +Mode, +Options) is det
Write documentation to the current output. Options are passed to openapi_server/2. In addition, the following options are processed:
file(+File)
Dump output to File.

This predicate is used by the swipl-openapi script to generate the commented client or server code.

 2237openapi_doc(File, Mode, Options) :-
 2238    must_be(oneof([client,server]), Mode),
 2239    read_openapi_spec(File, Spec, Options, Options1),
 2240    phrase(server_clauses(Spec, Options1), Clauses),
 2241    setup_call_cleanup(
 2242        doc_output(Stream, Close, Options),
 2243        doc_gen(Stream, File, Clauses, [mode(Mode)|Options]),
 2244        Close).
 2245
 2246doc_output(Stream, close(Stream), Options) :-
 2247    option(file(File), Options),
 2248    !,
 2249    open(File, write, Stream).
 2250doc_output(current_output, true, _).
 2251
 2252doc_gen(Stream, File, Clauses, Options) :-
 2253    findall(OperationId-Data,
 2254            doc_data(Clauses, OperationId, Data, Options), Pairs),
 2255    file_header(Stream, File, [operations(Pairs)|Options]),
 2256    forall(member(OperationId-Data, Pairs),
 2257           (   phrase(openapi_doc(OperationId, Data, Options), S)
 2258           ->  format(Stream, '~s', [S])
 2259           ;   warning(openapi(doc_failed, OperationId), Options)
 2260           )).
 2261
 2262file_header(Stream, File, Options) :-
 2263    option(mode(client), Options),
 2264    !,
 2265    client_module(Stream, File, Options),
 2266    findall(Opt, client_option(Opt, Options), ClientOptions),
 2267    format(Stream, ':- use_module(library(openapi)).~n', []),
 2268    format(Stream, ':- use_module(library(option)).~n~n', []),
 2269    format(Stream, ':- use_module(library(debug)).~n~n', []),
 2270    portray_clause(Stream, (:- openapi_client(File, ClientOptions))),
 2271    nl(Stream).
 2272file_header(Stream, File, Options) :-
 2273    option(mode(server), Options),
 2274    !,
 2275    findall(Opt, server_option(Opt, Options), ServerOptions),
 2276    format(Stream, ':- use_module(library(openapi)).~n', []),
 2277    format(Stream, ':- use_module(library(option)).~n', []),
 2278    format(Stream, ':- use_module(library(debug)).~n', []),
 2279    server_header(Stream, File, Options),
 2280    format(Stream, '~n', []),
 2281    portray_clause(Stream, (:- openapi_server(File, ServerOptions))),
 2282    nl(Stream).
 2283file_header(_, _, _).
 client_module(+Stream, +SpecFile, +Options)
Emit a module header for the generated client if the option module(Module) is present. If Module is true, derive the module from the client filename or the SpecFile.
 2291client_module(Stream, SpecFile, Options) :-
 2292    module_name(Module, SpecFile, Options),
 2293    option(operations(Ops), Options),
 2294    !,
 2295    format(Stream, ':- module(~q,~n~t[ ~12|', [Module]),
 2296    exports(Ops, Stream),
 2297    format(Stream, '~t~10|]).~n', []).
 2298client_module(_, _, _).
 2299
 2300module_name(Module, SpecFile, Options) :-
 2301    option(module(M), Options),
 2302    (   M == true
 2303    ->  option(file(File), Options, SpecFile),
 2304        file_base_name(File, Base),
 2305        file_name_extension(Module, _, Base)
 2306    ;   Module = M
 2307    ).
 2308
 2309exports([], _).
 2310exports([OperationId-Data|T], Stream) :-
 2311    (   T == []
 2312    ->  Sep = ''
 2313    ;   Sep = ','
 2314    ),
 2315    export(Stream, OperationId, Data.arguments, Sep),
 2316    exports(T, Stream).
 2317
 2318export(Stream, OperationId, Args, Sep) :-
 2319    length(Args, Arity),
 2320    phrase(mode_args(Args), Codes),
 2321    format(Stream, '~t~12|~q~w~t~48|% ~s~n',
 2322           [OperationId/Arity, Sep, Codes]).
 client_option(-ClientOption, +Options) is nondet
Pass options for generating the client at runtime.
 2328client_option(warn(false), _Options).
 2329client_option(type_check_request(Mode), Options) :-
 2330    option(type_check_request(Mode), Options).
 2331client_option(Option, Options) :-
 2332    common_option(Option, Options).
 server_option(-ServerOption, +Options) is nondet
Pass options for generating the server at runtime.
 2338server_option(type_check_response(Bool), Options) :-
 2339    option(type_check_response(Bool), Options),
 2340    must_be(boolean, Bool).
 2341server_option(format_response(Bool), Options) :-
 2342    option(format_response(Bool), Options),
 2343    must_be(boolean, Bool).
 2344server_option(Option, Options) :-
 2345    common_option(Option, Options).
 2346
 2347common_option(server_url(URL), Options) :-
 2348    option(server_url(URL), Options).
 2349common_option(enum_case_sensitive(Bool), Options) :-
 2350    option(enum_case_sensitive(Bool), Options).
 2351common_option(enum_case(Case), Options) :-
 2352    option(enum_case(Case), Options),
 2353    must_be(oneof([lower,upper,preserve]), Case).
 server_header(+Stream, +File, +Options) is det
Emit the header for generating a server.
 2359server_header(Stream, File, Options) :-
 2360    (   option(httpd(true), Options)
 2361    ;   option(ui(true), Options)
 2362    ),
 2363    !,
 2364    format(Stream, ':- use_module(library(http/thread_httpd)).~n', []),
 2365    (   option(ui(true), Options)
 2366    ->  server_ui(Stream, File, Options)
 2367    ;   option(httpd(true), Options)
 2368    ->  server_restonly(Stream, Options)
 2369    ;   true
 2370    ).
 2371server_header(_,_,_).
 2372
 2373server_ui(Stream, File, _Options) :-
 2374    format(Stream, ':- use_module(library(http/http_dispatch)).~n', []),
 2375    format(Stream, ':- use_module(library(swagger_ui)).~n', []),
 2376    format(Stream, '
 2377:- http_handler(root(.),
 2378                http_redirect(see_other, root(\'swagger_ui\')),
 2379                []).
 2380:- http_handler(root(\'swagger.yaml\'),
 2381                http_reply_file(~q, []),
 2382                [id(swagger_config)]).
 2383
 2384server(Port) :-
 2385    http_server(dispatch,
 2386                [ port(Port)
 2387                ]).
 2388
 2389dispatch(Request) :-
 2390    openapi_dispatch(Request),
 2391    !.
 2392dispatch(Request) :-
 2393    http_dispatch(Request).
 2394
 2395', [File]).
 2396
 2397server_restonly(Stream, _Options) :-
 2398    format(Stream, '
 2399server(Port) :-
 2400    http_server(openapi_dispatch,
 2401                [ port(Port)
 2402                ]).
 2403
 2404', []).
 2405
 2406		 /*******************************
 2407		 *        INTROSPECTION		*
 2408		 *******************************/
 openapi_arg(?PredicateName, ?Index, ?Name, ?Type) is nondet
True when PredicateName's one-based Index-th argument is named Name and has type Type.
Arguments:
Type- is as defined by the first argument of json_check/3.
 2417% Server clauses
 2418openapi_arg(M:OperationId, ArgI, Arg, Type) :-
 2419    Clause = openapi_handler(_Method, _PathList, _SegmentMatches,
 2420                             _Request, _HdrParams, _AsOption, _OptionParam,
 2421                             _Content, _Responses, _Security, Handler),
 2422    clause(M:Clause, true),
 2423    functor(Handler, OperationId, _),
 2424    clause_data(Clause, module(M), OperationId, Data, []),
 2425    nth1(ArgI, Data.arguments, p(Arg, Type, _Description)).
 2426% client clauses
 2427openapi_arg(M:OperationId, ArgI, Arg, Type) :-
 2428    Clause = openapi_type(Head),
 2429    clause(M:Clause, true),
 2430    functor(Head, OperationId, _),
 2431    arg(ArgI, Head, Arg:Type).
 2432
 2433
 2434		 /*******************************
 2435		 *   DOCUMENTATION GENERATION	*
 2436		 *******************************/
 2437
 2438:- meta_predicate
 2439    prefix(+, //, -, ?, ?).
 openapi_doc(+OperationID, +Data, +Options)// is det
 2443openapi_doc(OperationId, Data, Options) -->
 2444    doc_mode(OperationId, Data.arguments),
 2445    "\n%\n",
 2446    doc_description(Data.doc),
 2447    doc_security(Data.security),
 2448    doc_args(Data.arguments),
 2449    doc_path(Data.doc),
 2450    "\n",
 2451    server_skeleton(OperationId, Data.arguments, Options).
 server_skeleton(+OperationId, +Args:list, +Options)// is det
Generate the skeleton clause for the operation.
 2457:- det(server_skeleton//3). 2458server_skeleton(_OperationId, _Args, Options) -->
 2459    { option(mode(client), Options) },
 2460    !.
 2461server_skeleton(OperationId, Args, Options) -->
 2462    { option(mode(server), Options),
 2463      maplist(server_arg_name, Args, ArgNames),
 2464      Head =.. [OperationId|ArgNames],
 2465      server_skeleton_clause(Head, Clause),
 2466      (   string(Clause)
 2467      ->  string_codes(Clause, Codes)
 2468      ;   with_output_to(codes(Codes),
 2469                         portray_clause(Clause))
 2470      )
 2471    },
 2472    string(Codes).
 server_skeleton_clause(+Head, -Clause) is det
Generate the server skeleton clause. This predicate can be hooked using openapi_server_clause/2 with the same signature.
Arguments:
Head- is a term OperationId(Arg, ...), where each arg has the shape '$VAR'(Name) and Name is the CamelCase version of the parameter, a valid name for a Prolog variable.
Clause- is either a string, which is inserted into the output untranslated or a term that is handed to portray_clause/1.
 2485:- det(server_skeleton_clause/2). 2486:- multifile
 2487    user:openapi_server_clause/2. 2488server_skeleton_clause(Head, Clause) :-
 2489    user:openapi_server_clause(Head, Clause),
 2490    !.
 2491server_skeleton_clause(Head, Clause) :-
 2492    functor(Head, _, Arity),
 2493    arg(Arity, Head, Response),
 2494    Clause = (Head :-
 2495                  debug(openapi, "~p", [Head]),
 2496                  Response = status(404)).
 2497
 2498
 2499doc_mode(OperationId, Args) -->
 2500    "%! ", quoted_atom(OperationId),
 2501    "(", mode_args(Args), ") is det.".
 2502
 2503mode_args([]) --> [].
 2504mode_args([H|T]) -->
 2505    mode_arg(H),
 2506    (  {T==[]}
 2507    -> []
 2508    ;  ", ",
 2509       mode_args(T)
 2510    ).
 2511
 2512mode_arg(p(Name, _Type, _Descr)) -->
 2513    mode(Name), camel_case(Name).
 2514
 2515mode(response) --> !, "-".
 2516mode(_) --> "+".
 2517
 2518server_arg_name(p(Param, _Type, _Descr), '$VAR'(ArgName)) :-
 2519    camel_case(Param, ArgName).
 2520
 2521quoted_atom(Atom, List, Tail) :-
 2522    format(codes(List,Tail), '~q', [Atom]).
 camel_case(+Name)
Emit an identifier in CamelCase.
 2528camel_case(Name) -->
 2529    { camel_case(Name, Camel) },
 2530    atom(Camel).
 2531
 2532camel_case(Name, Camel) :-
 2533    atom_codes(Name, Codes),
 2534    phrase(camel(Codes), CamelCodes),
 2535    atom_codes(Camel, CamelCodes).
 2536
 2537camel([]) --> [].
 2538camel([H|T]) -->
 2539    { code_type(H, to_lower(U)) },
 2540    [U],
 2541    camel_skip(T).
 2542
 2543camel_skip([]) --> [].
 2544camel_skip([0'_|T]) --> !, camel(T).
 2545camel_skip([0'-|T]) --> !, camel(T).
 2546camel_skip([H|T]) --> !, [H], camel_skip(T).
 uncamel_case(+In:atom, -Out:atom)
Turn the commonly use CamelCase operationId into a pleasant Prolog identifier. This ensures the first character is lower case and lU sequences are translated into l_l. lUU is changed into l_UU
 2554uncamel_case(In, Out) :-
 2555    atom_codes(In, Codes),
 2556    phrase(uncamel(UnCamel), Codes),
 2557    atom_codes(Out, UnCamel).
 2558
 2559uncamel([H|T]) -->
 2560    [U],
 2561    { code_type(U, upper(H)) },
 2562    !,
 2563    uncamel_(T).
 2564uncamel(List) -->
 2565    uncamel_(List).
 2566
 2567uncamel_([L,0'_,U1,U2|T]) -->
 2568    [L,U1,U2],
 2569    { code_type(L, lower),
 2570      code_type(U1, upper),
 2571      code_type(U2, upper)
 2572    },
 2573    !,
 2574    uncamel_(T).
 2575uncamel_([L,0'_,Lower|T]) -->
 2576    [L,U],
 2577    { code_type(L, lower),
 2578      code_type(U, upper(Lower))
 2579    },
 2580    !,
 2581    uncamel_(T).
 2582uncamel_([H|T]) -->
 2583    [H],
 2584    !,
 2585    uncamel_(T).
 2586uncamel_([]) -->
 2587    [].
 doc_description(+Doc)//
Emit the summary and documentation
 2593doc_description(Doc) -->
 2594    { memberchk(summary(Summary), Doc),
 2595      memberchk(description(Desc), Doc),
 2596      string_lines(Desc, Lines)
 2597    }, !,
 2598    "%  ", atom(Summary), "\n",
 2599    lines(Lines, "%  "),
 2600    "%\n".
 2601doc_description(Doc) -->
 2602    { memberchk(description(Desc), Doc),
 2603      string_lines(Desc, Lines)
 2604    }, !,
 2605    lines(Lines, "%  "),
 2606    "%\n".
 2607doc_description(Doc) -->
 2608    { memberchk(summary(Summary), Doc)
 2609    }, !,
 2610    "%  ", atom(Summary), "\n",
 2611    "%\n".
 2612doc_description(_) -->  [].
 2613
 2614string_lines(String, Lines) :-
 2615    split_string(String, "\n", "", Lines0),
 2616    delete_empty_lines(Lines0, Lines1),
 2617    reverse(Lines1, Lines2),
 2618    delete_empty_lines(Lines2, Lines3),
 2619    reverse(Lines3, Lines).
 2620
 2621delete_empty_lines([Line|T0], T) :-
 2622    empty_line(Line),
 2623    !,
 2624    delete_empty_lines(T0, T).
 2625delete_empty_lines(T, T).
 2626
 2627empty_line(Line) :-
 2628    split_string(Line, " \t", " \t", [""]).
 2629
 2630lines([], _) --> [].
 2631lines([H|T], Prefix) --> atom(Prefix), atom(H), "\n", lines(T, Prefix).
 2632
 2633doc_security([public]) -->
 2634    !.
 2635doc_security(List) -->
 2636    "%  Authentication options:\n",
 2637    doc_security_list(List),
 2638    "%\n".
 2639
 2640doc_security_list([]) -->
 2641    [].
 2642doc_security_list([H|T]) -->
 2643    doc_security_option(H),
 2644    doc_security_list(T).
 2645
 2646doc_security_option(public) -->
 2647    "%   - no authentication required\n".
 2648doc_security_option(Term) -->
 2649    { arg(2, Term, Name) },
 2650    "%   - ", atom(Name), "\n".
 2651
 2652doc_args([]) --> [].
 2653doc_args([H|T]) --> doc_arg(H), doc_args(T).
 2654
 2655doc_arg(p(Name, Type, Description)) -->
 2656    indent(0),
 2657    prefix(0, ("@arg ", camel_case(Name), " "), Indent),
 2658    type(Type, Indent), "\n",
 2659    arg_description(Description).
 2660
 2661doc_path(Doc) -->
 2662    { memberchk(path(Path), Doc) },
 2663    !,
 2664    "%\n%  @see Path = ", atom(Path), "\n".
 2665doc_path(_) -->
 2666    [].
 2667
 2668arg_description(options(List)) -->
 2669    !,
 2670    arg_options(List).
 2671arg_description(Description) -->
 2672    { string_lines(Description, Lines) },
 2673    lines(Lines, "%       ").
 2674
 2675arg_options([]) --> [].
 2676arg_options([H|T]) --> arg_option(H), arg_options(T).
 2677
 2678arg_option(p(Name, Type, Description)) -->
 2679    { string_lines(Description, Lines) },
 2680    "%       - ", quoted_atom(Name), "(+", type(Type), ")", "\n",
 2681    lines(Lines, "%         ").
 type(+Type)//
 2685type(list(option)) --> !.
 2686type(url(URL)) -->
 2687    !,
 2688    { file_base_name(URL, TypeName) },
 2689    atom(TypeName).
 2690type(Type) -->
 2691    type(Type, 0).
 2692
 2693type(array(Type, Opts), Indent) -->
 2694    !,
 2695    prefix(Indent, "array(", NewIndent),
 2696    type(Type, NewIndent), ")",
 2697    (   {Opts == []}
 2698    ->  []
 2699    ;   " [", sequence(array_attr, ",", Opts), "]"
 2700    ).
 2701type(string([pattern(Pattern)]), _Indent) -->
 2702    !,
 2703    "/", atom(Pattern), "/".
 2704type(string(Attrs), _Indent) -->
 2705    { select(pattern(Pattern), Attrs, Attrs1) },
 2706    !,
 2707    "/", atom(Pattern), "/ [", sequence(str_attr, ",", Attrs1), "]".
 2708type(string(Attrs), _Indent) -->
 2709    !,
 2710    "string [", sequence(str_attr, ",", Attrs), "]".
 2711type(enum(List,_,lower), _Indent) -->
 2712    { maplist(downcase_atom, List, Lower) },
 2713    sequence(atom, "|", Lower).
 2714type(object(Properties), Indent) -->
 2715    !,
 2716    prefix(Indent, "{ ", NewIndent),
 2717    sequence(obj_property(NewIndent), (",", nl(NewIndent)), Properties),
 2718    nl(Indent), "}".
 2719type(oneOf(List), Indent) -->
 2720    !,
 2721    prefix(Indent, "( ", NewIndent),
 2722    sequence(itype(NewIndent), (nl(Indent),"| "), List),
 2723    nl(Indent), ")".
 2724type(Type, _Indent, List, Tail) :-
 2725    format(codes(List, Tail), '~p', [Type]).
 2726
 2727itype(Indent, Type) -->
 2728    type(Type, Indent).
 2729
 2730obj_property(Indent, p(Name, Type, Opts)) -->
 2731    atom(Name), ": ",
 2732    { atom_length(Name, NameL),
 2733      NewIndent is Indent+NameL+2
 2734    },
 2735    type(Type, NewIndent),
 2736    obj_property_attrs(Opts).
 2737
 2738obj_property_attrs([]) -->
 2739    !.
 2740obj_property_attrs(Opts) -->
 2741    " [", sequence(obj_property_attr, "",Opts), "]".
 2742
 2743obj_property_attr(required) --> "R".
 2744obj_property_attr(nullable) --> "N".
 2745
 2746str_attr(min_length(Len)) --> format(">=~w", [Len]).
 2747str_attr(max_length(Len)) --> format("=<~w", [Len]).
 2748
 2749array_attr(min_items(Len)) --> format(">=~w", [Len]).
 2750array_attr(max_items(Len)) --> format("=<~w", [Len]).
 2751array_attr(unique_items(true)) --> "unique".
 2752
 2753prefix(Indent, Prefix, NewIndent) -->
 2754    here(Start),
 2755    Prefix,
 2756    here(End),
 2757    { diff_len(Start, End, 0, PLen),
 2758      NewIndent is Indent+PLen
 2759    }.
 2760
 2761diff_len(Here, End, Len, Len) :-
 2762    Here == End,
 2763    !.
 2764diff_len([_|Here], End, Len0, Len) :-
 2765    Len1 is Len0+1,
 2766    diff_len(Here, End, Len1, Len).
 2767
 2768here(List,List,List).
 2769
 2770nl(Indent) -->
 2771    "\n", indent(Indent).
 2772
 2773indent(Indent) -->
 2774    "%  ", spaces(Indent).
 2775
 2776spaces(Indent) -->
 2777    format('~t~*|', [Indent]).
 2778
 2779format(Format, Args, List, Tail) :-
 2780    format(codes(List, Tail), Format, Args).
 doc_data(:ServerClauses, -OperationID, -Data:dict, +Options) is nondet
Get a dict that contains all information to produce the documentation.
 2787doc_data(Clauses, OperationId, Data, Options) :-
 2788    member(Clause, Clauses),
 2789    clause_data(Clause, Clauses, OperationId, Data, Options).
 2790
 2791clause_data(Clause, Clauses, OperationId, Data, Options) :-
 2792    Clause = openapi_handler(_Method, _PathList, Segments,
 2793                             Request, HdrParams, AsOption, OptionParam,
 2794                             Content, Responses, Security, Handler),
 2795    Data = #{arguments:Params, doc:Doc, security:Security},
 2796    Handler =.. [OperationId|Args],
 2797    (   (   Clauses = module(M)
 2798        ->  M:openapi_doc(OperationId, Doc)
 2799        ;   memberchk(openapi_doc(OperationId, Doc), Clauses)
 2800        ),
 2801        maplist(doc_param(from(Segments,
 2802                               Request, HdrParams, AsOption, OptionParam,
 2803                               Content, Responses), Options), Args, Params0),
 2804        exclude(==(-), Params0, Params)
 2805    ->  true
 2806    ;   warning(openapi(doc_failed, OperationId), Options),
 2807        fail
 2808    ).
 2809
 2810doc_param(from(Segments, Request, HdrParams, AsOption, OptionParam,
 2811               Content, Responses), Options,
 2812          Arg, Param) :-
 2813    (   segment_param(Arg, Segments, Param)
 2814    ;   request_param(Arg, Request, Param)
 2815    ;   OptionParam == Arg,
 2816        option_param(AsOption, Param)
 2817    ;   content_param(Arg, Content, Param)
 2818    ;   header_param(Arg, HdrParams, Param)
 2819    ;   response_param(Arg, Responses, Param, Options)
 2820    ;   start_debugger_fail
 2821    ), !.
 2822
 2823segment_param(Arg, Segments, p(Name, Type, Description)) :-
 2824    member(segment(Type, _, Arg0, Name, Description), Segments),
 2825    Arg == Arg0, !.
 2826
 2827request_param(Arg, Requests, Param) :-
 2828    member(R, Requests),
 2829    arg(1, R, Arg0),
 2830    Arg == Arg0, !,
 2831    doc_request_param(R, Param).
 2832
 2833param_json_type(Opts, Type) :-
 2834    memberchk(openapi(Type), Opts),
 2835    !.
 2836param_json_type(Opts, Type) :-
 2837    memberchk(list(openapi(Type0)), Opts),
 2838    Type = array(Type0).
 2839
 2840option_param(AsOption, p(options, list(option), options(Options))) :-
 2841    phrase(doc_request_params(AsOption), Options).
 2842
 2843doc_request_params([]) --> [].
 2844doc_request_params([H|T]) -->
 2845    { doc_request_param(H, Param) },
 2846    [ Param ],
 2847    doc_request_params(T).
 2848
 2849doc_request_param(Request, p(Name,Type,Description)) :-
 2850    Request =.. [Name,_Var,Options],
 2851    (   param_json_type(Options, Type)
 2852    ->  true
 2853    ;   Type = string,
 2854        warning(openapi(no_type, Name), [])
 2855    ),
 2856    (   memberchk(description(Description), Options)
 2857    ->  true
 2858    ;   Description = ""
 2859    ).
 2860
 2861content_param(Arg,
 2862              content(_MediaType, Scheme, Arg0, Description),
 2863              p(request_body, Scheme, Description)) :-
 2864    Arg == Arg0, !.
 2865
 2866header_param(Arg, HdrParams, Param) :-
 2867    member(HdrParam, HdrParams),
 2868    arg(1, HdrParam, Arg0),
 2869    Arg == Arg0,
 2870    !,
 2871    doc_request_param(HdrParam, Param).
 2872
 2873response_param(Arg, Responses, -, Options) :-
 2874    is_reponse_arg(Arg, Responses),
 2875    option(mode(client), Options),
 2876    \+ response_has_data(Responses), !.
 2877response_param(Arg, Responses, p(response, Scheme, Description), _Options) :-
 2878    member(response(Code,_As,_MediaType, Scheme, Arg0, Description),
 2879           Responses),
 2880    Arg == Arg0,
 2881    between(200, 399, Code), !.
 2882
 2883is_reponse_arg(Arg, Responses) :-
 2884    member(R, Responses),
 2885    arg(5, R, Arg0),
 2886    Arg == Arg0.
 error(+Term, +Options) is det
Print an error message. If silent(true) is an option, the error is silently ignored.
 2894error(_Term, Options) :-
 2895    option(silent(true), Options),
 2896    !.
 2897error(Term, _Options) :-
 2898    print_message(error, Term).
 warning(+Term, +Options) is det
Print an warning message. If silent(true) is an option, the warning is silently ignored.
 2905warning(_Term, Options) :-
 2906    option(silent(true), Options),
 2907    !.
 2908warning(Term, _Options) :-
 2909    print_message(warning, Term).
 2910
 2911:- if(current_prolog_flag(gui, true)). 2912start_debugger :-
 2913    current_prolog_flag(debug, true),
 2914    !,
 2915    gtrace.
 2916:- endif. 2917start_debugger.
 2918
 2919start_debugger_fail :-
 2920    start_debugger,
 2921    fail.
 2922
 2923
 2924		 /*******************************
 2925		 *        ENABLE EXPANSION	*
 2926		 *******************************/
 2927
 2928:- multifile
 2929    system:term_expansion/2. 2930
 2931system:term_expansion((:- openapi_server(File, Options)), Clauses) :-
 2932    \+ current_prolog_flag(xref, true),
 2933    expand_openapi_server(File, Options, Clauses).
 2934system:term_expansion((:- openapi_client(File, Options)), Clauses) :-
 2935    \+ current_prolog_flag(xref, true),
 2936    expand_openapi_client(File, Options, Clauses).
 2937
 2938
 2939		 /*******************************
 2940		 *           MESSAGES		*
 2941		 *******************************/
 2942
 2943:- multifile
 2944    prolog:message//1,
 2945    prolog:error_message//1,
 2946    prolog:message_context//1. 2947
 2948prolog:message(openapi(path_failed, Path-_Spec)) -->
 2949    [ 'OpenAPI: failed to generate clauses for path ~p'-[Path] ].
 2950prolog:message(openapi(no_operation_id, Method, Path, PredicateName)) -->
 2951    [ 'OpenAPI: no operationId for ~p ~p, using ~p'-
 2952      [Method, Path, PredicateName] ].
 2953prolog:message(openapi(doc_failed, OperationId)) -->
 2954    [ 'OpenAPI: failed to generate documentation for operationId ~p'-
 2955      [OperationId] ].
 2956prolog:message(openapi(no_type, Param)) -->
 2957    [ 'OpenAPI: no type for parameter ~p (assuming "string")'-[Param] ].
 2958prolog:message(openapi(unknown_type, Type, -)) -->
 2959    [ 'OpenAPI: unrecognized type `~p`'-[Type] ].
 2960prolog:message(openapi(unknown_type, Type, Format)) -->
 2961    [ 'OpenAPI: unrecognized type `~p` with format `~p`'-[Type, Format] ].
 2962prolog:message(openapi(unknown_string_format, Format)) -->
 2963    [ 'OpenAPI: Using plain "string" for string with format `~p`'-[Format] ].
 2964
 2965prolog:error_message(rest_error(missing_header(Name))) -->
 2966    [ 'REST error: missing header: ', ansi(code, '~p', [Name]) ].
 2967prolog:error_message(rest_error(Code, Term)) -->
 2968    [ 'REST error: code: ~p, data: ~p'-[Code, Term] ].
 2969prolog:error_message(openapi_invalid_reply(Code, ExCodes, Error)) -->
 2970    [ 'OpenAPI: request replied code ~p (expected one of ~p)'-[Code, ExCodes],
 2971      nl,
 2972      '  Document: ~p'-[Error]
 2973    ].
 2974prolog:message_context(rest(Name, Where, Type)) -->
 2975    [ ' (REST '-[] ],
 2976    rest_context(Name, Where, Type),
 2977    [ ')'-[] ].
 2978
 2979rest_context(body, request_body, json) -->
 2980    [ 'invalid request body'-[] ].
 2981rest_context(body, request_body, _Type) -->
 2982    [ 'request body'-[] ].
 2983rest_context(Name, Where, _Type) -->
 2984    [ '~p parameter ~p'-[Where, Name] ]