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

   72:- meta_predicate
   73    openapi_dispatch(:).
 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.
   82openapi_server(File, Options) :-
   83    throw(error(context_error(nodirective, openapi_server(File, Options)), _)).
   84
   85expand_openapi_server(File, Options,
   86                      [ (:- discontiguous((openapi_handler/10,
   87                                           openapi_doc/2,
   88                                           openapi_error_hook/3)))
   89                      | Clauses
   90                      ]) :-
   91    read_openapi_spec(File, Spec, Options, Options1),
   92    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.
  101openapi_client(File, Options) :-
  102    throw(error(context_error(nodirective,
  103                              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.
  111expand_openapi_client(File, Options, Clauses) :-
  112    read_openapi_spec(File, Spec, Options, Options1),
  113    phrase(client_clauses(Spec, Options1), Clauses).
 read_openapi_spec(+File, -Spec, +Options0, -Options) is det
  117read_openapi_spec(File, Spec, Options0, [yaml(Spec)|Options]) :-
  118    (   prolog_load_context(directory, Dir)
  119    ->  true
  120    ;   Dir = '.'
  121    ),
  122    absolute_file_name(File, Path,
  123                       [ relative_to(Dir),
  124                         extensions(['',json,yaml]),
  125                         access(read)
  126                       ]),
  127    uri_file_name(BaseURI, Path),
  128    openapi_read(Path, Spec),
  129    merge_options(Options0, [base_uri(BaseURI)], Options).
 openapi_read(+File, -Term) is det
Read an OpenAPI specification file.
  135openapi_read(File, Term) :-
  136    file_name_extension(_, yaml, File),
  137    !,
  138    setup_call_cleanup(
  139        open(File, read, In, [encoding(utf8)]),
  140        yaml_read(In, Term),
  141        close(In)).
  142openapi_read(File, Term) :-
  143    setup_call_cleanup(
  144        open(File, read, In, [encoding(utf8)]),
  145        json_read_dict(In, Term),
  146        close(In)).
  147
  148		 /*******************************
  149		 *       SERVER COMPILER	*
  150		 *******************************/
 server_clauses(+JSONTerm, +Options)//
Grammar to generate clauses that control openapi/1. Options processed:
base_uri(+URI)
Base URI for resolving types.
  160server_clauses(JSONTerm, Options) -->
  161    { dict_pairs(JSONTerm.paths, _, Paths)
  162    },
  163    root_clause(JSONTerm.servers),
  164    server_path_clauses(Paths, Options),
  165    json_schema_clauses(JSONTerm, Options).
  166
  167root_clause([Server|_]) -->
  168    { uri_components(Server.url, Components),
  169      uri_data(path, Components, Root)
  170    },
  171    [ openapi_root(Root) ].
  172
  173server_path_clauses([], _) --> [].
  174server_path_clauses([H|T], Options) -->
  175    (   server_path_clause(H, Options)
  176    ->  []
  177    ;   { error(openapi(path_failed, H), Options),
  178          start_debugger
  179        }
  180    ),
  181    server_path_clauses(T, Options).
  182
  183server_path_clause(Path-Spec, Options) -->
  184    { dict_pairs(Spec, _, Methods0),
  185      (   selectchk(parameters-Parms, Methods0, Methods)
  186      ->  Options1 = [parameters(Parms)|Options]
  187      ;   Methods = Methods0,
  188          Options1 = Options
  189      )
  190    },
  191    path_handlers(Methods, Path, Options1).
  192
  193path_handlers([], _Path, _) --> [].
  194path_handlers([Method-Spec|T], Path, Options) -->
  195    { path_handler(Path, Method, Spec, Fact, Options),
  196      path_docs(Method, Path, Spec, Docs, Options)
  197    },
  198    [Fact, Docs],
  199    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.
  206path_handler(Path, Method, Spec,
  207             openapi_handler(Method, PathList, SegmentMatches,
  208                             Request, AsOption, OptionParam,
  209                             Content, Responses, Security, Handler),
  210             Options) :-
  211    path_vars(Path, PathList, PathBindings),
  212    (   spec_parameters(Spec, ParamSpecs, Options)
  213    ->  server_parameters(ParamSpecs, PathBindings, SegmentMatches,
  214                          Request, AsOption, Params,
  215                          [ path(Path),
  216                            method(Method)
  217                          | Options
  218                          ]),
  219        (   AsOption == []
  220        ->  OptionParams = []
  221        ;   OptionParams = [OptionParam]
  222        )
  223    ;   PathBindings == []
  224    ->  SegmentMatches = [],
  225        Params = [],
  226        Request = [],
  227        AsOption = [],
  228        OptionParams = []
  229    ;   error(openapi(not_covered_path_vars(Method, Path, PathBindings)),
  230              Options),
  231        fail
  232    ),
  233    content_parameter(Method, Spec, Content, Params, Params1, Options),
  234    append(Params1, [Result|OptionParams], AllParams),
  235    dict_pairs(Spec.responses, _, ResPairs),
  236    maplist(response(Result, Options), ResPairs, Responses),
  237    spec_security(Spec, Security, Options),
  238    handler_predicate(Method, Path, Spec, PredName, Options),
  239    Handler =.. [PredName|AllParams].
  240
  241spec_parameters(Spec, Parameters, Options) :-
  242    option(parameters(Common), Options, []),
  243    (   Me = Spec.get(parameters)
  244    ->  true
  245    ;   Me = []
  246    ),
  247    append(Common, Me, Parameters),
  248    Parameters \== [].
 server_parameters(+ParamSpecs, +PathBindings, -SegmentMatches, -RequestParams, -RequestOptions, -HandlerParams, +Options) is det
  254server_parameters([], _, [], [], [], [], _).
  255server_parameters([H|T], PathB, Segs, Request, AsOption, Params, Options) :-
  256    _{name:NameS, in:"query"} :< H,
  257    !,
  258    phrase(http_param_options(H, Options), Opts),
  259    atom_string(Name, NameS),
  260    R0 =.. [Name,P0,Opts],
  261    (   Opts = [optional(true)|_],
  262        \+ option(optional(unbound), Options)
  263    ->  AsOption = [R0|AsOpts],
  264        server_parameters(T, PathB, Segs, Request, AsOpts, Params, Options)
  265    ;   Request = [R0|Req],
  266        Params  = [P0|Ps],
  267        server_parameters(T, PathB, Segs, Req, AsOption, Ps, Options)
  268    ).
  269server_parameters([H|T], PathB, [segment(Type, Seg, P0, Name, Descr)|Segs],
  270                  Req, AsOption, [P0|Ps], Options) :-
  271    _{name:NameS, in:"path"} :< H,
  272    !,
  273    atom_string(Name, NameS),
  274    (   memberchk(Name=Seg, PathB)
  275    ->  param_type(H, Type, Options),
  276        param_description(H, Descr)
  277    ;   option(path(Path), Options),
  278        option(method(Method), Options),
  279        error(openapi(missing_path_parameter(Method, Name, Path)), Options),
  280        fail
  281    ),
  282    server_parameters(T, PathB, Segs, Req, AsOption, Ps, Options).
  283server_parameters([H|T], PathB, Segs, Request, AsOption, Params, Options) :-
  284    deref(H, Param, Options),
  285    !,
  286    server_parameters([Param|T], PathB, Segs, Request, AsOption, Params, Options).
  287server_parameters([H|_], _PathB, _Segments, _Req, _AsOption, _, Options) :-
  288    error(openapi(parameter_failed(H)), Options),
  289    fail.
  290
  291http_param_options(Spec, Options) -->
  292    hp_optional(Spec),
  293    hp_type(Spec, Options),
  294    hp_description(Spec).
  295
  296hp_optional(Spec) -->
  297    { param_optional(Spec, optional) },
  298    !,
  299    [optional(true)].
  300hp_optional(_) --> [].
  301
  302hp_type(Spec, Options) -->
  303    hp_schema(Spec.get(schema), Options),
  304    !.
  305hp_type(_, _) --> [].
  306
  307hp_schema(Spec, Options) -->
  308    { json_type(Spec, Type, Options),
  309      json_param_type(Type, ParmType)
  310    },
  311    !,
  312    [ ParmType ].
  313hp_schema(_Spec, _Options) -->
  314    { start_debugger_fail }.
  315
  316json_param_type(array(Type), list(openapi(Type))) :- !.
  317json_param_type(Type, openapi(Type)).
  318
  319hp_description(Spec) -->
  320    { Descr = Spec.get(description) },
  321    !,
  322    [ description(Descr) ].
  323hp_description(_) --> [].
  324
  325deref(Spec, Yaml, Options) :-
  326    _{'$ref':Ref} :< Spec,
  327    atomic_list_concat(Segments, /, Ref),
  328    !,
  329    option(yaml(Doc), Options),
  330    yaml_subdoc(Segments, Doc, Yaml).
  331
  332yaml_subdoc([], Doc, Doc).
  333yaml_subdoc([H|T], Doc, Sub) :-
  334    (   (H == '' ; H == '#')
  335    ->  Sub0 = Doc
  336    ;   Sub0 = Doc.H
  337    ),
  338    yaml_subdoc(T, Sub0, Sub).
 path_docs(+Method, +Path, +Spec, -Docs) is det
Generate documentation clauses for an operationId
  344path_docs(Method, Path, Spec,
  345          openapi_doc(OperationID, [path(Path)|Docs]),
  346          Options) :-
  347    handler_predicate(Method, Path, Spec, OperationID, [warn(false)|Options]),
  348    phrase(path_doc(Spec), Docs).
 path_doc(+Spec)//
Generate a list of documentation properties for Path
  354path_doc(Spec) -->
  355    path_doc(summary, Spec),
  356    path_doc(description, Spec),
  357    path_doc(tags, Spec).
  358
  359path_doc(Key, Spec) -->
  360    { Value = Spec.get(Key),
  361      !,
  362      Attr =.. [Key,Value]
  363    },
  364    [Attr].
  365path_doc(_, _) --> [].
 path_vars(+PathSpec, -Segments, -Bindings) is det
  370path_vars(PathSpec, Segments, Bindings) :-
  371    string_codes(PathSpec, Codes),
  372    phrase(path_vars(Segments, Bindings), Codes).
  373
  374path_vars([Segment,Var|Segments], [VarName=Var|Bindings]) -->
  375    string(SegCodes), "{", string(VarCodes), "}",
  376    !,
  377    { atom_codes(Segment, SegCodes),
  378      atom_codes(VarName, VarCodes)
  379    },
  380    path_vars(Segments, Bindings).
  381path_vars(Segments, []) -->
  382    remainder(Codes),
  383    {   Codes == []
  384    ->  Segments = []
  385    ;   atom_codes(Segment, Codes),
  386        Segments = [Segment]
  387    }.
 content_parameter(+Method, +Spec, -Content, +Params0, -Params, +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.
  395content_parameter(Method, Spec, content(MediaType, Schema, Var, Descr),
  396                  Params, AllParams, Options) :-
  397    has_content(Method),
  398    !,
  399    request_content_type(Spec, MediaType, Schema, Options),
  400    content_description(Spec, Descr),
  401    append(Params, [Var], AllParams).
  402content_parameter(_, _, -, Params, Params, _).
  403
  404has_content(post).
  405has_content(put).
  406
  407content_description(JSON, Descr) :-
  408    Descr = JSON.get(requestBody).get(description),
  409    !.
  410content_description(_JSON, "").
  411
  412request_content_type(Spec, MediaType, Schema, Options) :-
  413    (   Body = Spec.get(requestBody)
  414    ->  true
  415    ;   Body = _{}
  416    ),
  417    !,
  418    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.
  435response(Result, Options, CodeA-Spec,
  436         response(Code, As, MediaType, Type, Result, Descr)) :-
  437    response_code(CodeA, Code, As),
  438    response_description(Spec, Descr),
  439    content_type(Spec, MediaType, Type, Options).
  440
  441response_code(default, _, error) :- !.
  442response_code(A, N, data) :-
  443    to_number(A, N).
  444
  445response_description(Spec, Descr) :-
  446    Descr = Spec.get(description),
  447    !.
  448response_description(_, "") .
 content_type(+Sec, -BodyType, -Schema, +Options) is det
Find the ContentType for the request body and, if applicable, its schema.
  455content_type(_Spec, media(application/json, []), Type, Options) :-
  456    option(type_check_results(false), Options),
  457    !,
  458    Type = (-).
  459content_type(Spec, media(application/json, []), Type, Options) :-
  460    Content = Spec.get(content),
  461    Media = Content.get('application/json'),
  462    !,
  463    (   Schema = Media.get(schema)
  464    ->  json_type(Schema, Type, Options)
  465    ;   Type = (-)
  466    ).
  467content_type(_Spec, media(Type, []), -, Options) :-
  468    option(default_request_body_type(Type0), Options),
  469    !,
  470    to_content_type(Type0, Type).
  471content_type(_Spec, media(application/json, []), -, _).
  472
  473to_content_type(Type0, Main/Sub) :-
  474    atomic(Type0),
  475    atomic_list_concat([Main,Sub], /, Type0),
  476    !.
  477to_content_type(Type, Type) :-
  478    Type = Main/Sub,
  479    must_be(atom, Main),
  480    must_be(atom, Sub).
  481to_content_type(Type, _) :-
  482    type_error(content_type, Type).
  483
  484
  485		 /*******************************
  486		 *       CLIENT COMPILER	*
  487		 *******************************/
 client_clauses(+JSONTerm, +Options)//
Generate clauses for the client. The generated clauses are:
  502client_clauses(JSONTerm, Options) -->
  503    { dict_pairs(JSONTerm.paths, _, Paths)
  504    },
  505    server_clauses(JSONTerm.servers),
  506    client_path_clauses(Paths, Options),
  507    json_schema_clauses(JSONTerm, Options).
  508
  509server_clauses([]) --> [].
  510server_clauses([H|T]) --> server_clause(H), server_clauses(T).
  511
  512server_clause(Server) -->
  513    [ openapi_server(Server.get(url)) ].
  514
  515client_path_clauses([], _) --> [].
  516client_path_clauses([H|T], Options) -->
  517    (   client_path_clause(H, Options)
  518    ->  []
  519    ;   { error(openapi(path_failed, H), Options) }
  520    ),
  521    client_path_clauses(T, Options).
  522
  523client_path_clause(Path-Spec, Options) -->
  524    { dict_pairs(Spec, _, Methods0),
  525      (   selectchk(parameters-Parms, Methods0, Methods)
  526      ->  Options1 = [parameters(Parms)|Options]
  527      ;   Methods = Methods0,
  528          Options1 = Options
  529      )
  530    },
  531    client_handlers(Methods, Path, Options1).
  532
  533client_handlers([], _, _) --> [].
  534client_handlers([H|T], Path, Options) -->
  535    { client_handler(H, Path, Clause, Options) },
  536    [Clause],
  537    client_handlers(T, Path, Options).
  538
  539client_handler(Method-Spec, PathSpec, (Head :- Body), Options) :-
  540    path_vars(PathSpec, PathList, PathBindings),
  541    handler_predicate(Method, PathSpec, Spec, PredName, Options),
  542    (   spec_parameters(Spec, ParamSpecs, Options)
  543    ->  client_parameters(ParamSpecs, PathBindings,
  544                          Params, Query, Optional,
  545                          CheckParams,
  546                          [ path(PathSpec),
  547                            method(Method)
  548                          | Options
  549                          ]),
  550        (   Optional == []
  551        ->  ClientOptionArg = []
  552        ;   ClientOptionArg = [ClientOptions]
  553        )
  554    ;   PathBindings == []
  555    ->  Params = [],
  556        Query = [],
  557        CheckParams = true,
  558        Optional = [],
  559        ClientOptionArg = []
  560    ;   error(openapi(not_covered_path_vars(Method, PathSpec, PathBindings)),
  561              Options),
  562        fail
  563    ),
  564    content_parameter(Method, Spec, Content, Params, Params1, Options),
  565    request_body(Method, PathSpec, Module, Content, ContentGoal, RequestOptions),
  566    dict_pairs(Spec.responses, _, ResPairs),
  567    maplist(response(Result, Options), ResPairs, Responses),
  568    (   response_has_data(Responses)
  569    ->  append(Params1, [Result|ClientOptionArg], AllParams)
  570    ;   append(Params1, ClientOptionArg, AllParams)
  571    ),
  572    spec_security(Spec, Security, Options),
  573    prolog_load_context(module, Module),
  574    (   PathBindings == []
  575    ->  Path = PathSpec,
  576        PathGoal = true
  577    ;   PathGoal = atomic_list_concat(PathList, Path)
  578    ),
  579    Head =.. [PredName|AllParams],
  580    Body = ( CheckParams, PathGoal, ContentGoal,
  581             openapi:assemble_query(Module, Method, Path,
  582                                    Query, Optional, ClientOptions,
  583                                    URL),
  584             context_module(CM),
  585             openapi:assemble_security(Security, CM, SecOptions),
  586             append(SecOptions, RequestOptions, OpenOptions),
  587             debug(openapi(client), '~w ~w', [Method, URL]),
  588             setup_call_cleanup(
  589                 openapi:http_open(URL, In,
  590                           [ status_code(Status),
  591                             method(Method),
  592                             header(content_type, ContentType),
  593                             request_header(accept = 'application/json')
  594                           | OpenOptions
  595                           ]),
  596                 openapi:openapi_read_reply(Status, ContentType, Responses,
  597                                            In, Result),
  598                 close(In))
  599           ).
 handler_predicate(+Method, +Path, +Spec, -PredicateName, +Options) is det
Generate a predicate name from a specification. Prefers the operationId.
  606handler_predicate(_, _, Spec, PredicateName, _Options) :-
  607    uncamel_case(Spec.get(operationId), PredicateName),
  608    !.
  609handler_predicate(Method, Path, _Spec, PredicateName, Options) :-
  610    atomic_list_concat(Segments, /, Path),
  611    reverse(Segments, RevSegments),
  612    member(Segment, RevSegments),
  613    \+ sub_atom(Segment, _, _, _, '{'),
  614    !,
  615    file_name_extension(Name, _, Segment),
  616    atomic_list_concat([Method, '_', Name], PredicateName),
  617    (   option(warn(true), Options, true)
  618    ->  warning(openapi(no_operation_id, Method, Path, PredicateName), Options)
  619    ;   true
  620    ).
 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.
  629response_has_data(Responses) :-
  630    maplist(arg(1), Responses, Codes),
  631    member(Code, Codes),
  632    \+ code_has_no_data(Code), !.
  633
  634code_has_no_data(Code) :-
  635    var(Code).                                  % errors
  636code_has_no_data(204).                          % No content
 client_parameters(+Spec, +PathBindings, -Params, -Required, -Optional, -Check, +Options)
  642client_parameters([], _, [], [], [], true, _).
  643client_parameters([H|T], PathBindings, [P0|Ps],
  644                  [qparam(Name,P0,Type,Opt)|Qs], Optional, Check, Options) :-
  645    _{name:NameS, in:"query"} :< H,
  646    param_optional(H, Opt),
  647    \+ ( Opt == optional,
  648         \+ option(optional(unbound), Options)
  649       ),
  650    !,
  651    param_type(H, Type, Options),
  652    atom_string(Name, NameS),
  653    client_parameters(T, PathBindings, Ps, Qs, Optional, Check0, Options),
  654    mkconj(Check0, true, Check).
  655client_parameters([H|T], PathBindings,
  656                  Params, Query, [qparam(Name,_,Type,optional)|OptT],
  657                  Check, Options) :-
  658    _{name:NameS, in:"query"} :< H,
  659    !,
  660    param_type(H, Type, Options),
  661    atom_string(Name, NameS),
  662    client_parameters(T, PathBindings, Params, Query, OptT, Check0, Options),
  663    mkconj(Check0, true, Check).
  664client_parameters([H|T], PathBindings, [P0|Ps], Query, Opt, Check, Options) :-
  665    _{name:NameS, in:"path"} :< H,
  666    !,
  667    atom_string(Name, NameS),
  668    param_type(H, Type, Options),
  669    (   memberchk(Name=Segment, PathBindings)
  670    ->  Check1 = openapi:segment_value(Type, Segment, P0)
  671    ;   option(path(Path), Options),
  672        option(method(Method), Options),
  673        error(openapi(missing_path_parameter(Method, Name, Path)), Options),
  674        fail
  675    ),
  676    client_parameters(T, PathBindings, Ps, Query, Opt, Check0, Options),
  677    mkconj(Check0, Check1, Check).
  678client_parameters([H|T], PathBindings, Params, Query, Opt, Check, Options) :-
  679    deref(H, Param, Options),
  680    !,
  681    client_parameters([Param|T], PathBindings, Params, Query, Opt, Check, Options).
  682
  683
  684param_optional(Spec, Optional) :-
  685    (   Spec.get(required) == false
  686    ->  Optional = optional
  687    ;   _Default = Spec.get(schema).get(default)
  688    ->  Optional = optional
  689    ;   Optional = required
  690    ).
  691
  692param_type(Spec, Type, Options) :-
  693    json_type(Spec.get(schema), Type, Options),
  694    !.
  695param_type(_Spec, any, _Options).
  696
  697param_description(Spec, Description) :-
  698    Description = Spec.get(description),
  699    !.
  700param_description(_Spec, "").
  701
  702mkconj(true, G, G) :- !.
  703mkconj(G, true, G) :- !.
  704mkconj(G1, G2,  (G1,G2)).
 request_body(+Method, +Path, +Module, +ContentSpec, -Goal, -HTTPOPenOptions) is det
Translate the request body into options for http_open/3.
  711request_body(Method, Path, Module,
  712	     content(media(application/json,_), Schema, InVar, _Descr),
  713             openapi:assemble_content(Module, Method, Path,
  714                                      json, Schema, InVar, OutVar),
  715             [ post(json(OutVar))
  716             ]) :-
  717    !.
  718request_body(Method, Path, Module,
  719	     content(media(multipart/'form-data',_), Schema, InVar, _Descr),
  720             openapi:assemble_content(Module, Method, Path,
  721                                      form_data, Schema, InVar, OutVar),
  722             [ post(form_data(OutVar))
  723             ]) :-
  724    !.
  725request_body(_, _, _, content(MediaType, _Schema, _Var, _Descr), _, _) :-
  726    !,
  727    domain_error(openapi(content_type), MediaType).
  728request_body(_, _, _, _, true, []).
  729
  730
  731		 /*******************************
  732		 *           SECURITY		*
  733		 *******************************/
 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.
  755spec_security(Spec, Security, Options) :-
  756    maplist(security(Options), Spec.get(security), Security),
  757    Security \== [],
  758    !.
  759spec_security(_, [public], _).
  760
  761security(Options, Sec, Security) :-
  762    dict_pairs(Sec, _, [Scheme-Args]),
  763    option(yaml(Doc), Options),
  764    yaml_subdoc([components, securitySchemes,Scheme], Doc, SchemeObj),
  765    security_scheme(Scheme, SchemeObj, Args, Security, Options).
  766security(_Options, Sec, public) :-
  767    dict_pairs(Sec, _, []),
  768    !.
  769
  770security_scheme(SchemeName, Dict, Args,
  771                http(Scheme, SchemeName, Args), _Options) :-
  772    _{type: "http", scheme: SchemeS} :< Dict,
  773    !,
  774    atom_string(Scheme, SchemeS).
  775security_scheme(SchemeName, Dict, Args,
  776                api_key(header(Name), SchemeName, Args), _Options) :-
  777    _{type: "apiKey", in: "header", name: NameS} :< Dict,
  778    !,
  779    atom_string(Name, NameS).
  780security_scheme(SchemeName, Dict, _, public, Options) :-
  781    warning(openapi(unknown_security_scheme(SchemeName, Dict)), Options).
  782
  783
  784		 /*******************************
  785		 *       RUNTIME SUPPORT	*
  786		 *******************************/
  787
  788:- public
  789    assemble_query/7,
  790    assemble_content/7.  791
  792assemble_query(Module, Method, Path, QParams, QOptional, QOptions, URL) :-
  793    call(Module:openapi_server(ServerBase)),
  794    convlist(client_query_param, QParams, QueryFromArgs),
  795    optional_query_params(QOptional, QOptions, QueryFromOptions),
  796    application_extra_query_parameters(Module, Method, Path, Extra),
  797    append([Extra, QueryFromArgs, QueryFromOptions], Query),
  798    (   Query == []
  799    ->  atomics_to_string([ServerBase, Path], URL)
  800    ;   phrase(array_query(Query), ArrayQuery),
  801        uri_query_components(QueryString, ArrayQuery),
  802        atomics_to_string([ServerBase, Path, "?", QueryString], URL)
  803    ).
  804
  805assemble_content(Module, Method, Path, Format, Schema, In, Content) :-
  806    (   Schema == (-)
  807    ->  Content0 = In
  808    ;   json_check(Schema, Content0, In)
  809    ),
  810    (   current_predicate(Module:extend_content/5),
  811        Module:extend_content(Method, Path, json, Content0, Content1)
  812    ->  true
  813    ;   Content1 = Content0
  814    ),
  815    output_format(Format, Content1, Content).
  816
  817output_format(json, Content, Content).
  818output_format(form_data, Dict, Form) :-
  819    dict_pairs(Dict, _, FormPairs),
  820    maplist(form_entry, FormPairs, Form).
  821
  822form_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.
  830application_extra_query_parameters(Module, Method, Path, Extra) :-
  831    current_predicate(Module:extra_query_parameters/3),
  832    Module:extra_query_parameters(Method, Path, Extra),
  833    !,
  834    must_be(list, Extra).
  835application_extra_query_parameters(_, _, _, []).
 array_query(Query)//
Rewrite Name=List into Name=E1, Name=E2, ... to support array(Type) for parameters passed as queries.
  844array_query([]) --> [].
  845array_query([Name=Value|T]) -->
  846    (   {is_list(Value)}
  847    ->  repeat_query(Value, Name)
  848    ;   [Name=Value]
  849    ),
  850    array_query(T).
  851
  852repeat_query([], _) --> [].
  853repeat_query([H|T], Name) -->
  854    [ Name=H ],
  855    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.
  862client_query_param(qparam(Name, PlValue, Type, _Required),
  863                   Name = Value) :-
  864    nonvar(PlValue),
  865    !,
  866    (   Type == any
  867    ->  Value = PlValue
  868    ;   json_check(Type, Value, PlValue)
  869    ).
  870client_query_param(qparam(_Name, _PlValue, _Type, optional), _) :-
  871    !, fail.                                    % leave to convlist/3.
  872client_query_param(qparam(_Name, PlValue, Type, required), _) :-
  873    type_error(Type, PlValue).
  874
  875optional_query_params([], _, []).
  876optional_query_params([qparam(Name, PlValue, Type, optional)|T0], Options, Q) :-
  877    Term =.. [Name,PlValue],
  878    option(Term, Options),
  879    !,
  880    json_check(Type, Value, PlValue),
  881    Q = [Name=Value|QT],
  882    optional_query_params(T0, Options, QT).
  883optional_query_params([_|T0], Options, Q) :-
  884    optional_query_params(T0, Options, Q).
 segment_value(+Type, ?Segment, ?Prolog) is det
Transform between a Segment string and the Prolog value according to Type.
  891segment_value(Type, Segment, Prolog) :-
  892    nonvar(Segment),
  893    !,
  894    uri_encoded(segment, Value, Segment),
  895    json_check(Type, Value, Prolog).
  896segment_value(Type, Segment, Prolog) :-
  897    json_check(Type, Value, Prolog),
  898    uri_encoded(segment, Value, Segment).
 openapi_read_reply(+Code, +ContentType, +Responses, +In, -Result) is det
Handle the reply at the client side.
  904:- public openapi_read_reply/5.  905
  906openapi_read_reply(Code, ContentType, Responses, In, Result) :-
  907    debug(openapi(reply), 'Got code ~p; type: ~p; response schemas: ~p',
  908          [Code, ContentType, Responses]),
  909    http_parse_header_value(content_type, ContentType, ParsedContentType),
  910    (   memberchk(response(Code, As, ExpectedContentType, Type, _Result, _Comment),
  911                  Responses)
  912    ->  true
  913    ;   read_reply(ParsedContentType, -, data, Code, In, Error),
  914        maplist(arg(1), Responses, ExCodes),
  915        throw(error(openapi_invalid_reply(Code, ExCodes, Error), _))
  916    ),
  917    content_matches(ExpectedContentType, ParsedContentType, ProcessType),
  918    read_reply(ProcessType, Type, As, Code, In, Result).
  919
  920content_matches(ContentType, ContentType, ContentType) :- !.
  921content_matches(media(Type, _), media(Type, Attrs), media(Type, Attrs)) :- !.
  922content_matches(Expected, Got, _) :-
  923    type_error(media(Expected), Got).
  924
  925read_reply(media(application/json, _), Type, As, Code, In, Result) :-
  926    json_read_dict(In, Result0, []),
  927    (   debugging(openapi(reply_object))
  928    ->  print_term(Result0, [])
  929    ;   true
  930    ),
  931    (   Type = (-)
  932    ->  Result = Result0
  933    ;   json_check(Type, Result0, Result1)
  934    ),
  935    reply_result(As, Code, Result1, Result).
  936
  937reply_result(data,  _Code, Result, Result).
  938reply_result(error, Code, Result, _ ) :-
  939    throw(error(rest_error(Code, Result), _)).
 assemble_security(+Security, +ClientModule, -HTTPOptions)
Assemble additional HTTP options from the security description.
  945:- public assemble_security/3.  946assemble_security(Security, CM, SecOptions) :-
  947    current_predicate(CM:security_options/2),
  948    CM:security_options(Security, SecOptions), !.
  949assemble_security(Security, _, []) :-
  950    memberchk(public, Security),
  951    !.
  952assemble_security(Security, _, _) :-
  953    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.
  967		 /*******************************
  968		 *          DISPATCHER		*
  969		 *******************************/
 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
  980openapi_dispatch(M:Request) :-
  981    memberchk(path(FullPath), Request),
  982    memberchk(method(Method), Request),
  983    M:openapi_root(Root),
  984    atom_concat(Root, Path, FullPath),
  985    M:openapi_handler(Method, Path, Segments,
  986                      Required, AsOption, OptionParam, Content,
  987                      Responses, _Security,
  988                      Handler),
  989    !,
  990    (   catch(openapi_run(M:Request,
  991                          Segments,
  992                          Required, AsOption, OptionParam, Content,
  993                          Responses,
  994                          Handler),
  995              Error,
  996              openapi_error(M, Error, Responses))
  997    ->  true
  998    ;   openapi_error(M, failed, Responses)
  999    ).
 1000
 1001openapi_run(Module:Request,
 1002            Segments,
 1003            Required, AsOption, OptionParam, Content,
 1004            Responses,
 1005            Handler) :-
 1006    append(Required, AsOption, RequestParams),
 1007    catch(( maplist(segment_parameter, Segments),
 1008            http_parameters([method(get)|Request], RequestParams),
 1009            request_body(Content, Request),
 1010            server_handler_options(AsOption, OptionParam)
 1011          ), IE, input_error(IE, RequestParams)),
 1012    call(Module:Handler),
 1013    catch(openapi_reply(Responses), OE,
 1014          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.
 1023input_error(error(Formal, Context), RequestParams) :-
 1024    subsumes_term(context(_, http_parameter(_)), Context),
 1025    Context = context(_, http_parameter(Param)),
 1026    debug(rest(error), 'Error in ~p; request = ~p', [Param, RequestParams]),
 1027    member(ReqParam, RequestParams),
 1028    ReqParam =.. [Param, _Value, Options],
 1029    http_param_type(Options, Type),
 1030    !,
 1031    throw(error(Formal, rest(Param, request, Type))).
 1032input_error(E, _RequestParams) :- throw(E).
 1033
 1034http_param_type(Options, Type) :-
 1035    memberchk(openapi(Type), Options),
 1036    !.
 1037http_param_type(Options, array(Type)) :-
 1038    memberchk(list(openapi(Type)), Options),
 1039    !.
 1040
 1041output_error(E) :- throw(E).
 1042
 1043:- meta_predicate
 1044    add_error_context(0, +). 1045
 1046add_error_context(Goal, C) :-
 1047    catch(Goal, error(Formal, _), throw(error(Formal, C))).
 segment_parameter(?Segment)
Fill a segment parameter
 1053segment_parameter(segment(Type, Segment, Value, Name, _Description)) :-
 1054    add_error_context(
 1055        segment_value(Type, Segment, Value),
 1056        rest(Name, path, Type)).
 1057
 1058server_handler_options([], []).
 1059server_handler_options([H|T], Options) :-
 1060    arg(1, H, Value),
 1061    (   var(Value)
 1062    ->  server_handler_options(T, Options)
 1063    ;   functor(H, Name, _),
 1064        Opt =.. [Name,Value],
 1065        Options = [Opt|OptT],
 1066        server_handler_options(T, OptT)
 1067    ).
 request_body(+ContentSpec, +Request) is det
Read the specified request body.
 1073request_body(-, _).
 1074request_body(content(media(application/json,_), -, Body, _Descr), Request) :-
 1075    !,
 1076    add_error_context(
 1077        http_read_json_dict(Request, Body),
 1078        rest(body, request_body, json)).
 1079request_body(content(media(application/json,_), Type, Body, _Descr), Request) :-
 1080    add_error_context(
 1081        http_read_json_dict(Request, Body0),
 1082        rest(body, request_body, json)),
 1083    add_error_context(
 1084        json_check(Type, Body0, Body),
 1085        rest(body, request_body, Type)).
 openapi_reply(+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.
 1104openapi_reply(Responses) :-
 1105    Responses = [R0|_],
 1106    arg(5, R0, Reply),
 1107    reply_status(Reply, Code, Data),
 1108    memberchk(response(Code, _As, MediaType, Type, _, _Descr), Responses),
 1109    openapi_reply(Code, MediaType, Type, Data).
 1110
 1111reply_status(Var, _, _) :-
 1112    var(Var), !,
 1113    instantiation_error(Var).
 1114reply_status(status(Code, Data), Code, Data) :- !.
 1115reply_status(status(Code), Code, '') :- !.
 1116reply_status(Data, 200, Data).
 1117
 1118openapi_reply(Code, _, _, '') :-
 1119    !,
 1120    format('Status: ~d~n~n', [Code]).
 1121openapi_reply(Code, media(application/json,_), -, Data) :-
 1122    !,
 1123    reply_json_dict(Data, [status(Code)]).
 1124openapi_reply(Code, media(application/json,_), Type, Data) :-
 1125    !,
 1126    json_check(Type, Out, Data),
 1127    reply_json_dict(Out, [status(Code)]).
 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.
 1139openapi_error(Module, Error, Responses) :-
 1140    map_error(Module, Error, Responses, Reply),
 1141    Responses = [R0|_],
 1142    arg(5, R0, Reply),
 1143    openapi_reply(Responses),
 1144    !.
 1145openapi_error(_Module, Error, _Responses) :-
 1146    throw(Error).
 1147
 1148map_error(Module, Error, Responses, Reply) :-
 1149    call(Module:openapi_error_hook(Error, Responses, Reply)),
 1150    !.
 1151map_error(_Module, Error, _Responses, Reply) :-
 1152    Error = error(_, Context),
 1153    nonvar(Context),
 1154    http_error_status(Context, Error, Status),
 1155    message_to_string(Error, Message),
 1156    Reply = status(Status, _{code:Status, message:Message}).
 1157
 1158http_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.
 1180		 /*******************************
 1181		 *            TYPES		*
 1182		 *******************************/
 api_type(?Type, ?Format, ?TypeID) is det
 1188api_type(Type, Format, TypeID) :-
 1189    api_type(_Name, Type, Format, TypeID), !.
 1190api_type(Type, Format, _TypeID) :-
 1191    print_message(error, openapi(unknown_type, Type, Format)),
 1192    fail.
 api_type(?Name, ?Type, ?Format, ?TypeID)
The formats defined by the OAS are:
 1199api_type(integer,  integer,    int32,       int32).
 1200api_type(long,     integer,    int64,       int64).
 1201api_type(long,     integer,    -,           integer).
 1202api_type(float,    number,     float,       float).
 1203api_type(double,   number,     double,      float).
 1204api_type(double,   number,     -,           float).
 1205api_type(string,   string,     -,           string).
 1206api_type(byte,     string,     byte,        base64).
 1207api_type(binary,   string,     binary,      binary).
 1208api_type(boolean,  boolean,    -,           boolean).
 1209api_type(date,     string,     date,        date).
 1210api_type(dateTime, string,     'date-time', date_time).
 1211api_type(password, string,     password,    password).
 1212api_type(uri,      string,     uri,         uri). % Not in OAS
 oas_type(+Type, ?In, ?Out) is det
 1216oas_type(int32, In, Out) :-
 1217    cvt_integer(In, Out),
 1218    must_be(between(-2147483648, 2147483647), Out).
 1219oas_type(int64, In, Out) :-
 1220    cvt_integer(In, Out),
 1221    must_be(between(-9223372036854775808, 9223372036854775807), Out).
 1222oas_type(integer, In, Out) :-
 1223    cvt_integer(In, Out).
 1224oas_type(number, In, Out) :-
 1225    cvt_number(In, Out).
 1226oas_type(float, In, Out) :-
 1227    (   nonvar(In)
 1228    ->  cvt_number(In, Out0),
 1229        Out is float(Out0)
 1230    ;   cvt_number(In0, Out),
 1231        In is float(In0)
 1232    ).
 1233oas_type(string, In, Out) :-
 1234    (   var(In)
 1235    ->  to_string(Out, In)
 1236    ;   to_atom(In, Out)
 1237    ).
 1238oas_type(uri, In, Out) :-
 1239    (   var(In)
 1240    ->  to_atom(Out, In)
 1241    ;   to_atom(In, Out)
 1242    ).
 1243oas_type(binary, In, Out) :-
 1244    (   var(In)
 1245    ->  to_string(Out, In)
 1246    ;   to_string(In, Out)
 1247    ).
 1248oas_type(base64, In, Out) :-
 1249    base64(In, Out).
 1250oas_type(boolean, In, Out) :-
 1251    (   var(In)
 1252    ->  to_boolean(Out, In)
 1253    ;   to_boolean(In, Out)
 1254    ).
 1255oas_type(date, In, Out) :-
 1256    xsd_time_string(Out, 'http://www.w3.org/2001/XMLSchema#date', In).
 1257oas_type(date_time, In, Out) :-
 1258    xsd_time_string(Out, 'http://www.w3.org/2001/XMLSchema#dateTime', In).
 1259oas_type(password, In, Out) :-
 1260    (   var(In)
 1261    ->  to_string(Out, In)
 1262    ;   to_string(In, Out)
 1263    ).
 1264
 1265cvt_integer(In, Out) :-
 1266    cvt_number(In, Out),
 1267    must_be(integer, Out).
 1268
 1269cvt_number(In, Out) :- nonvar(In), !, to_number(In, Out).
 1270cvt_number(N, N)    :- must_be(number, N).
 1271
 1272to_number(In, Out) :-
 1273    (   number(In)
 1274    ->  Out = In
 1275    ;   atom_number(In, Out0)
 1276    ->  Out = Out0
 1277    ;   type_error(number, In)
 1278    ).
 1279
 1280to_string(Val, String) :-
 1281    atom_string(Val, String).
 1282
 1283to_atom(Val, Atom) :-
 1284    atom_string(Atom, Val).
 1285
 1286to_boolean(Var, _) :-
 1287    var(Var),
 1288    !,
 1289    instantiation_error(Var).
 1290to_boolean(false,   false).
 1291to_boolean(true,    true).
 1292to_boolean('FALSE', false).
 1293to_boolean('TRUE',  true).
 1294to_boolean(0,       false).
 1295to_boolean(1,       true).
 1296to_boolean(no,      false).
 1297to_boolean(yes,     true).
 1298to_boolean('NO',    false).
 1299to_boolean('YES',   true).
 1300to_boolean(off,     false).
 1301to_boolean(on,      true).
 1302to_boolean('OFF',   false).
 1303to_boolean('ON',    true).
 json_check(+Spec, ?JSONIn, ?JSONOut) is det
Validate a JSON object.
Errors
- type_error(Expected, Value)
- existence_error(json_schema, URL)
 1312json_check(url(URL), In, Out) :-
 1313    !,
 1314    (   json_schema(URL, Type)
 1315    ->  json_check(Type, In, Out)
 1316    ;   existence_error(json_schema, URL)
 1317    ).
 1318json_check(object, In, Out) :-
 1319    !,
 1320    In = Out,
 1321    (   is_json_object(In)
 1322    ->  true
 1323    ;   type_error(object, In)
 1324    ).
 1325json_check(object(Properties), In, Out) :-
 1326    !,
 1327    (   nonvar(In)
 1328    ->  json_object_pairs(In, InPairs),
 1329        obj_properties_in(InPairs, Properties, OutPairs),
 1330        dict_pairs(Out, _, OutPairs)
 1331    ;   json_object_pairs(Out, OutPairs),
 1332        obj_properties_out(OutPairs, Properties, InPairs),
 1333        dict_pairs(In, _, InPairs)
 1334    ).
 1335json_check(array(Type), In, Out) :-
 1336    !,
 1337    (   is_list(In)
 1338    ->  maplist(json_check(Type), In, Out)
 1339    ;   is_list(Out)
 1340    ->  maplist(json_check(Type), In, Out)
 1341    ;   must_be(list, In, Out)
 1342    ).
 1343json_check(oneOf(Types), In, Out) :-
 1344    !,
 1345    (   nonvar(In)
 1346    ->  append(_, [Type|Rest], Types),
 1347        catch(json_check(Type, In, Out), _, fail),
 1348        (   member(T2, Rest),
 1349            catch(json_check(T2, In, _), _, fail)
 1350        ->  type_error(oneOf(Types), In)
 1351        ;   true
 1352        )
 1353    ;   append(_, [Type|Rest], Types),
 1354        catch(json_check(Type, In, Out), _, fail),
 1355        (   member(T2, Rest),
 1356            catch(json_check(T2, _, Out), _, fail)
 1357        ->  type_error(oneOf(Types), Out)
 1358        ;   true
 1359        )
 1360    ).
 1361json_check(allOf(Types), In, Out) :-
 1362    !,
 1363    (   nonvar(In)
 1364    ->  maplist(json_check_in_out_type(In), Outs, Types),
 1365        join_dicts(Outs, Out)
 1366    ;   maplist(json_check_out_in_type(Out), Ins, Types),
 1367        join_dicts(Ins, In)
 1368    ).
 1369json_check(anyOf(Types), In, Out) :-
 1370    !,
 1371    (   member(Type, Types),
 1372        catch(json_check(Type, In, Out), _, fail)
 1373    ->  true
 1374    ;   nonvar(In)
 1375    ->  type_error(oneOf(Types), In)
 1376    ;   type_error(oneOf(Types), Out)
 1377    ).
 1378json_check(not(Type), In, Out) :-
 1379    !,
 1380    (   \+ catch(json_check(Type, In, Out), _, fail)
 1381    ->  In = Out
 1382    ;   (   nonvar(In)
 1383        ->  type_error(not(Type), In)
 1384        ;   type_error(not(Type), Out)
 1385        )
 1386    ).
 1387json_check(enum(Values), In, Out) :-
 1388    !,
 1389    oas_type(string, In, Out),
 1390    (   memberchk(Out, Values)
 1391    ->  true
 1392    ;   domain_error(oneof(Values), Out)
 1393    ).
 1394json_check(numeric(Type, Domain), In, Out) :-
 1395    !,
 1396    oas_type(Type, In, Out),
 1397    (   number_in_domain(Domain, Out)
 1398    ->  true
 1399    ;   domain_error(Domain, Out)
 1400    ).
 1401json_check(any, In, Out) :-
 1402    !,
 1403    In = Out.
 1404json_check(Type, In, Out) :-
 1405    oas_type(Type, In, Out).
 1406
 1407json_check_in_out_type(In, Out, Type) :- json_check(Type, In, Out).
 1408json_check_out_in_type(Out, In, Type) :- json_check(Type, In, Out).
 1409
 1410number_in_domain(between(Min, Max), Value) :-
 1411    Value >= Min,
 1412    Value =< Max.
 1413number_in_domain(max(Max), Value) :-
 1414    Value =< Max.
 1415number_in_domain(min(Min), Value) :-
 1416    Value >= Min.
 is_json_object(@Term) is semidet
True when Term can be used as a JSON object mapping.
 1422is_json_object(Dict) :-
 1423    is_dict(Dict, _), !.
 1424is_json_object(json(Attrs)) :-
 1425    is_list(Attrs),
 1426    maplist(name_value, Attrs).
 1427
 1428name_value(Name = _Value) :- atomic(Name).
 1429name_value(Term) :- compound(Term), compound_name_arity(Term, _, 1).
 1430
 1431json_object_pairs(Dict, Pairs) :-
 1432    is_dict(Dict, _),
 1433    !,
 1434    dict_pairs(Dict, _, Pairs).
 1435json_object_pairs(json(List), Pairs) :-
 1436    is_list(List),
 1437    maplist(name_value, List, Keys, Values),
 1438    !,
 1439    pairs_keys_values(Pairs0, Keys, Values),
 1440    keysort(Pairs0, Pairs).
 1441json_object_pairs(Obj, _) :-
 1442    type_error(json_object, Obj).
 1443
 1444name_value(Name - Value, Name, Value) :- !.
 1445name_value(Name = Value, Name, Value) :- !.
 1446name_value(Term, Name, Value) :- Term =.. [Name,Value].
 obj_properties_in(+InPairs, +Spec, -OutPairs)
 1450obj_properties_in([], Spec, []) :-
 1451    !,
 1452    check_missing(Spec).
 1453obj_properties_in(List, [], List) :-
 1454    !.
 1455obj_properties_in([NV|T0], PL, [NV|T]) :-
 1456    PL = [p(P,_,_)|_],
 1457    NV = N-_,
 1458    N @< P,
 1459    !,
 1460    obj_properties_in(T0, PL, T).
 1461obj_properties_in([N-V0|T0], [p(N,Type,_Req)|PT], [N-V|T]) :-
 1462    !,
 1463    json_check(Type, V0, V),
 1464    obj_properties_in(T0, PT, T).
 1465obj_properties_in(T0, [p(N,_Type,Req)|PT], T) :-
 1466    (   Req == false
 1467    ->  obj_properties_in(T0, PT, T)
 1468    ;   existence_error(json_property, N)
 1469    ).
 1470
 1471check_missing([]).
 1472check_missing([p(N,_Type,Req)|T]) :-
 1473    (   Req == false
 1474    ->  check_missing(T)
 1475    ;   existence_error(json_property, N)
 1476    ).
 obj_properties_out(+OutPairs, +Spec, -InPairs)
 1480obj_properties_out([], Spec, []) :-
 1481    !,
 1482    check_missing(Spec).
 1483obj_properties_out(List, [], List) :-
 1484    !.
 1485obj_properties_out([NV|T0], PL, [NV|T]) :-
 1486    PL = [p(P,_,_)|_],
 1487    NV = N-_,
 1488    N @< P,
 1489    !,
 1490    obj_properties_out(T0, PL, T).
 1491obj_properties_out([N-V0|T0], [p(N,Type,_Req)|PT], [N-V|T]) :-
 1492    !,
 1493    json_check(Type, V, V0),
 1494    obj_properties_out(T0, PT, T).
 1495obj_properties_out(T0, [p(N,_Type,Req)|PT], T) :-
 1496    (   Req == false
 1497    ->  obj_properties_out(T0, PT, T)
 1498    ;   existence_error(json_property, N)
 1499    ).
 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.
 1506join_dicts([One], One) :- !.
 1507join_dicts([H1,H2|T], Dict) :-
 1508    H = H1.put(H2),
 1509    join_dicts([H|T], Dict).
 must_be(+Type, ?In, ?Out) is det
Support bi-directional type check for json_check/3.
 1515must_be(Type, In, Out) :-
 1516    (   nonvar(In)
 1517    ->  must_be(Type, In)
 1518    ;   must_be(Type, Out)
 1519    ).
 1520
 1521:- multifile
 1522    http:convert_parameter/3. 1523
 1524http:convert_parameter(openapi(Type), In, Out) :-
 1525    json_check(Type, In, Out).
 json_schema(?URL, ?Spec)
Spec is one of
 1539:- multifile
 1540    json_schema/2.
 json_schema_clauses(+JSONTerm, +Options)//
 1544json_schema_clauses(JSONTerm, Options) -->
 1545    { Schemas = JSONTerm.get(components).get(schemas),
 1546      dict_pairs(Schemas, _, SchemaPairs)
 1547    },
 1548    !,
 1549    schema_clauses(SchemaPairs, Options).
 1550json_schema_clauses(_, _) --> [].
 schema_clauses(+Specs, +Options)//
Compile the OpenAPI schema definitions into json_schema/2 clauses.
 1557schema_clauses([], _) --> [].
 1558schema_clauses([H|T], Options) -->
 1559    schema_clause(H, Options),
 1560    schema_clauses(T, Options).
 1561
 1562schema_clause(Schema-Spec, Options) -->
 1563    { json_type(Spec, Type, Options),
 1564      option(base_uri(Base), Options),
 1565      file_directory_name(Base, Dir),
 1566      atomic_list_concat([Dir, '#/components/schemas/', Schema], URL)
 1567    },
 1568    [ openapi:json_schema(URL, Type) ].
 json_type(+Spec, -Type, +Options) is det
True when Type is the type representation for the JSON type description Spec.
 1575json_type(Spec, Type, _) :-
 1576    _{type:TypeS, format:FormatS} :< Spec,
 1577    !,
 1578    atom_string(Type0, TypeS),
 1579    atom_string(Format, FormatS),
 1580    api_type(Type0, Format, Type1),
 1581    numeric_domain(Spec, Type0, Type1, Type).
 1582json_type(Spec, object(Props), Options) :-
 1583    _{required:ReqS, properties:PropSpecs} :< Spec,
 1584    !,
 1585    dict_pairs(PropSpecs, _, Pairs),
 1586    maplist(atom_string, Req, ReqS),
 1587    maplist(schema_property(Req, Options), Pairs, Props0),
 1588    sort(Props0, Props).
 1589json_type(Spec, object, _Options) :-
 1590    _{type:"object"} :< Spec,
 1591    !.
 1592json_type(Spec, array(Type), Options) :-
 1593    _{type:"array", items:IType} :< Spec,
 1594    !,
 1595    json_type(IType, Type, Options).
 1596json_type(Spec, oneOf(Types), Options) :-
 1597    _{oneOf:List} :< Spec,
 1598    !,
 1599    maplist(opts_json_type(Options), List, Types).
 1600json_type(Spec, allOf(Types), Options) :-
 1601    _{allOf:List} :< Spec,
 1602    !,
 1603    maplist(opts_json_type(Options), List, Types).
 1604json_type(Spec, anyOf(Types), Options) :-
 1605    _{anyOf:List} :< Spec,
 1606    !,
 1607    maplist(opts_json_type(Options), List, Types).
 1608json_type(Spec, not(Type), Options) :-
 1609    _{not:NSpec} :< Spec,
 1610    !,
 1611    json_type(NSpec, Type, Options).
 1612json_type(Spec, enum(Values), _) :-
 1613    _{type:"string", enum:ValuesS} :< Spec,
 1614    !,
 1615    maplist(atom_string, Values, ValuesS).
 1616json_type(Spec, Type, _) :-
 1617    _{type:TypeS} :< Spec,
 1618    !,
 1619    atom_string(Type0, TypeS),
 1620    api_type(Type0, -, Type1),
 1621    numeric_domain(Spec, Type0, Type1, Type).
 1622json_type(Spec, Type, Options) :-
 1623    _{'$ref':URLS} :< Spec,
 1624    !,
 1625    option(base_uri(Base), Options),
 1626    uri_normalized(URLS, Base, URL),
 1627    (   url_type(URL, Spec2)
 1628    ->  atom_string(NewBase, URL),
 1629        json_type(Spec2, Type, [base_uri(NewBase)|Options])
 1630    ;   Type = url(URL)
 1631    ).
 1632json_type(_Spec, _Type, _Options) :-
 1633    start_debugger_fail.
 1634
 1635opts_json_type(Options, Spec, Type) :-
 1636    json_type(Spec, Type, Options).
 1637
 1638schema_property(Reqs, Options, Name-Spec, p(Name, Type, Req)) :-
 1639    (   memberchk(Name, Reqs)
 1640    ->  Req = true
 1641    ;   Req = false
 1642    ),
 1643    json_type(Spec, Type, Options).
 1644
 1645numeric_domain(Spec, Type0, Type1, Type) :-
 1646    numeric_type(Type0),
 1647    !,
 1648    (   _{minimum:Min, maximum:Max} :< Spec
 1649    ->  Type = numeric(Type1, between(Min,Max))
 1650    ;   _{minimum:Min} :< Spec
 1651    ->  Type = numeric(Type1, min(Min))
 1652    ;   _{maximum:Max} :< Spec
 1653    ->  Type = numeric(Type1, max(Max))
 1654    ;   Type = Type1
 1655    ).
 1656numeric_domain(_, _Type0, Type, Type).
 1657
 1658numeric_type(integer).
 1659numeric_type(number).
 url_type(+URL, -Type:json) is semidet
Assuming URL points to a local file and fragment thereof that specifies a type, Type is the JSON representation of this type.
 1666url_type(URL, Type) :-
 1667    uri_components(URL, Components),
 1668    uri_data(scheme, Components, file),
 1669    uri_data(path, Components, FileEnc),
 1670    uri_data(fragment, Components, Fragment),
 1671    uri_encoded(path, File, FileEnc),
 1672    openapi_read(File, Spec),
 1673    atomic_list_concat(Segments, /, Fragment),
 1674    yaml_subdoc(Segments, Spec, Type).
 1675
 1676
 1677
 1678
 1679		 /*******************************
 1680		 *        DOC GENERATION	*
 1681		 *******************************/
 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.

 1694openapi_doc(File, Mode, Options) :-
 1695    must_be(oneof([client,server]), Mode),
 1696    read_openapi_spec(File, Spec, Options, Options1),
 1697    phrase(server_clauses(Spec, Options1), Clauses),
 1698    setup_call_cleanup(
 1699        doc_output(Stream, Close, Options),
 1700        doc_gen(Stream, File, Clauses, [mode(Mode)|Options]),
 1701        Close).
 1702
 1703doc_output(Stream, close(Stream), Options) :-
 1704    option(file(File), Options),
 1705    !,
 1706    open(File, write, Stream).
 1707doc_output(current_output, true, _).
 1708
 1709doc_gen(Stream, File, Clauses, Options) :-
 1710    findall(OperationId-Data,
 1711            doc_data(Clauses, OperationId, Data, Options), Pairs),
 1712    file_header(Stream, File, [operations(Pairs)|Options]),
 1713    forall(member(OperationId-Data, Pairs),
 1714           (   phrase(openapi_doc(OperationId, Data, Options), S)
 1715           ->  format(Stream, '~s', [S])
 1716           ;   warning(openapi(doc_failed, OperationId), Options)
 1717           )).
 1718
 1719file_header(Stream, File, Options) :-
 1720    option(mode(client), Options),
 1721    !,
 1722    client_module(Stream, File, Options),
 1723    client_options(Options, ClientOptions),
 1724    format(Stream, ':- use_module(library(openapi)).~n', []),
 1725    format(Stream, ':- use_module(library(option)).~n~n', []),
 1726    portray_clause(Stream, (:- openapi_client(File, ClientOptions))),
 1727    nl(Stream).
 1728file_header(Stream, File, Options) :-
 1729    option(mode(server), Options),
 1730    !,
 1731    format(Stream, ':- use_module(library(openapi)).~n', []),
 1732    format(Stream, ':- use_module(library(option)).~n', []),
 1733    format(Stream, ':- use_module(library(debug)).~n', []),
 1734    server_header(Stream, File, Options),
 1735    format(Stream, '~n', []),
 1736    format(Stream, ':- openapi_server(~q, []).~n~n', [File]).
 1737file_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.
 1745client_module(Stream, SpecFile, Options) :-
 1746    module_name(Module, SpecFile, Options),
 1747    option(operations(Ops), Options),
 1748    !,
 1749    format(Stream, ':- module(~q,~n~t[ ~12|', [Module]),
 1750    exports(Ops, Stream),
 1751    format(Stream, '~t~10|]).~n', []).
 1752client_module(_, _, _).
 1753
 1754module_name(Module, SpecFile, Options) :-
 1755    option(module(M), Options),
 1756    (   M == true
 1757    ->  option(file(File), Options, SpecFile),
 1758        file_base_name(File, Base),
 1759        file_name_extension(Module, _, Base)
 1760    ;   Module = M
 1761    ).
 1762
 1763exports([], _).
 1764exports([OperationId-Data|T], Stream) :-
 1765    (   T == []
 1766    ->  Sep = ''
 1767    ;   Sep = ','
 1768    ),
 1769    export(Stream, OperationId, Data.arguments, Sep),
 1770    exports(T, Stream).
 1771
 1772export(Stream, OperationId, Args, Sep) :-
 1773    length(Args, Arity),
 1774    phrase(mode_args(Args), Codes),
 1775    format(Stream, '~t~12|~q~w~t~48|% ~s~n',
 1776           [OperationId/Arity, Sep, Codes]).
 client_options(+Options, -ClientOptions) is det
Pass options for generatingn the client at runtime.
 1782client_options(Options, [warn(false),type_check_results(Mode)]) :-
 1783    option(type_check_results(Mode), Options),
 1784    !.
 1785client_options(_, [warn(false)]).
 1786
 1787server_header(Stream, File, Options) :-
 1788    (   option(httpd(true), Options)
 1789    ;   option(ui(true), Options)
 1790    ),
 1791    !,
 1792    format(Stream, ':- use_module(library(http/thread_httpd)).~n', []),
 1793    (   option(ui(true), Options)
 1794    ->  server_ui(Stream, File, Options)
 1795    ;   option(httpd(true), Options)
 1796    ->  server_restonly(Stream, Options)
 1797    ;   true
 1798    ).
 1799server_header(_,_,_).
 1800
 1801server_ui(Stream, File, _Options) :-
 1802    format(Stream, ':- use_module(library(http/http_dispatch)).~n', []),
 1803    format(Stream, ':- use_module(library(swagger_ui)).~n', []),
 1804    format(Stream, '
 1805:- http_handler(root(.),
 1806                http_redirect(see_other, root(\'swagger_ui\')),
 1807                []).
 1808:- http_handler(root(\'swagger.yaml\'),
 1809                http_reply_file(~q, []),
 1810                [id(swagger_config)]).
 1811
 1812server(Port) :-
 1813    http_server(dispatch,
 1814                [ port(Port)
 1815                ]).
 1816
 1817dispatch(Request) :-
 1818    openapi_dispatch(Request),
 1819    !.
 1820dispatch(Request) :-
 1821    http_dispatch(Request).
 1822
 1823', [File]).
 1824
 1825server_restonly(Stream, _Options) :-
 1826    format(Stream, '
 1827server(Port) :-
 1828    http_server(openapi_dispatch,
 1829                [ port(Port)
 1830                ]).
 1831
 1832', []).
 openapi_doc(+OperationID, +Data, +Options)// is det
 1836openapi_doc(OperationId, Data, Options) -->
 1837    doc_mode(OperationId, Data.arguments),
 1838    "\n%\n",
 1839    doc_description(Data.doc),
 1840    doc_security(Data.security),
 1841    doc_args(Data.arguments),
 1842    doc_path(Data.doc),
 1843    "\n",
 1844    server_skeleton(OperationId, Data.arguments, Options).
 1845
 1846server_skeleton(OperationId, Args, Options) -->
 1847    { option(mode(server), Options) },
 1848    !,
 1849    server_head(OperationId, Args), " :-",
 1850    "\n    debug(openapi, \"~p\", [",
 1851		 server_head(OperationId, Args), "]),",
 1852    "\n    Response = status(404).\n\n".
 1853server_skeleton(_,_,_) --> [].
 1854
 1855doc_mode(OperationId, Args) -->
 1856    "%! ", quoted_atom(OperationId),
 1857    "(", mode_args(Args), ") is det.".
 1858
 1859mode_args([]) --> [].
 1860mode_args([H|T]) -->
 1861    mode_arg(H),
 1862    (  {T==[]}
 1863    -> []
 1864    ;  ", ",
 1865       mode_args(T)
 1866    ).
 1867
 1868mode_arg(p(Name, _Type, _Descr)) -->
 1869    mode(Name), camel_case(Name).
 1870
 1871mode(response) --> !, "-".
 1872mode(_) --> "+".
 1873
 1874server_head(OperationId, Args) -->
 1875    quoted_atom(OperationId),
 1876    "(", arguments(Args), ")".
 1877
 1878arguments([]) --> [].
 1879arguments([H|T]) -->
 1880    argument(H),
 1881    (  {T==[]}
 1882    -> []
 1883    ;  ", ",
 1884       arguments(T)
 1885    ).
 1886
 1887argument(p(Name, _Type, _Descr)) -->
 1888    camel_case(Name).
 1889
 1890quoted_atom(Atom, List, Tail) :-
 1891    format(codes(List,Tail), '~q', [Atom]).
 camel_case(+Name)
Emit an identifier in CamelCase.
 1897camel_case(Name) -->
 1898    { camel_case(Name, Camel) },
 1899    atom(Camel).
 1900
 1901camel_case(Name, Camel) :-
 1902    atom_codes(Name, Codes),
 1903    phrase(camel(Codes), CamelCodes),
 1904    atom_codes(Camel, CamelCodes).
 1905
 1906camel([]) --> [].
 1907camel([H|T]) -->
 1908    { code_type(H, to_lower(U)) },
 1909    [U],
 1910    camel_skip(T).
 1911
 1912camel_skip([]) --> [].
 1913camel_skip([0'_|T]) --> !, camel(T).
 1914camel_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
 1922uncamel_case(In, Out) :-
 1923    atom_codes(In, Codes),
 1924    phrase(uncamel(UnCamel), Codes),
 1925    atom_codes(Out, UnCamel).
 1926
 1927uncamel([H|T]) -->
 1928    [U],
 1929    { code_type(U, upper(H)) },
 1930    !,
 1931    uncamel_(T).
 1932uncamel(List) -->
 1933    uncamel_(List).
 1934
 1935uncamel_([L,0'_,U1,U2|T]) -->
 1936    [L,U1,U2],
 1937    { code_type(L, lower),
 1938      code_type(U1, upper),
 1939      code_type(U2, upper)
 1940    },
 1941    !,
 1942    uncamel_(T).
 1943uncamel_([L,0'_,Lower|T]) -->
 1944    [L,U],
 1945    { code_type(L, lower),
 1946      code_type(U, upper(Lower))
 1947    },
 1948    !,
 1949    uncamel_(T).
 1950uncamel_([H|T]) -->
 1951    [H],
 1952    !,
 1953    uncamel_(T).
 1954uncamel_([]) -->
 1955    [].
 doc_description(+Doc)//
Emit the summary and documentation
 1961doc_description(Doc) -->
 1962    { memberchk(summary(Summary), Doc),
 1963      memberchk(description(Desc), Doc),
 1964      string_lines(Desc, Lines)
 1965    }, !,
 1966    "%  ", atom(Summary), "\n",
 1967    lines(Lines, "%  "),
 1968    "%\n".
 1969doc_description(Doc) -->
 1970    { memberchk(description(Desc), Doc),
 1971      string_lines(Desc, Lines)
 1972    }, !,
 1973    lines(Lines, "%  "),
 1974    "%\n".
 1975doc_description(Doc) -->
 1976    { memberchk(summary(Summary), Doc)
 1977    }, !,
 1978    "%  ", atom(Summary), "\n",
 1979    "%\n".
 1980doc_description(_) -->  [].
 1981
 1982string_lines(String, Lines) :-
 1983    split_string(String, "\n", "", Lines0),
 1984    delete_empty_lines(Lines0, Lines1),
 1985    reverse(Lines1, Lines2),
 1986    delete_empty_lines(Lines2, Lines3),
 1987    reverse(Lines3, Lines).
 1988
 1989delete_empty_lines([Line|T0], T) :-
 1990    empty_line(Line),
 1991    !,
 1992    delete_empty_lines(T0, T).
 1993delete_empty_lines(T, T).
 1994
 1995empty_line(Line) :-
 1996    split_string(Line, " \t", " \t", [""]).
 1997
 1998lines([], _) --> [].
 1999lines([H|T], Prefix) --> atom(Prefix), atom(H), "\n", lines(T, Prefix).
 2000
 2001doc_security([public]) -->
 2002    !.
 2003doc_security(List) -->
 2004    "%  Authentication options:\n",
 2005    doc_security_list(List),
 2006    "%\n".
 2007
 2008doc_security_list([]) -->
 2009    [].
 2010doc_security_list([H|T]) -->
 2011    doc_security_option(H),
 2012    doc_security_list(T).
 2013
 2014doc_security_option(public) -->
 2015    "%   - no authentication required\n".
 2016doc_security_option(Term) -->
 2017    { arg(2, Term, Name) },
 2018    "%   - ", atom(Name), "\n".
 2019
 2020doc_args([]) --> [].
 2021doc_args([H|T]) --> doc_arg(H), doc_args(T).
 2022
 2023doc_arg(p(Name, Type, Description)) -->
 2024    "%  @arg ", camel_case(Name), " ", type(Type), "\n",
 2025    arg_description(Description).
 2026
 2027doc_path(Doc) -->
 2028    { memberchk(path(Path), Doc) },
 2029    !,
 2030    "%\n%  @see Path = ", atom(Path), "\n".
 2031doc_path(_) -->
 2032    [].
 2033
 2034arg_description(options(List)) -->
 2035    !,
 2036    arg_options(List).
 2037arg_description(Description) -->
 2038    { string_lines(Description, Lines) },
 2039    lines(Lines, "%       ").
 2040
 2041arg_options([]) --> [].
 2042arg_options([H|T]) --> arg_option(H), arg_options(T).
 2043
 2044arg_option(p(Name, Type, Description)) -->
 2045    { string_lines(Description, Lines) },
 2046    "%       - ", quoted_atom(Name), "(+", type(Type), ")", "\n",
 2047    lines(Lines, "%         ").
 2048
 2049type(list(option)) --> !.
 2050type(url(URL)) -->
 2051    !,
 2052    { file_base_name(URL, TypeName) },
 2053    atom(TypeName).
 2054type(array(Type)) --> !,
 2055    "array(", type(Type), ")".
 2056type(Type, List, Tail) :-
 2057    format(codes(List, Tail), '~p', [Type]).
 doc_data(:ServerClauses, -OperationID, -Data:dict, +Options) is nondet
Get a dict that contains all information to produce the documentation.
 2065doc_data(Clauses, OperationId,
 2066         _{arguments:Params, doc:Doc, security:Security},
 2067         Options) :-
 2068    member(openapi_handler(_Method, _PathList, Segments,
 2069                           Request, AsOption, OptionParam,
 2070                           Content, Responses, Security, Handler), Clauses),
 2071    Handler =.. [OperationId|Args],
 2072    (   memberchk(openapi_doc(OperationId, Doc), Clauses),
 2073        maplist(doc_param(from(Segments,
 2074                               Request, AsOption, OptionParam,
 2075                               Content, Responses), Options), Args, Params0),
 2076        exclude(==(-), Params0, Params)
 2077    ->  true
 2078    ;   warning(openapi(doc_failed, OperationId), Options),
 2079        fail
 2080    ).
 2081
 2082doc_param(from(Segments, Request, AsOption, OptionParam,
 2083               Content, Responses), Options,
 2084          Arg, Param) :-
 2085    (   segment_param(Arg, Segments, Param)
 2086    ;   request_param(Arg, Request, Param)
 2087    ;   OptionParam == Arg,
 2088        option_param(AsOption, Param)
 2089    ;   content_param(Arg, Content, Param)
 2090    ;   response_param(Arg, Responses, Param, Options)
 2091    ;   start_debugger_fail
 2092    ), !.
 2093
 2094segment_param(Arg, Segments, p(Name, Type, Description)) :-
 2095    member(segment(Type, _, Arg0, Name, Description), Segments),
 2096    Arg == Arg0, !.
 2097
 2098request_param(Arg, Requests, Param) :-
 2099    member(R, Requests),
 2100    arg(1, R, Arg0),
 2101    Arg == Arg0, !,
 2102    doc_request_param(R, Param).
 2103
 2104param_json_type(Opts, Type) :-
 2105    memberchk(openapi(Type), Opts),
 2106    !.
 2107param_json_type(Opts, Type) :-
 2108    memberchk(list(openapi(Type0)), Opts),
 2109    Type = array(Type0).
 2110
 2111option_param(AsOption, p(options, list(option), options(Options))) :-
 2112    phrase(doc_request_params(AsOption), Options).
 2113
 2114doc_request_params([]) --> [].
 2115doc_request_params([H|T]) -->
 2116    { doc_request_param(H, Param) },
 2117    [ Param ],
 2118    doc_request_params(T).
 2119
 2120doc_request_param(Request, p(Name,Type,Description)) :-
 2121    Request =.. [Name,_Var,Options],
 2122    (   param_json_type(Options, Type)
 2123    ->  true
 2124    ;   Type = string,
 2125        warning(openapi(no_type, Name), [])
 2126    ),
 2127    (   memberchk(description(Description), Options)
 2128    ->  true
 2129    ;   Description = ""
 2130    ).
 2131
 2132content_param(Arg,
 2133              content(_MediaType, Scheme, Arg0, Description),
 2134              p(request_body, Scheme, Description)) :-
 2135    Arg == Arg0, !.
 2136
 2137response_param(Arg, Responses, -, Options) :-
 2138    is_reponse_arg(Arg, Responses),
 2139    option(mode(client), Options),
 2140    \+ response_has_data(Responses), !.
 2141response_param(Arg, Responses, p(response, Scheme, Description), _Options) :-
 2142    member(response(Code,_As,_MediaType, Scheme, Arg0, Description),
 2143           Responses),
 2144    Arg == Arg0,
 2145    between(200, 399, Code), !.
 2146
 2147is_reponse_arg(Arg, Responses) :-
 2148    member(R, Responses),
 2149    arg(5, R, Arg0),
 2150    Arg == Arg0.
 error(+Term, +Options) is det
Print an error message. If silent(true) is an option, the error is silently ignored.
 2158error(_Term, Options) :-
 2159    option(silent(true), Options),
 2160    !.
 2161error(Term, _Options) :-
 2162    print_message(error, Term).
 warning(+Term, +Options) is det
Print an warning message. If silent(true) is an option, the warning is silently ignored.
 2169warning(_Term, Options) :-
 2170    option(silent(true), Options),
 2171    !.
 2172warning(Term, _Options) :-
 2173    print_message(warning, Term).
 2174
 2175start_debugger :-
 2176    current_prolog_flag(debug, true),
 2177    !,
 2178    gtrace.
 2179start_debugger.
 2180
 2181start_debugger_fail :-
 2182    start_debugger,
 2183    fail.
 2184
 2185
 2186		 /*******************************
 2187		 *        ENABLE EXPANSION	*
 2188		 *******************************/
 2189
 2190:- multifile
 2191    system:term_expansion/2. 2192
 2193system:term_expansion((:- openapi_server(File, Options)), Clauses) :-
 2194    \+ current_prolog_flag(xref, true),
 2195    expand_openapi_server(File, Options, Clauses).
 2196system:term_expansion((:- openapi_client(File, Options)), Clauses) :-
 2197    \+ current_prolog_flag(xref, true),
 2198    expand_openapi_client(File, Options, Clauses).
 2199
 2200
 2201		 /*******************************
 2202		 *           MESSAGES		*
 2203		 *******************************/
 2204
 2205:- multifile
 2206    prolog:message//1,
 2207    prolog:error_message//1,
 2208    prolog:message_context//1. 2209
 2210prolog:message(openapi(path_failed, Path-_Spec)) -->
 2211    [ 'OpenAPI: failed to generate clauses for path ~p'-[Path] ].
 2212prolog:message(openapi(no_operation_id, Method, Path, PredicateName)) -->
 2213    [ 'OpenAPI: no operationId for ~p ~p, using ~p'-
 2214      [Method, Path, PredicateName] ].
 2215prolog:message(openapi(doc_failed, OperationId)) -->
 2216    [ 'OpenAPI: failed to generate documentation for operationId ~p'-
 2217      [OperationId] ].
 2218prolog:message(openapi(no_type, Param)) -->
 2219    [ 'OpenAPI: no type for parameter ~p (assuming "string")'-[Param] ].
 2220prolog:message(openapi(unknown_type, Type, -)) -->
 2221    [ 'OpenAPI: unrecognized type `~p`'-[Type] ].
 2222prolog:message(openapi(unknown_type, Type, Format)) -->
 2223    [ 'OpenAPI: unrecognized type `~p` with format `~p`'-[Type, Format] ].
 2224
 2225prolog:error_message(rest_error(Code, Term)) -->
 2226    [ 'REST error: code: ~p, data: ~p'-[Code, Term] ].
 2227prolog:error_message(openapi_invalid_reply(Code, ExCodes, Error)) -->
 2228    [ 'OpenAPI: request replied code ~p (expected one of ~p)'-[Code, ExCodes],
 2229      nl,
 2230      '  Document: ~p'-[Error]
 2231    ].
 2232prolog:message_context(rest(Name, Where, Type)) -->
 2233    [ ' (REST '-[] ],
 2234    rest_context(Name, Where, Type),
 2235    [ ')'-[] ].
 2236
 2237rest_context(body, request_body, json) -->
 2238    [ 'invalid request body'-[] ].
 2239rest_context(body, request_body, _Type) -->
 2240    [ 'request body'-[] ].
 2241rest_context(Name, Where, _Type) -->
 2242    [ '~p parameter ~p'-[Where, Name] ]