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 openapi_response/2 % :PredicateName, Responses:list 45 ]). 46:- use_module(library(apply)). 47:- use_module(library(apply_macros), []). 48:- use_module(library(debug)). 49:- use_module(library(option)). 50:- use_module(library(error)). 51:- use_module(library(base64)). 52:- use_module(library(sgml)). 53:- use_module(library(lists)). 54:- use_module(library(pairs)). 55:- use_module(library(yaml)). 56:- use_module(library(uri)). 57:- use_module(library(dcg/basics)). 58:- use_module(library(http/json)). 59:- use_module(library(http/http_json)). 60:- use_module(library(http/http_parameters)). 61:- use_module(library(http/http_header)). 62:- use_module(library(listing), [portray_clause/2, portray_clause/1]). 63:- use_module(library(pprint), [print_term/2]). 64:- use_module(library(http/http_open)). 65:- use_module(library(pcre), [re_match/3]). 66:- use_module(library(dcg/high_order), [sequence/5]). 67 68 % generated code.
78:- meta_predicate
79 openapi_dispatch( ),
80 openapi_arg( , , , ),
81 openapi_response( , ).
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.90openapi_server(File, Options) :- 91 throw(error(context_error(nodirective, openapi_server(File, Options)), _)). 92 93expand_openapi_server(File, Options, 94 [ (:- discontiguous((openapi_handler/11, 95 openapi_doc/2))), 96 (:- multifile((openapi_error_hook/3))) 97 | Clauses 98 ]) :- 99 read_openapi_spec(File, Spec, Options, Options1), 100 phrase(server_clauses(Spec, Options1), Clauses).
client.pl
spec.yaml` to create
a file that uses this directive and contains documentation for the
generated predicates.
109openapi_client(File, Options) :-
110 throw(error(context_error(nodirective,
111 openapi_client(File, Options)), _)).
119expand_openapi_client(File, Options, AllClauses) :-
120 AllClauses = [ (:- discontiguous(openapi_type/1))
121 | Clauses
122 ],
123 read_openapi_spec(File, Spec, Options, Options1),
124 phrase(client_clauses(Spec, Options1), Clauses).
128read_openapi_spec(File, Spec, Options0, [yaml(Spec)|Options]) :-
129 ( prolog_load_context(directory, Dir)
130 -> true
131 ; Dir = '.'
132 ),
133 absolute_file_name(File, Path,
134 [ relative_to(Dir),
135 extensions(['',json,yaml]),
136 access(read)
137 ]),
138 uri_file_name(BaseURI, Path),
139 openapi_read(Path, Spec),
140 merge_options(Options0, [base_uri(BaseURI)], Options).
146openapi_read(File, Term) :- 147 file_name_extension(_, yaml, File), 148 !, 149 setup_call_cleanup( 150 open(File, read, In, [encoding(utf8)]), 151 yaml_read(In, Term), 152 close(In)). 153openapi_read(File, Term) :- 154 setup_call_cleanup( 155 open(File, read, In, [encoding(utf8)]), 156 json_read_dict(In, Term), 157 close(In)). 158 159 /******************************* 160 * SERVER COMPILER * 161 *******************************/
true
)true
(default false
), generate JSON with a nice
layout.176server_clauses(JSONTerm, Options) --> 177 { dict_pairs(JSONTerm.paths, _, Paths) 178 }, 179 root_clause(JSONTerm, Options), 180 server_config_clauses(Options), 181 server_path_clauses(Paths, Options), 182 json_schema_clauses(JSONTerm, Options). 183 184root_clause(_, Options) --> 185 { option(server_url(ServerURL), Options), 186 !, 187 uri_components(ServerURL, Components), 188 uri_data(path, Components, Root) 189 }, 190 !, 191 [ openapi_root(Root) ]. 192root_clause(Spec, _Options) --> 193 { Spec.get(servers) = [Server|_], 194 !, 195 uri_components(Server.url, Components), 196 uri_data(path, Components, Root) 197 }, 198 [ openapi_root(Root) ]. 199root_clause(_Spec, _Options) --> 200 [ openapi_root('') ]. 201 202server_config_clauses(Options) --> 203 { findall(Clause, server_config(Clause, Options), Clauses) }, 204 string(Clauses). 205 206server_config(openapi_server_config(type_check_response(Mode)), Options) :- 207 option(type_check_response(Mode), Options, true). 208server_config(openapi_server_config(reply_json_options(Opts)), Options) :- 209 ( option(format_response(false), Options, false) 210 -> Opts = [width(0)] 211 ; Opts = [] 212 ). 213 214server_path_clauses([], _) --> []. 215server_path_clauses([H|T], Options) --> 216 ( server_path_clause(H, Options) 217 -> [] 218 ; { error(openapi(path_failed, H), Options), 219 start_debugger 220 } 221 ), 222 server_path_clauses(T, Options). 223 224server_path_clause(Path-Spec, Options) --> 225 { dict_pairs(Spec, _, Methods0), 226 ( selectchk(parameters-Parms0, Methods0, Methods) 227 -> deref(Parms0, Parms, Options), 228 Options1 = [parameters(Parms)|Options] 229 ; Methods = Methods0, 230 Options1 = Options 231 ) 232 }, 233 path_handlers(Methods, Path, Options1). 234 235path_handlers([], _Path, _) --> []. 236path_handlers([Method-Spec|T], Path, Options) --> 237 { path_handler(Path, Method, Spec, Fact, Options), 238 path_docs(Method, Path, Spec, Docs, Options) 239 }, 240 [Fact, Docs], 241 path_handlers(T, Path, Options).
248path_handler(Path, Method, Spec, 249 openapi_handler(Method, PathList, SegmentMatches, 250 Request, HdrParams, AsOption, OptionParam, 251 Content, Responses, Security, Handler), 252 Options) :- 253 path_vars(Path, PathList, PathBindings), 254 ( spec_parameters(Spec, ParamSpecs, Options) 255 -> server_parameters(ParamSpecs, PathBindings, SegmentMatches, 256 Request, AsOption, TypeAndArgs0, HdrParams, 257 [ path(Path), 258 method(Method) 259 | Options 260 ]), 261 ( AsOption == [] 262 -> OptionParams = [] 263 ; OptionParams = [OptionParam] 264 ) 265 ; PathBindings == [] 266 -> SegmentMatches = [], 267 TypeAndArgs0 = [], 268 HdrParams = [], 269 Request = [], 270 AsOption = [], 271 OptionParams = [] 272 ; error(openapi(not_covered_path_vars(Method, Path, PathBindings)), 273 Options), 274 fail 275 ), 276 content_parameter(Method, Spec, Content, TypeAndArgs0, TypeAndArgs, Options), 277 maplist(arg(1), TypeAndArgs, Args), 278 append(Args, [Result|OptionParams], AllArgs), 279 dict_pairs(Spec.responses, _, ResPairs), 280 maplist(response(Result, Options), ResPairs, Responses), 281 spec_security(Spec, Security, Options), 282 handler_predicate(Method, Path, Spec, PredName, Options), 283 Handler =.. [PredName|AllArgs]. 284 285spec_parameters(Spec, Parameters, Options) :- 286 option(parameters(Common), Options, []), 287 ( Me0 = Spec.get(parameters) 288 -> deref(Me0, Me, Options) 289 ; Me = [] 290 ), 291 append(Common, Me, Parameters), 292 Parameters \== [].
301server_parameters([], _, [], [], [], [], [], _). 302server_parameters([H|T], PathB, Segs, Request, AsOption, Args, HdrOpts, Options) :- 303 _{name:NameS, in:"query"} :< H, 304 !, 305 phrase(http_param_options(H, Options), Opts), 306 atom_string(Name, NameS), 307 R0 =.. [Name,P0,Opts], 308 ( Opts = [optional(true)|_], 309 \+ option(optional(unbound), Options) 310 -> AsOption = [R0|AsOpts], 311 server_parameters(T, PathB, Segs, Request, AsOpts, Args, HdrOpts, Options) 312 ; Request = [R0|Req], 313 param_type(H, Type, Options), 314 Args = [a(P0,Name,Type)|MoreArgs], 315 server_parameters(T, PathB, Segs, Req, AsOption, MoreArgs, HdrOpts, Options) 316 ). 317server_parameters([H|T], PathB, [segment(Type, Seg, A0, Name, Descr)|Segs], 318 Req, AsOption, [a(A0,Name,Type)|Args], HdrOpts, Options) :- 319 _{name:NameS, in:"path"} :< H, 320 !, 321 atom_string(Name, NameS), 322 ( memberchk(Name=Seg, PathB) 323 -> param_type(H, Type, Options), 324 param_description(H, Descr) 325 ; option(path(Path), Options), 326 option(method(Method), Options), 327 error(openapi(missing_path_parameter(Method, Name, Path)), Options), 328 fail 329 ), 330 server_parameters(T, PathB, Segs, Req, AsOption, Args, HdrOpts, Options). 331server_parameters([H|T], PathB, Segs, Req, AsOption, Args, [R0|HdrOpts], Options) :- 332 _{name:NameS, in:"header"} :< H, 333 !, 334 phrase(http_param_options(H, Options), Opts), 335 atom_string(Name, NameS), 336 R0 =.. [Name,A0,Opts], 337 ( Opts = [optional(true)|_], 338 \+ option(optional(unbound), Options) 339 -> AsOption = [R0|AsOpts], 340 server_parameters(T, PathB, Segs, Req, AsOpts, Args, HdrOpts, Options) 341 ; param_type(H, Type, Options), 342 Args = [a(A0,Name,Type)|MoreArgs], 343 server_parameters(T, PathB, Segs, Req, AsOption, MoreArgs, HdrOpts, Options) 344 ). 345server_parameters([H|T], PathB, Segs, Request, AsOption, Args, HdrOpts, Options) :- 346 deref(H, Param, Options), 347 !, 348 server_parameters([Param|T], PathB, Segs, Request, AsOption, Args, HdrOpts, Options). 349server_parameters([H|_], _PathB, _Segments, _Req, _AsOption, _, _HdrOpts, Options) :- 350 error(openapi(parameter_failed(H)), Options), 351 fail. 352 353http_param_options(Spec, Options) --> 354 hp_optional(Spec), 355 hp_type(Spec, Options), 356 hp_description(Spec). 357 358hp_optional(Spec) --> 359 { param_optional(Spec, optional) }, 360 !, 361 [optional(true)]. 362hp_optional(_) --> []. 363 364hp_type(Spec, Options) --> 365 hp_schema(Spec.get(schema), Options), 366 !. 367hp_type(_, _) --> []. 368 369hp_schema(Spec, Options) --> 370 { json_type(Spec, Type, Options), 371 json_param_type(Type, ParmType) 372 }, 373 !, 374 [ ParmType ]. 375hp_schema(_Spec, _Options) --> 376 { start_debugger_fail }. 377 378json_param_type(array(Type, _), list(openapi(Type))) :- !. 379json_param_type(Type, openapi(Type)). 380 381hp_description(Spec) --> 382 { Descr = Spec.get(description) }, 383 !, 384 [ description(Descr) ]. 385hp_description(_) --> []. 386 387deref(Spec, Yaml, Options) :- 388 is_dict(Spec), 389 _{'$ref':URLS} :< Spec, 390 sub_atom(URLS, 0, _, _, './'), 391 !, 392 option(base_uri(Base), Options), 393 uri_normalized(URLS, Base, URL), 394 url_yaml(URL, Yaml). 395deref(Spec, Yaml, Options) :- 396 is_dict(Spec), 397 _{'$ref':Ref} :< Spec, 398 atomic_list_concat(Segments, /, Ref), 399 !, 400 option(yaml(Doc), Options), 401 yaml_subdoc(Segments, Doc, Yaml). 402deref(Yaml, Yaml, _). 403 404yaml_subdoc([], Doc, Doc). 405yaml_subdoc([H|T], Doc, Sub) :- 406 ( (H == '' ; H == '#') 407 -> Sub0 = Doc 408 ; Sub0 = Doc.H 409 ), 410 yaml_subdoc(T, Sub0, Sub).
416path_docs(Method, Path, Spec,
417 openapi_doc(OperationID, [path(Path)|Docs]),
418 Options) :-
419 handler_predicate(Method, Path, Spec, OperationID, [warn(false)|Options]),
420 phrase(path_doc(Spec), Docs).
426path_doc(Spec) --> 427 path_doc(summary, Spec), 428 path_doc(description, Spec), 429 path_doc(tags, Spec). 430 431path_doc(Key, Spec) --> 432 { Value = Spec.get(Key), 433 !, 434 Attr =.. [Key,Value] 435 }, 436 [Attr]. 437path_doc(_, _) --> [].
Name=Var
, e.g.
?- path_vars('/aap/{noot}/mies', Segs, B). Segs = ['/aap/', _A, '/mies'], B = [noot=_A].
450path_vars(PathSpec, Segments, Bindings) :- 451 string_codes(PathSpec, Codes), 452 phrase(path_vars(Segments, Bindings), Codes). 453 454path_vars([Segment,Var|Segments], [VarName=Var|Bindings]) --> 455 string(SegCodes), "{", string(VarCodes), "}", 456 !, 457 { atom_codes(Segment, SegCodes), 458 atom_codes(VarName, VarCodes) 459 }, 460 path_vars(Segments, Bindings). 461path_vars(Segments, []) --> 462 remainder(Codes), 463 { Codes == [] 464 -> Segments = [] 465 ; atom_codes(Segment, Codes), 466 Segments = [Segment] 467 }.
475match_path_list([], ""). 476match_path_list([Path], Path) :- 477 !. 478match_path_list([Atom], String) :- 479 !, 480 atom_string(Atom, String). 481match_path_list([H|T], Path) :- 482 nonvar(H), 483 !, 484 string_concat(H, Rest, Path), 485 match_path_list(T, Rest). 486match_path_list([V,H|T], Path) :- 487 assertion(nonvar(H)), 488 sub_string(Path, B, _, A, H), 489 sub_string(Path, 0, B, _, V), 490 sub_string(Path, _, A, 0, Rest), 491 match_path_list(T, Rest), 492 !.
500content_parameter(Method, Spec, content(MediaType, Schema, Var, Descr), 501 Args, AllArgs, Options) :- 502 has_content(Method), 503 !, 504 request_content_type(Spec, MediaType, Schema, Options), 505 content_description(Spec, Descr), 506 append(Args, [a(Var,'RequestBody',Schema)], AllArgs). 507content_parameter(_, _, -, Args, Args, _). 508 509has_content(post). 510has_content(put). 511 512content_description(JSON, Descr) :- 513 Descr = JSON.get(requestBody).get(description), 514 !. 515content_description(_JSON, ""). 516 517request_content_type(Spec, MediaType, Schema, Options) :- 518 ( Body = Spec.get(requestBody) 519 -> true 520 ; Body = _{} 521 ), 522 !, 523 content_type(Body, MediaType, Schema, Options).
default
data
or error
540response(Result, Options, CodeA-Spec, 541 response(Code, As, MediaType, Type, Result, Descr)) :- 542 response_code(CodeA, Code, As), 543 response_description(Spec, Descr), 544 content_type(Spec, MediaType, Type, Options). 545 546response_code(default, _, error) :- !. 547response_code(A, N, data) :- 548 to_number(A, N). 549 550response_description(Spec, Descr) :- 551 Descr = Spec.get(description), 552 !. 553response_description(_, "") .
560content_type(_Spec, media(application/json, []), Type, Options) :- 561 option(type_check_request(false), Options), 562 !, 563 Type = (-). 564content_type(Spec, media(application/json, []), Type, Options) :- 565 Content = Spec.get(content), 566 Media = Content.get('application/json'), 567 !, 568 ( Schema = Media.get(schema) 569 -> json_type(Schema, Type, Options) 570 ; Type = (-) 571 ). 572content_type(_Spec, media(Type, []), -, Options) :- 573 option(default_request_body_type(Type0), Options), 574 !, 575 to_content_type(Type0, Type). 576content_type(_Spec, media(application/json, []), -, _). 577 578to_content_type(Type0, Main/Sub) :- 579 atomic(Type0), 580 atomic_list_concat([Main,Sub], /, Type0), 581 !. 582to_content_type(Type, Type) :- 583 Type = Main/Sub, 584 must_be(atom, Main), 585 must_be(atom, Sub). 586to_content_type(Type, _) :- 587 type_error(content_type, Type). 588 589 590 /******************************* 591 * CLIENT COMPILER * 592 *******************************/
openapi_server(URL)
One or more clauses describing the location of the server
as defined in the OpenAPI file. If the option
server_url(ServerURL)
is provided, this replaces the
locations found in the OpenAPI file.operationId
described in the Swagger file. The arguments
are defined by the parameters and response from the
OpenAPI specification.json_schema(URL, Type)
Clauses that define the JSON schema types.610client_clauses(JSONTerm, Options) --> 611 { dict_pairs(JSONTerm.paths, _, Paths) 612 }, 613 server_url_clauses(JSONTerm.servers, Options), 614 client_path_clauses(Paths, Options), 615 json_schema_clauses(JSONTerm, Options). 616 617server_url_clauses(_Servers, Options) --> 618 { option(server_url(ServerURL), Options) 619 }, 620 !, 621 [ openapi_server(ServerURL) ]. 622server_url_clauses(Servers, _Options) --> 623 server_url_clauses(Servers). 624 625server_url_clauses([]) --> []. 626server_url_clauses([H|T]) --> server_url_clauses(H), server_url_clauses(T). 627 628server_url_clauses(Server) --> 629 [ openapi_server(Server.get(url)) ]. 630 631client_path_clauses([], _) --> []. 632client_path_clauses([H|T], Options) --> 633 ( client_path_clause(H, Options) 634 -> [] 635 ; { error(openapi(path_failed, H), Options) } 636 ), 637 client_path_clauses(T, Options). 638 639client_path_clause(Path-Spec, Options) --> 640 { dict_pairs(Spec, _, Methods0), 641 ( selectchk(parameters-Parms, Methods0, Methods) 642 -> Options1 = [parameters(Parms)|Options] 643 ; Methods = Methods0, 644 Options1 = Options 645 ) 646 }, 647 client_handlers(Methods, Path, Options1). 648 649client_handlers([], _, _) --> []. 650client_handlers([H|T], Path, Options) --> 651 { client_handler(H, Path, Clause, TypeClause, Options) }, 652 [Clause, TypeClause], 653 client_handlers(T, Path, Options). 654 655:- det(client_handler/5). 656client_handler(Method-Spec, PathSpec, (Head :- Body), openapi_type(TypeHead), Options) :- 657 path_vars(PathSpec, PathList, PathBindings), 658 handler_predicate(Method, PathSpec, Spec, PredName, Options), 659 ( spec_parameters(Spec, ParamSpecs, Options) 660 -> client_parameters(ParamSpecs, PathBindings, 661 ArgAndTypes, HdrParams, Query, Optional, 662 CheckParams, 663 [ path(PathSpec), 664 method(Method) 665 | Options 666 ]), 667 ( Optional == [] 668 -> ClientOptionArgs = [] 669 ; ClientOptionArgs = [ClientOptions] 670 ) 671 ; PathBindings == [] 672 -> ArgAndTypes = [], 673 Query = [], 674 CheckParams = true, 675 Optional = [], 676 ClientOptionArgs = [], 677 HdrParams = [] 678 ; error(openapi(not_covered_path_vars(Method, PathSpec, PathBindings)), 679 Options), 680 fail 681 ), 682 content_parameter(Method, Spec, Content, ArgAndTypes, ArgAndTypes1, Options), 683 maplist(arg(1), ArgAndTypes1, Args), 684 maplist(client_arg, ArgAndTypes1, ClientArgs), 685 TypeHead =.. [PredName|ClientArgs], 686 request_body(Method, PathSpec, Module, Content, ContentGoal, RequestOptions), 687 dict_pairs(Spec.responses, _, ResPairs), 688 maplist(response(Result, Options), ResPairs, Responses), 689 ( response_has_data(Responses) 690 -> ResultArgs = [Result] 691 ; ResultArgs = [] 692 ), 693 append([ Args, 694 ResultArgs, 695 ClientOptionArgs 696 ], AllArgs), 697 spec_security(Spec, Security, Options), 698 prolog_load_context(module, Module), 699 ( PathBindings == [] 700 -> Path = PathSpec, 701 PathGoal = true 702 ; PathGoal = atomic_list_concat(PathList, Path) 703 ), 704 Head =.. [PredName|AllArgs], 705 Body = ( CheckParams, PathGoal, ContentGoal, 706 openapi:assemble_query(Module, Method, Path, 707 HdrParams, Query, Optional, ClientOptions, 708 URL, HdrOptions), 709 context_module(CM), 710 openapi:assemble_security(Security, CM, SecOptions), 711 append([ SecOptions, 712 RequestOptions, 713 HdrOptions 714 ], OpenOptions), 715 debug(openapi(client), '~w ~w', [Method, URL]), 716 setup_call_cleanup( 717 openapi:http_open(URL, In, 718 [ status_code(Status), 719 method(Method), 720 header(content_type, ContentType), 721 request_header(accept = 'application/json') 722 | OpenOptions 723 ]), 724 openapi:openapi_read_reply(Status, ContentType, Responses, 725 In, Result), 726 close(In)) 727 ). 728 729:- det(client_arg/2). 730client_arg(a(_, Name, Type), ArgName:Type) :- 731 camel_case(Name, ArgName).
operationId
.738handler_predicate(_, _, Spec, PredicateName, _Options) :- 739 uncamel_case(Spec.get(operationId), PredicateName), 740 !. 741handler_predicate(Method, Path, _Spec, PredicateName, Options) :- 742 atomic_list_concat(Segments, /, Path), 743 reverse(Segments, RevSegments), 744 member(Segment, RevSegments), 745 \+ sub_atom(Segment, _, _, _, '{'), 746 !, 747 file_name_extension(Name, _, Segment), 748 atomic_list_concat([Method, '_', Name], PredicateName), 749 ( option(warn(true), Options, true) 750 -> warning(openapi(no_operation_id, Method, Path, PredicateName), Options) 751 ; true 752 ).
761response_has_data(Responses) :- 762 maplist(arg(1), Responses, Codes), 763 member(Code, Codes), 764 \+ code_has_no_data(Code), !. 765 766code_has_no_data(Code) :- 767 var(Code). % errors 768code_has_no_data(204). % No content
782client_parameters([], _, [], [], [], [], true, _). 783client_parameters([H|T], PathBindings, [a(A0,Name,Type)|Args], HdrParams, 784 [qparam(Name,A0,Type,Opt)|Qs], Optional, Check, Options) :- 785 _{name:NameS, in:"query"} :< H, 786 param_optional(H, Opt), 787 \+ ( Opt == optional, 788 \+ option(optional(unbound), Options) 789 ), 790 !, 791 param_type(H, Type, Options), 792 atom_string(Name, NameS), 793 client_parameters(T, PathBindings, Args, HdrParams, Qs, Optional, Check, Options). 794client_parameters([H|T], PathBindings, [a(A0,Name,Type)|Args], 795 [hparam(Name,A0,Type,Opt)|HdrParams], 796 Query, Optional, Check, Options) :- 797 _{name:NameS, in:"header"} :< H, 798 param_optional(H, Opt), 799 \+ ( Opt == optional, 800 \+ option(optional(unbound), Options) 801 ), 802 !, 803 param_type(H, Type, Options), 804 atom_string(Name, NameS), 805 client_parameters(T, PathBindings, Args, HdrParams, Query, Optional, Check, Options). 806client_parameters([H|T], PathBindings, 807 Params, HdrParams, Query, [qparam(Name,_,Type,optional)|OptT], 808 Check, Options) :- 809 _{name:NameS, in:"query"} :< H, 810 !, 811 param_type(H, Type, Options), 812 atom_string(Name, NameS), 813 client_parameters(T, PathBindings, Params, HdrParams, 814 Query, OptT, Check, Options). 815client_parameters([H|T], PathBindings, Args, 816 [hparam(Name,_,Type,optional)|HdrParams], Query, Optional, 817 Check, Options) :- 818 _{name:NameS, in:"header"} :< H, 819 !, 820 param_type(H, Type, Options), 821 atom_string(Name, NameS), 822 client_parameters(T, PathBindings, Args, HdrParams, 823 Query, Optional, Check, Options). 824client_parameters([H|T], PathBindings, [a(A0,Name,Type)|Args], 825 HdrParams, Query, Opt, Check, Options) :- 826 _{name:NameS, in:"path"} :< H, 827 !, 828 atom_string(Name, NameS), 829 param_type(H, Type, Options), 830 ( memberchk(Name=Segment, PathBindings) 831 -> Check1 = openapi:segment_value(Type, Segment, A0) 832 ; option(path(Path), Options), 833 option(method(Method), Options), 834 error(openapi(missing_path_parameter(Method, Name, Path)), Options), 835 fail 836 ), 837 client_parameters(T, PathBindings, Args, HdrParams, 838 Query, Opt, Check0, Options), 839 mkconj(Check0, Check1, Check). 840client_parameters([H|T], PathBindings, Args, HdrParams, 841 Query, Opt, Check, Options) :- 842 deref(H, Param, Options), 843 !, 844 client_parameters([Param|T], PathBindings, Args, HdrParams, 845 Query, Opt, Check, Options). 846 847param_optional(Spec, Optional) :- 848 ( Spec.get(required) == false 849 -> Optional = optional 850 ; _Default = Spec.get(schema).get(default) 851 -> Optional = optional 852 ; Optional = required 853 ). 854 855param_type(Spec, Type, Options) :- 856 json_type(Spec.get(schema), Type, Options), 857 !. 858param_type(_Spec, any, _Options). 859 860param_description(Spec, Description) :- 861 Description = Spec.get(description), 862 !. 863param_description(_Spec, ""). 864 865mkconj(true, G, G) :- !. 866mkconj(G, true, G) :- !. 867mkconj(G1, G2, (G1,G2)).
874request_body(Method, Path, Module, 875 content(media(application/json,_), Schema, InVar, _Descr), 876 openapi:assemble_content(Module, Method, Path, 877 json, Schema, InVar, OutVar), 878 [ post(json(OutVar)) 879 ]) :- 880 !. 881request_body(Method, Path, Module, 882 content(media(multipart/'form-data',_), Schema, InVar, _Descr), 883 openapi:assemble_content(Module, Method, Path, 884 form_data, Schema, InVar, OutVar), 885 [ post(form_data(OutVar)) 886 ]) :- 887 !. 888request_body(_, _, _, content(MediaType, _Schema, _Var, _Descr), _, _) :- 889 !, 890 domain_error(openapi(content_type), MediaType). 891request_body(_, _, _, _, true, []). 892 893 894 /******************************* 895 * SECURITY * 896 *******************************/
basic
and http bearer
authentications. Name is
the name of the security scheme from the OpenAPI document.918spec_security(Spec, Security, Options) :- 919 maplist(security(Options), Spec.get(security), Security), 920 Security \== [], 921 !. 922spec_security(_, [public], _). 923 924security(Options, Sec, Security) :- 925 dict_pairs(Sec, _, [Scheme-Args]), 926 option(yaml(Doc), Options), 927 yaml_subdoc([components, securitySchemes,Scheme], Doc, SchemeObj), 928 security_scheme(Scheme, SchemeObj, Args, Security, Options). 929security(_Options, Sec, public) :- 930 dict_pairs(Sec, _, []), 931 !. 932 933security_scheme(SchemeName, Dict, Args, 934 http(Scheme, SchemeName, Args), _Options) :- 935 _{type: "http", scheme: SchemeS} :< Dict, 936 !, 937 atom_string(Scheme, SchemeS). 938security_scheme(SchemeName, Dict, Args, 939 api_key(header(Name), SchemeName, Args), _Options) :- 940 _{type: "apiKey", in: "header", name: NameS} :< Dict, 941 !, 942 atom_string(Name, NameS). 943security_scheme(SchemeName, Dict, _, public, Options) :- 944 warning(openapi(unknown_security_scheme(SchemeName, Dict)), Options). 945 946 947 /******************************* 948 * RUNTIME SUPPORT * 949 *******************************/ 950 951:- public 952 assemble_query/9, 953 assemble_content/7.
960assemble_query(Module, Method, Path, HeaderParams, QParams, QOptional, QOptions, 961 URL, OpenOptions) :- 962 call(Module:openapi_server(ServerBase)), 963 convlist(client_query_param, QParams, QueryFromArgs), 964 optional_query_params(QOptional, QOptions, QueryFromOptions), 965 application_extra_query_parameters(Module, Method, Path, Extra), 966 append([Extra, QueryFromArgs, QueryFromOptions], Query), 967 ( Query == [] 968 -> atomics_to_string([ServerBase, Path], URL) 969 ; phrase(array_query(Query), ArrayQuery), 970 uri_query_components(QueryString, ArrayQuery), 971 atomics_to_string([ServerBase, Path, "?", QueryString], URL) 972 ), 973 convlist(client_header_param(QOptions), HeaderParams, OpenOptions). 974 975assemble_content(Module, Method, Path, Format, Schema, In, Content) :- 976 ( Schema == (-) 977 -> Content0 = In 978 ; json_check(Schema, Content0, In) 979 ), 980 ( current_predicate(Module:extend_content/5), 981 Module:extend_content(Method, Path, json, Content0, Content1) 982 -> true 983 ; Content1 = Content0 984 ), 985 output_format(Format, Content1, Content). 986 987output_format(json, Content, Content). 988output_format(form_data, Dict, Form) :- 989 dict_pairs(Dict, _, FormPairs), 990 maplist(form_entry, FormPairs, Form). 991 992form_entry(Name-Value, Name=Value).
1000application_extra_query_parameters(Module, Method, Path, Extra) :- 1001 current_predicate(Module:extra_query_parameters/3), 1002 Module:extra_query_parameters(Method, Path, Extra), 1003 !, 1004 must_be(list, Extra). 1005application_extra_query_parameters(_, _, _, []).
array(Type,
Opts)
for parameters passed as queries.1014array_query([]) --> []. 1015array_query([Name=Value|T]) --> 1016 ( {is_list(Value)} 1017 -> repeat_query(Value, Name) 1018 ; [Name=Value] 1019 ), 1020 array_query(T). 1021 1022repeat_query([], _) --> []. 1023repeat_query([H|T], Name) --> 1024 [ Name=H ], 1025 repeat_query(T, Name).
1032client_query_param(qparam(Name, PlValue, Type, _Required), 1033 Name = Value) :- 1034 nonvar(PlValue), 1035 !, 1036 ( Type == any 1037 -> Value = PlValue 1038 ; json_check(Type, Value, PlValue) 1039 ). 1040client_query_param(qparam(_Name, _PlValue, _Type, optional), _) :- 1041 !, fail. % leave to convlist/3. 1042client_query_param(qparam(_Name, PlValue, Type, required), _) :- 1043 type_error(Type, PlValue). 1044 1045optional_query_params([], _, []). 1046optional_query_params([qparam(Name, PlValue, Type, optional)|T0], Options, Q) :- 1047 Term =.. [Name,PlValue], 1048 option(Term, Options), 1049 !, 1050 json_check(Type, Value, PlValue), 1051 Q = [Name=Value|QT], 1052 optional_query_params(T0, Options, QT). 1053optional_query_params([_|T0], Options, Q) :- 1054 optional_query_params(T0, Options, Q).
1060client_header_param(_QOptions, hparam(Name, PlValue, Type, _Required), 1061 request_header(Name=Value)) :- 1062 nonvar(PlValue), 1063 !, 1064 ( Type == any 1065 -> Value = PlValue 1066 ; json_check(Type, Value, PlValue) 1067 ). 1068client_header_param(QOptions, hparam(Name, _PlValue, Type, _Required), 1069 request_header(Name=Value)) :- 1070 Opt =.. [Name,PlValue], 1071 option(Opt, QOptions), 1072 !, 1073 json_check(Type, Value, PlValue). 1074client_header_param(_QOptions, hparam(Name, _PlValue, _Type, required), 1075 _) :- 1076 existence_error(openapi_option, Name).
1083segment_value(Type, Segment, Prolog) :- 1084 nonvar(Segment), 1085 !, 1086 uri_encoded(segment, Value, Segment), 1087 json_check(Type, Value, Prolog). 1088segment_value(Type, Segment, Prolog) :- 1089 json_check(Type, Value, Prolog), 1090 uri_encoded(segment, Value, Segment).
1096:- public openapi_read_reply/5. 1097 1098openapi_read_reply(Code, _ContentType, Responses, _In, Result) :- 1099 no_content(Code), 1100 !, 1101 ( memberchk(response(Code, _As, _ExpectedContentType, _Type, _Result, _Comment), 1102 Responses) 1103 -> Result = true 1104 ; maplist(arg(1), Responses, ExCodes), 1105 throw(error(openapi_invalid_reply(Code, ExCodes, ""), _)) 1106 ). 1107openapi_read_reply(Code, ContentType, Responses, In, Result) :- 1108 debug(openapi(reply), 'Got code ~p; type: ~p; response schemas: ~p', 1109 [Code, ContentType, Responses]), 1110 http_parse_header_value(content_type, ContentType, ParsedContentType), 1111 ( memberchk(response(Code, As, ExpectedContentType, Type, _Result, _Comment), 1112 Responses) 1113 -> true 1114 ; read_reply(ParsedContentType, -, data, Code, In, Error), 1115 maplist(arg(1), Responses, ExCodes), 1116 throw(error(openapi_invalid_reply(Code, ExCodes, Error), _)) 1117 ), 1118 content_matches(ExpectedContentType, ParsedContentType, ProcessType), 1119 read_reply(ProcessType, Type, As, Code, In, Result). 1120 1121no_content(204). 1122 1123content_matches(ContentType, ContentType, ContentType) :- !. 1124content_matches(media(Type, _), media(Type, Attrs), media(Type, Attrs)) :- !. 1125content_matches(Expected, Got, _) :- 1126 type_error(media(Expected), Got). 1127 1128read_reply(media(application/json, _), Type, As, Code, In, Result) :- 1129 json_read_dict(In, Result0, []), 1130 ( debugging(openapi(reply_object)) 1131 -> print_term(Result0, []) 1132 ; true 1133 ), 1134 ( Type = (-) 1135 -> Result = Result0 1136 ; json_check(Type, Result0, Result1) 1137 ), 1138 reply_result(As, Code, Result1, Result). 1139 1140reply_result(data, _Code, Result, Result). 1141reply_result(error, Code, Result, _ ) :- 1142 throw(error(rest_error(Code, Result), _)).
1148:- public assemble_security/3. 1149assemble_security(Security, CM, SecOptions) :- 1150 current_predicate(CM:security_options/2), 1151 CM:security_options(Security, SecOptions), !. 1152assemble_security(Security, _, []) :- 1153 memberchk(public, Security), 1154 !. 1155assemble_security(Security, _, _) :- 1156 existence_error(security_data, Security).
security_data
.1170 /******************************* 1171 * DISPATCHER * 1172 *******************************/
1183openapi_dispatch(M:Request) :- 1184 memberchk(path(FullPath), Request), 1185 memberchk(method(Method), Request), 1186 M:openapi_root(Root), 1187 atom_concat(Root, Path, FullPath), 1188 M:openapi_handler(Method, PathList, Segments, 1189 Required, HdrParams, AsOption, OptionParam, Content, 1190 Responses, _Security, 1191 Handler), 1192 match_path_list(PathList, Path), 1193 !, 1194 ( Error = error(_,_), 1195 catch(openapi_run(M:Request, 1196 Segments, 1197 Required, HdrParams, AsOption, OptionParam, Content, 1198 Responses, 1199 Handler), 1200 Error, 1201 openapi_error(M, Error, Responses)) 1202 -> true 1203 ; openapi_error(M, failed, Responses) 1204 ). 1205 1206openapi_run(Module:Request, 1207 Segments, 1208 Required, HdrParams, AsOption, OptionParam, Content, 1209 Responses, 1210 Handler) :- 1211 append(Required, AsOption, RequestParams), 1212 IE = error(_,_), 1213 catch(( maplist(segment_parameter, Segments), 1214 maplist(header_parameter(Request), HdrParams), 1215 http_parameters([method(get)|Request], RequestParams), 1216 request_body(Content, Request), 1217 server_handler_options(AsOption, OptionParam) 1218 ), IE, input_error(IE, RequestParams)), 1219 call(Module:Handler), 1220 OE = error(_,_), 1221 catch(openapi_reply(Module, Responses), OE, 1222 output_error(OE)).
rest(Param,
query, Type)
context.1231input_error(error(Formal, Context), RequestParams) :- 1232 subsumes_term(context(_, http_parameter(_)), Context), 1233 Context = context(_, http_parameter(Param)), 1234 debug(rest(error), 'Error in ~p; request = ~p', [Param, RequestParams]), 1235 member(ReqParam, RequestParams), 1236 ReqParam =.. [Param, _Value, Options], 1237 http_param_type(Options, Type), 1238 !, 1239 throw(error(Formal, rest(Param, request, Type))). 1240input_error(E, _RequestParams) :- throw(E). 1241 1242http_param_type(Options, Type) :- 1243 memberchk(openapi(Type), Options), 1244 !. 1245http_param_type(Options, array(Type, _)) :- 1246 memberchk(list(openapi(Type)), Options), 1247 !. 1248 1249output_error(E) :- throw(E). 1250 1251:- meta_predicate 1252 add_error_context( , ). 1253 1254add_error_context(Goal, C) :- 1255 catch(Goal, error(Formal, _), throw(error(Formal, C))).
1261segment_parameter(segment(Type, Segment, Value, Name, _Description)) :- 1262 add_error_context( 1263 segment_value(Type, Segment, Value), 1264 rest(Name, path, Type)). 1265 1266server_handler_options([], []). 1267server_handler_options([H|T], Options) :- 1268 arg(1, H, Value), 1269 ( var(Value) 1270 -> server_handler_options(T, Options) 1271 ; functor(H, Name, _), 1272 Opt =.. [Name,Value], 1273 Options = [Opt|OptT], 1274 server_handler_options(T, OptT) 1275 ).
1283header_parameter(Request, HdrParam) :-
1284 HdrParam =.. [Name, Arg, _Opts],
1285 Header =.. [Name,Arg],
1286 ( memberchk(Header, Request)
1287 -> true
1288 ; print_message(warning, error(rest_error(missing_header(Name)), _))
1289 ).
1295request_body(-, _). 1296request_body(content(media(application/json,_), -, Body, _Descr), Request) :- 1297 !, 1298 add_error_context( 1299 http_read_json_dict(Request, Body), 1300 rest(body, request_body, json)). 1301request_body(content(media(application/json,_), Type, Body, _Descr), Request) :- 1302 add_error_context( 1303 http_read_json_dict(Request, Body0), 1304 rest(body, request_body, json)), 1305 add_error_context( 1306 json_check(Type, Body0, Body), 1307 rest(body, request_body, Type)).
application/json
and Data must be suitable for
json_write_dict/3.1326:- det(openapi_reply/2). 1327openapi_reply(Module, Responses) :- 1328 Responses = [R0|_], 1329 arg(5, R0, Reply), 1330 reply_status(Reply, Code, Data), 1331 memberchk(response(Code, _As, MediaType, Type, _, _Descr), Responses), 1332 openapi_reply(Code, MediaType, Type, Data, Module). 1333 1334reply_status(Var, _, _) :- 1335 var(Var), !, 1336 instantiation_error(Var). 1337reply_status(status(Code, Data), Code, Data) :- !. 1338reply_status(status(Code), Code, '') :- !. 1339reply_status(Data, 200, Data).
1343:- det(openapi_reply/5). 1344openapi_reply(Code, _, _, '', _) :- 1345 !, 1346 format('Status: ~d~n~n', [Code]). 1347openapi_reply(Code, media(application/json,_), -, Data, Module) :- 1348 !, 1349 Module:openapi_server_config(reply_json_options(Options)), 1350 reply_json_dict(Data, [status(Code)|Options]). 1351openapi_reply(Code, media(application/json,_), Type, Data, Module) :- 1352 !, 1353 ( Module:openapi_server_config(type_check_response(true)) 1354 -> json_check(Type, Out, Data) 1355 ; Out = Data 1356 ), 1357 Module:openapi_server_config(reply_json_options(Options)), 1358 reply_json_dict(Out, [status(Code)|Options]).
1370openapi_error(Module, Error, Responses) :- 1371 map_error(Module, Error, Responses, Reply), 1372 Responses = [R0|_], 1373 arg(5, R0, Reply), 1374 openapi_reply(Module, Responses), 1375 !. 1376openapi_error(_Module, Error, _Responses) :- 1377 throw(Error). 1378 1379map_error(Module, Error, Responses, Reply) :- 1380 call(Module:openapi_error_hook(Error, Responses, Reply)), 1381 !. 1382map_error(_Module, Error, _Responses, Reply) :- 1383 Error = error(_, Context), 1384 nonvar(Context), 1385 http_error_status(Context, Error, Status), 1386 message_to_string(Error, Message), 1387 Reply = status(Status, _{code:Status, message:Message}). 1388 1389http_error_status(rest(_,_,_), _, 400).
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.1411 /******************************* 1412 * TYPES * 1413 *******************************/
1419api_type(Type, Format, TypeID) :- 1420 api_type(_Name, Type, Format, TypeID), !. 1421api_type(string, Format, string) :- 1422 !, 1423 print_message(warning, openapi(unknown_string_format, Format)). 1424api_type(Type, Format, _TypeID) :- 1425 print_message(error, openapi(unknown_type, Type, Format)), 1426 fail.
1433api_type(integer, integer, int32, int32). 1434api_type(long, integer, int64, int64). 1435api_type(long, integer, -, integer). 1436api_type(float, number, float, float). 1437api_type(double, number, double, float). 1438api_type(double, number, -, float). 1439api_type(string, string, -, string). 1440api_type(byte, string, byte, base64). 1441api_type(binary, string, binary, binary). 1442api_type(boolean, boolean, -, boolean). 1443api_type(date, string, date, date). 1444api_type(dateTime, string, 'date-time', date_time). 1445api_type(password, string, password, password). 1446api_type(string, string, string, string). % Not in OAS 1447api_type(uri, string, uri, uri). % Not in OAS 1448api_type(uuid, string, uuid, uuid). % Not in OAS
1455oas_type(int32, In, Out) :- 1456 cvt_integer(In, Out), 1457 must_be(between(-2147483648, 2147483647), Out). 1458oas_type(int64, In, Out) :- 1459 cvt_integer(In, Out), 1460 must_be(between(-9223372036854775808, 9223372036854775807), Out). 1461oas_type(integer, In, Out) :- 1462 cvt_integer(In, Out). 1463oas_type(number, In, Out) :- 1464 cvt_number(In, Out). 1465oas_type(float, In, Out) :- 1466 ( nonvar(In) 1467 -> cvt_number(In, Out0), 1468 Out is float(Out0) 1469 ; cvt_number(In0, Out), 1470 In is float(In0) 1471 ). 1472oas_type(string, In, Out) :- 1473 ( var(In) 1474 -> to_string(Out, In) 1475 ; to_atom(In, Out) 1476 ). 1477oas_type(uri, In, Out) :- 1478 ( var(In) 1479 -> to_atom(Out, In) 1480 ; to_atom(In, Out) 1481 ). 1482oas_type(uuid, In, Out) :- 1483 ( var(In) 1484 -> to_atom(Out, In) 1485 ; to_atom(In, Out) 1486 ). 1487oas_type(binary, In, Out) :- 1488 ( var(In) 1489 -> to_string(Out, In) 1490 ; to_string(In, Out) 1491 ). 1492oas_type(base64, In, Out) :- 1493 base64(In, Out). 1494oas_type(boolean, In, Out) :- 1495 ( var(In) 1496 -> to_boolean(Out, In) 1497 ; to_boolean(In, Out) 1498 ). 1499oas_type(date, In, Out) :- 1500 cvt_date_time(date, In, Out). 1501oas_type(date_time, In, Out) :- 1502 cvt_date_time(date_time, In, Out). 1503oas_type(password, In, Out) :- 1504 ( var(In) 1505 -> to_string(Out, In) 1506 ; to_string(In, Out) 1507 ).
date(Y,M,D)
or date_time(Y,M,D,H,Mn,S,0)
), a time
stamp or an xsd dateTime string.1515cvt_date_time(Format, In, Out) :- 1516 ( var(In) 1517 -> ( ( atom(Out) 1518 -> to_string(Out, In) 1519 ; string(Out) 1520 -> In = Out 1521 ) 1522 -> valid_date_time(Format, In, _) 1523 ; compound(Out) 1524 -> valid_date_time(Format, In, Out) 1525 ; number(Out) 1526 -> stamp_date_time(Out, date(Y,M,D,H,Mn,S,0,_Tz,_Dst), 'UTC'), 1527 ( Format = date_time 1528 -> valid_date_time(Format, In, date_time(Y,M,D,H,Mn,S,0)) 1529 ; valid_date_time(Format, In, date(Y,M,D)) 1530 ) 1531 ) 1532 ; valid_date_time(Format, In, Out) % creating a date/6 struct 1533 ). 1534 1535valid_date_time(date, String, Date) :- 1536 xsd_time_string(Date, % date(Y,M,D) 1537 'http://www.w3.org/2001/XMLSchema#date', 1538 String). 1539valid_date_time(date_time, String, DateTime) :- 1540 xsd_time_string(DateTime, % date_time(Y,M,D,H,Mi,S[,TZ]) 1541 'http://www.w3.org/2001/XMLSchema#dateTime', 1542 String). 1543 1544cvt_integer(In, Out) :- 1545 cvt_number(In, Out), 1546 must_be(integer, Out). 1547 1548cvt_number(In, Out) :- nonvar(In), !, to_number(In, Out). 1549cvt_number(N, N) :- must_be(number, N). 1550 1551to_number(In, Out) :- 1552 ( number(In) 1553 -> Out = In 1554 ; atom_number(In, Out0) 1555 -> Out = Out0 1556 ; type_error(number, In) 1557 ). 1558 1559to_string(Val, String) :- 1560 atom_string(Val, String). 1561 1562to_atom(Val, Atom) :- 1563 atom_string(Atom, Val). 1564 1565to_boolean(Var, _) :- 1566 var(Var), 1567 !, 1568 instantiation_error(Var). 1569to_boolean(false, false). 1570to_boolean(true, true). 1571to_boolean('FALSE', false). 1572to_boolean('TRUE', true). 1573to_boolean(0, false). 1574to_boolean(1, true). 1575to_boolean(no, false). 1576to_boolean(yes, true). 1577to_boolean('NO', false). 1578to_boolean('YES', true). 1579to_boolean(off, false). 1580to_boolean(on, true). 1581to_boolean('OFF', false). 1582to_boolean('ON', true).
1591json_check(url(URL), In, Out) :- 1592 !, 1593 ( json_schema(URL, Type) 1594 -> json_check(Type, In, Out) 1595 ; existence_error(json_schema, URL) 1596 ). 1597json_check(object, In, Out) :- 1598 !, 1599 In = Out, 1600 ( is_json_object(In) 1601 -> true 1602 ; type_error(object, In) 1603 ). 1604json_check(object(Properties), In, Out) :- 1605 !, 1606 ( nonvar(In) 1607 -> json_object_pairs(In, InPairs), 1608 obj_properties_in(InPairs, Properties, OutPairs), 1609 dict_pairs(Out, _, OutPairs) 1610 ; json_object_pairs(Out, OutPairs), 1611 obj_properties_out(OutPairs, Properties, InPairs), 1612 dict_pairs(In, _, InPairs) 1613 ). 1614json_check(array(Type, Opts), In, Out) :- 1615 !, 1616 ( is_list(In) 1617 -> check_array_length(In, Opts), 1618 maplist(json_check(Type), In, Out) 1619 ; is_list(Out) 1620 -> check_array_length(Out, Opts), 1621 maplist(json_check(Type), In, Out) 1622 ; must_be(list, In, Out) 1623 ), 1624 check_array_unique(In, Opts). 1625json_check(oneOf(Types), In, Out) :- 1626 !, 1627 Error = error(_,_), 1628 ( nonvar(In) 1629 -> candidate_types(Types, In, Candidates, Best), 1630 ( Candidates = [] % no candidate, best error 1631 -> json_check(Best, In, Out) 1632 ; Candidates = [Type] % one candidate, check 1633 -> json_check(Type, In, Out) 1634 ; append(_, [Type|Rest], Types), % find type and verify no 2nd 1635 catch(json_check(Type, In, Out), Error, fail) 1636 -> ( member(T2, Rest), 1637 catch(json_check(T2, In, _), Error, fail) 1638 -> type_error(oneOf(Types), In) 1639 ; true 1640 ) 1641 ; type_error(oneOf(Types), In) 1642 ) 1643 ; candidate_types(Types, Out, Candidates, Best), 1644 ( Candidates = [] 1645 -> json_check(Best, In, Out) 1646 ; Candidates = [Type] 1647 -> json_check(Type, In, Out) 1648 ; append(_, [Type|Rest], Candidates), 1649 catch(json_check(Type, In, Out), Error, fail) 1650 -> ( member(T2, Rest), 1651 catch(json_check(T2, _, Out), Error, fail) 1652 -> type_error(oneOf(Types), Out) 1653 ; true 1654 ) 1655 ; type_error(oneOf(Types), Out) 1656 ) 1657 ). 1658json_check(allOf(Types), In, Out) :- 1659 !, 1660 ( nonvar(In) 1661 -> maplist(json_check_in_out_type(In), Outs, Types), 1662 join_dicts(Outs, Out) 1663 ; maplist(json_check_out_in_type(Out), Ins, Types), 1664 join_dicts(Ins, In) 1665 ). 1666json_check(anyOf(Types), In, Out) :- 1667 !, 1668 ( member(Type, Types), 1669 catch(json_check(Type, In, Out), _, fail) 1670 -> true 1671 ; nonvar(In) 1672 -> type_error(oneOf(Types), In) 1673 ; type_error(oneOf(Types), Out) 1674 ). 1675json_check(not(Type), In, Out) :- 1676 !, 1677 ( \+ catch(json_check(Type, In, Out), _, fail) 1678 -> In = Out 1679 ; ( nonvar(In) 1680 -> type_error(not(Type), In) 1681 ; type_error(not(Type), Out) 1682 ) 1683 ). 1684json_check(enum(Values, CaseSensitive, Case), In, Out) :- 1685 Enum = enum(Values, CaseSensitive, Case), 1686 !, 1687 ( var(In) % Out -> In 1688 -> enum_find_ex(Out, Enum, Value), 1689 to_string(Value, In) 1690 ; enum_find_ex(In, Enum, Value), 1691 enum_case(Case, Value, Out) 1692 ). 1693json_check(numeric(Type, Domain), In, Out) :- 1694 !, 1695 oas_type(Type, In, Out), 1696 ( number_in_domain(Domain, Out) 1697 -> true 1698 ; domain_error(Domain, Out) 1699 ). 1700json_check(any, In, Out) :- 1701 !, 1702 In = Out. 1703json_check(string(Restrictions), In, Out) :- 1704 !, 1705 oas_type(string, In, Out), 1706 maplist(check_string_restriction(In), Restrictions). 1707json_check(Type, In, Out) :- 1708 oas_type(Type, In, Out). 1709 1710json_check_in_out_type(In, Out, Type) :- json_check(Type, In, Out). 1711json_check_out_in_type(Out, In, Type) :- json_check(Type, In, Out).
1718:- det(candidate_types/4). 1719candidate_types(Types, Data, Candidates, Best) :- 1720 maplist(candidate_type(Data), Types, Scores), 1721 pairs_keys_values(Best0, Types, Scores), 1722 sort(2, @>=, Best0, Best1), 1723 Best1 = [Best-_|_], 1724 convlist(is_candidate, Best1, Candidates). 1725 1726is_candidate(Type-(_-0), Type).
1734candidate_type(Data, Type, Match-Mismatch) :- 1735 State = state(0,0), 1736 candidate_type_(Type, Data, State), 1737 State = state(Match, Mismatch). 1738 1739candidate_type_(object(Props), Data, State) :- 1740 !, 1741 ( is_dict(Data) 1742 -> ( member(p(Name, Type, Opts), Props), 1743 ( Field = Data.get(Name) 1744 -> incr_match(State), 1745 candidate_type_(Type, Field, State) 1746 ; memberchk(required, Opts) 1747 -> incr_mismatch(State) 1748 ; true 1749 ), 1750 fail 1751 ; true 1752 ) 1753 ; incr_mismatch(State) 1754 ). 1755candidate_type_(Type, Data, State) :- 1756 Type = enum(_, _, _), 1757 !, 1758 ( ( atom(Data) 1759 -> true 1760 ; string(Data) 1761 ), 1762 ( enum_find(Data, Type, _Value) 1763 -> incr_match(State) 1764 ; incr_mismatch(State) 1765 ) 1766 ; incr_mismatch(State) 1767 ). 1768candidate_type_(_, _, _). 1769 1770incr_match(State) :- 1771 arg(1, State, M0), 1772 M1 is M0+1, 1773 nb_setarg(1, State, M1). 1774incr_mismatch(State) :- 1775 arg(2, State, M0), 1776 M1 is M0-1, 1777 nb_setarg(2, State, M1).
1784number_in_domain(Domain, Value) :- 1785 number_in_domain_(Domain, Value), 1786 arg(3, Domain, MultipleOf), 1787 ( MultipleOf == (-) 1788 -> true 1789 ; Times is Value/MultipleOf, 1790 round(Times) =:= Times 1791 ). 1792 1793number_in_domain_(domain(between(Min, Max), ExclMin-ExclMax, _), Value) => 1794 satisfies_min(Min, Value, ExclMin), 1795 satisfies_max(Max, Value, ExclMax). 1796number_in_domain_(domain(max(Max), ExclMax, _), Value) => 1797 satisfies_max(Max, Value, ExclMax). 1798number_in_domain_(domain(min(Min), ExclMin, _), Value) => 1799 satisfies_min(Min, Value, ExclMin). 1800 1801satisfies_max(Max, Value, false) => 1802 Value =< Max. 1803satisfies_max(Max, Value, true) => 1804 Value < Max. 1805 1806satisfies_min(Min, Value, false) => 1807 Value >= Min. 1808satisfies_min(Min, Value, true) => 1809 Value > Min.
1819enum_find(From, enum(Values, CaseSensitive, _Case), Value) :- 1820 to_atom(From, V0), 1821 ( memberchk(V0, Values) 1822 -> Value = V0 1823 ; CaseSensitive == false, 1824 downcase_atom(V0, VL), 1825 member(V1, Values), 1826 downcase_atom(V1, VL) 1827 -> Value = V1 1828 ). 1829 1830enum_find_ex(From, Enum, Value) :- 1831 ( enum_find(From, Enum, Value) 1832 -> true 1833 ; arg(1, Enum, Values), 1834 domain_error(oneof(Values), From) 1835 ). 1836 1837enum_case(preserve, Out0, Out) => Out = Out0. 1838enum_case(lower, Out0, Out) => downcase_atom(Out0, Out). 1839enum_case(upper, Out0, Out) => upcase_atom(Out0, Out). 1840 1841check_string_restriction(String, min_length(MinLen)) => 1842 string_length(String, Len), 1843 ( Len >= MinLen 1844 -> true 1845 ; domain_error(string(minLength>=MinLen), String) 1846 ). 1847check_string_restriction(String, max_length(MaxLen)) => 1848 string_length(String, Len), 1849 ( Len =< MaxLen 1850 -> true 1851 ; domain_error(string(maxLength=<MaxLen), String) 1852 ). 1853check_string_restriction(String, pattern(Pattern)) => 1854 re_match(Pattern, String, []).
1860is_json_object(Dict) :- 1861 is_dict(Dict, _), !. 1862is_json_object(json(Attrs)) :- 1863 is_list(Attrs), 1864 maplist(name_value, Attrs). 1865 1866name_value(Name = _Value) :- atomic(Name). 1867name_value(Term) :- compound(Term), compound_name_arity(Term, _, 1). 1868 1869json_object_pairs(Dict, Pairs) :- 1870 is_dict(Dict, _), 1871 !, 1872 dict_pairs(Dict, _, Pairs). 1873json_object_pairs(json(List), Pairs) :- 1874 is_list(List), 1875 maplist(name_value, List, Keys, Values), 1876 !, 1877 pairs_keys_values(Pairs0, Keys, Values), 1878 keysort(Pairs0, Pairs). 1879json_object_pairs(Obj, _) :- 1880 type_error(json_object, Obj). 1881 1882name_value(Name - Value, Name, Value) :- !. 1883name_value(Name = Value, Name, Value) :- !. 1884name_value(Term, Name, Value) :- Term =.. [Name,Value].
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?1893obj_properties_in([], Spec, []) :- 1894 !, 1895 check_missing(Spec). 1896obj_properties_in(List, [], List) :- 1897 !. 1898obj_properties_in([NV|T0], PL, [NV|T]) :- 1899 PL = [p(P,_,_)|_], 1900 NV = N-_, 1901 N @< P, 1902 !, 1903 obj_properties_in(T0, PL, T). 1904obj_properties_in([N-V0|T0], [p(N,Type,Opts)|PT], [N-V|T]) :- 1905 !, 1906 ( V0 == null, 1907 ( memberchk(nullable, Opts) 1908 ; \+ memberchk(required, Opts) 1909 ) 1910 -> V = V0 1911 ; json_check(Type, V0, V) 1912 ), 1913 obj_properties_in(T0, PT, T). 1914obj_properties_in(T0, [p(N,_Type,Opts)|PT], T) :- 1915 ( memberchk(required, Opts) 1916 -> existence_error(json_property, N) 1917 ; obj_properties_in(T0, PT, T) 1918 ). 1919 1920check_missing([]). 1921check_missing([p(N,_Type,Opts)|T]) :- 1922 ( memberchk(required, Opts) 1923 -> existence_error(json_property, N) 1924 ; check_missing(T) 1925 ).
1929obj_properties_out([], Spec, []) :- 1930 !, 1931 check_missing(Spec). 1932obj_properties_out(List, [], List) :- 1933 !. 1934obj_properties_out([NV|T0], PL, [NV|T]) :- 1935 PL = [p(P,_,_)|_], 1936 NV = N-_, 1937 N @< P, 1938 !, 1939 obj_properties_out(T0, PL, T). 1940obj_properties_out([N-V0|T0], [p(N,Type,_Opts)|PT], [N-V|T]) :- 1941 !, 1942 json_check(Type, V, V0), 1943 obj_properties_out(T0, PT, T). 1944obj_properties_out(T0, [p(N,_Type,Opts)|PT], T) :- 1945 ( memberchk(required, Opts) 1946 -> existence_error(json_property, N) 1947 ; obj_properties_out(T0, PT, T) 1948 ).
1955join_dicts([One], One) :- !. 1956join_dicts([H1,H2|T], Dict) :- 1957 H = H1.put(H2), 1958 join_dicts([H|T], Dict).
1964must_be(Type, In, Out) :- 1965 ( nonvar(In) 1966 -> must_be(Type, In) 1967 ; must_be(Type, Out) 1968 ). 1969 1970:- multifile 1971 http:convert_parameter/3. 1972 1973httpconvert_parameter(openapi(Type), In, Out) :- 1974 json_check(Type, In, Out).
array(ItemType, Options)
object(Properties)
Properties is an ordered list of
required(Bool)
, nullable(Bool)
url(URL)
Reference to another type.
1989:- multifile
1990 json_schema/2.
1994json_schema_clauses(JSONTerm, Options) --> 1995 { Schemas = JSONTerm.get(components).get(schemas), 1996 dict_pairs(Schemas, _, SchemaPairs) 1997 }, 1998 !, 1999 schema_clauses(SchemaPairs, Options). 2000json_schema_clauses(_, _) --> [].
2007schema_clauses([], _) --> []. 2008schema_clauses([H|T], Options) --> 2009 schema_clause(H, Options), 2010 schema_clauses(T, Options). 2011 2012schema_clause(Schema-Spec, Options) --> 2013 { json_type(Spec, Type, Options), 2014 option(base_uri(Base), Options), 2015 file_directory_name(Base, Dir), 2016 atomic_list_concat([Dir, '#/components/schemas/', Schema], URL) 2017 }, 2018 [ openapi:json_schema(URL, Type) ].
2029json_type(Spec, Type, TypeOpts, Options) :- 2030 _{'$ref':URLS} :< Spec, 2031 !, 2032 option(base_uri(Base), Options), 2033 uri_normalized(URLS, Base, URL), 2034 ( url_yaml(URL, Spec2) 2035 -> atom_string(NewBase, URL), 2036 json_type(Spec2, Type, TypeOpts, [base_uri(NewBase)|Options]) 2037 ; Type = url(URL), 2038 TypeOpts = [] 2039 ). 2040json_type(Spec, Type, TypeOpts, Options) :- 2041 json_type(Spec, Type, Options), 2042 ( Spec.get(nullable) == true 2043 -> TypeOpts = [nullable] 2044 ; TypeOpts = [] 2045 ).
2049json_type(Spec, Type, _) :- 2050 _{type:TypeS, format:FormatS} :< Spec, 2051 !, 2052 atom_string(Type0, TypeS), 2053 atom_string(Format, FormatS), 2054 api_type(Type0, Format, Type1), 2055 type_restrictions(Spec, Type0, Type1, Type). 2056json_type(Spec, object(Props), Options) :- 2057 _{properties:PropSpecs} :< Spec, 2058 !, 2059 dict_pairs(PropSpecs, _, Pairs), 2060 ( maplist(atom_string, Req, Spec.get(required)) 2061 -> true 2062 ; Req = [] 2063 ), 2064 maplist(schema_property(Req, Options), Pairs, Props0), 2065 sort(Props0, Props). 2066json_type(Spec, array(Type, Opts), Options) :- 2067 _{type:"array", items:IType} :< Spec, 2068 !, 2069 array_restrictions(Spec, Opts), 2070 json_type(IType, Type, Options). 2071json_type(Spec, oneOf(Types), Options) :- 2072 _{oneOf:List} :< Spec, 2073 !, 2074 maplist(opts_json_type(Options), List, Types). 2075json_type(Spec, allOf(Types), Options) :- 2076 _{allOf:List} :< Spec, 2077 !, 2078 maplist(opts_json_type(Options), List, Types). 2079json_type(Spec, anyOf(Types), Options) :- 2080 _{anyOf:List} :< Spec, 2081 !, 2082 maplist(opts_json_type(Options), List, Types). 2083json_type(Spec, not(Type), Options) :- 2084 _{not:NSpec} :< Spec, 2085 !, 2086 json_type(NSpec, Type, Options). 2087json_type(Spec, object, _Options) :- 2088 _{type:"object"} :< Spec, 2089 !. 2090json_type(Spec, enum(Values, CaseSensitive, Case), Options) :- 2091 _{type:"string", enum:ValuesS} :< Spec, 2092 !, 2093 option(enum_case_sensitive(CaseSensitive), Options, true), 2094 option(enum_case(Case), Options, preserve), 2095 maplist(atom_string, Values, ValuesS). 2096json_type(Spec, Type, _) :- 2097 _{type:TypeS} :< Spec, 2098 !, 2099 atom_string(Type0, TypeS), 2100 api_type(Type0, -, Type1), 2101 type_restrictions(Spec, Type0, Type1, Type). 2102json_type(Spec, Type, Options) :- 2103 _{'$ref':URLS} :< Spec, 2104 !, 2105 option(base_uri(Base), Options), 2106 uri_normalized(URLS, Base, URL), 2107 ( url_yaml(URL, Spec2) 2108 -> atom_string(NewBase, URL), 2109 json_type(Spec2, Type, [base_uri(NewBase)|Options]) 2110 ; Type = url(URL) 2111 ). 2112json_type(_{properties:_{}}, Type, _Options) :- 2113 !, 2114 Type = (-). 2115json_type(_Spec, _Type, _Options) :- 2116 start_debugger_fail. 2117 2118opts_json_type(Options, Spec, Type) :- 2119 json_type(Spec, Type, Options). 2120 2121schema_property(Reqs, Options, Name-Spec, p(Name, Type, TypeOpts)) :- 2122 ( memberchk(Name, Reqs) 2123 -> TypeOpts = [ required | TypeOpts1 ] 2124 ; TypeOpts = TypeOpts1 2125 ), 2126 json_type(Spec, Type, TypeOpts1, Options).
2130type_restrictions(Spec, Type0, Type1, Type) :- 2131 numeric_type(Type0), 2132 !, 2133 ( _{minimum:Min, maximum:Max} :< Spec 2134 -> Type = numeric(Type1, domain(between(Min,Max), ExclMin-ExclMax, MultipleOf)) 2135 ; _{minimum:Min} :< Spec 2136 -> Type = numeric(Type1, domain(min(Min), ExclMin, MultipleOf)) 2137 ; _{maximum:Max} :< Spec 2138 -> Type = numeric(Type1, domain(max(Max), ExclMax, MultipleOf)) 2139 ; Type = Type1 2140 ), 2141 ( _{ exclusiveMinimum: ExclMin} :< Spec 2142 -> true 2143 ; ExclMin = false 2144 ), 2145 ( _{ exclusiveMaximum: ExclMax} :< Spec 2146 -> true 2147 ; ExclMax = false 2148 ), 2149 ( _{ multipleOf: MultipleOf} :< Spec 2150 -> true 2151 ; MultipleOf = (-) 2152 ). 2153type_restrictions(Spec, string, string, Type) :- 2154 setof(Restrict, string_restriction(Spec, Restrict), Restrictions), 2155 !, 2156 Type = string(Restrictions). 2157type_restrictions(_, _Type0, Type, Type). 2158 2159numeric_type(integer). 2160numeric_type(number). 2161 2162string_restriction(Spec, max_length(Len)) :- 2163 Len = Spec.get(maxLength). 2164string_restriction(Spec, min_length(Len)) :- 2165 Len = Spec.get(minLength). 2166string_restriction(Spec, pattern(Regex)) :- 2167 atom_string(Regex, Spec.get(pattern)). 2168 2169array_restrictions(Spec, Options) :- 2170 findall(Opt, array_restriction(Spec, Opt), Options). 2171 2172array_restriction(Spec, min_items(Min)) :- 2173 Min = Spec.get(minItems). 2174array_restriction(Spec, max_items(Max)) :- 2175 Max = Spec.get(minItems). 2176array_restriction(Spec, unique_items(true)) :- 2177 true == Spec.get(uniqueItems). 2178 2179check_array_length(List, Opts) :- 2180 memberchk(max_items(Max), Opts), 2181 !, 2182 ( memberchk(min_items(Min), Opts) 2183 -> true 2184 ; Min = 0 2185 ), 2186 length(List, Len), 2187 ( between(Min, Max, Len) 2188 -> true 2189 ; domain_error(array_length(Min,Max), List) 2190 ). 2191check_array_length(List, Opts) :- 2192 memberchk(min_items(Min), Opts), 2193 !, 2194 length(List, Len), 2195 ( Len >= Min 2196 -> true 2197 ; domain_error(array_length(Min,infinite), List) 2198 ). 2199check_array_length(_, _). 2200 2201check_array_unique(List, Opts) :- 2202 memberchk(unique_items(true), Opts), 2203 !, 2204 ( length(List, Len), 2205 sort(List, Sorted), 2206 length(Sorted, Len) 2207 -> true 2208 ; domain_error(unique_array, List) 2209 ). 2210check_array_unique(_, _).
2217url_yaml(URL, Yaml) :- 2218 uri_components(URL, Components), 2219 uri_data(scheme, Components, file), 2220 uri_data(path, Components, FileEnc), 2221 uri_data(fragment, Components, Fragment), 2222 uri_encoded(path, File, FileEnc), 2223 openapi_read(File, Yaml0), 2224 ( var(Fragment) 2225 -> Yaml = Yaml0 2226 ; atomic_list_concat(Segments, /, Fragment), 2227 yaml_subdoc(Segments, Yaml0, Yaml) 2228 ). 2229 2230 2231 /******************************* 2232 * DOC GENERATION * 2233 *******************************/
This predicate is used by the swipl-openapi
script to generate the
commented client or server code.
2246openapi_doc(File, Mode, Options) :- 2247 must_be(oneof([client,server]), Mode), 2248 read_openapi_spec(File, Spec, Options, Options1), 2249 phrase(server_clauses(Spec, Options1), Clauses), 2250 setup_call_cleanup( 2251 doc_output(Stream, Close, Options), 2252 doc_gen(Stream, File, Clauses, [mode(Mode)|Options]), 2253 Close). 2254 2255doc_output(Stream, close(Stream), Options) :- 2256 option(file(File), Options), 2257 !, 2258 open(File, write, Stream). 2259doc_output(current_output, true, _). 2260 2261doc_gen(Stream, File, Clauses, Options) :- 2262 findall(OperationId-Data, 2263 doc_data(Clauses, OperationId, Data, Options), Pairs), 2264 file_header(Stream, File, [operations(Pairs)|Options]), 2265 forall(member(OperationId-Data, Pairs), 2266 ( phrase(openapi_doc(OperationId, Data, Options), S) 2267 -> format(Stream, '~s', [S]) 2268 ; warning(openapi(doc_failed, OperationId), Options) 2269 )). 2270 2271file_header(Stream, File, Options) :- 2272 option(mode(client), Options), 2273 !, 2274 client_module(Stream, File, Options), 2275 findall(Opt, client_option(Opt, Options), ClientOptions), 2276 format(Stream, ':- use_module(library(openapi)).~n', []), 2277 format(Stream, ':- use_module(library(option)).~n~n', []), 2278 format(Stream, ':- use_module(library(debug)).~n~n', []), 2279 portray_clause(Stream, (:- openapi_client(File, ClientOptions))), 2280 nl(Stream). 2281file_header(Stream, File, Options) :- 2282 option(mode(server), Options), 2283 !, 2284 findall(Opt, server_option(Opt, Options), ServerOptions), 2285 format(Stream, ':- use_module(library(openapi)).~n', []), 2286 format(Stream, ':- use_module(library(option)).~n', []), 2287 format(Stream, ':- use_module(library(debug)).~n', []), 2288 server_header(Stream, File, Options), 2289 format(Stream, '~n', []), 2290 portray_clause(Stream, (:- openapi_server(File, ServerOptions))), 2291 nl(Stream). 2292file_header(_, _, _).
module(Module)
is present. If Module is true
, derive the module
from the client filename or the SpecFile.2300client_module(Stream, SpecFile, Options) :- 2301 module_name(Module, SpecFile, Options), 2302 option(operations(Ops), Options), 2303 !, 2304 format(Stream, ':- module(~q,~n~t[ ~12|', [Module]), 2305 exports(Ops, Stream), 2306 format(Stream, '~t~10|]).~n', []). 2307client_module(_, _, _). 2308 2309module_name(Module, SpecFile, Options) :- 2310 option(module(M), Options), 2311 ( M == true 2312 -> option(file(File), Options, SpecFile), 2313 file_base_name(File, Base), 2314 file_name_extension(Module, _, Base) 2315 ; Module = M 2316 ). 2317 2318exports([], _). 2319exports([OperationId-Data|T], Stream) :- 2320 ( T == [] 2321 -> Sep = '' 2322 ; Sep = ',' 2323 ), 2324 export(Stream, OperationId, Data.arguments, Sep), 2325 exports(T, Stream). 2326 2327export(Stream, OperationId, Args, Sep) :- 2328 length(Args, Arity), 2329 phrase(mode_args(Args), Codes), 2330 format(Stream, '~t~12|~q~w~t~48|% ~s~n', 2331 [OperationId/Arity, Sep, Codes]).
2337client_option(warn(false), _Options). 2338client_option(type_check_request(Mode), Options) :- 2339 option(type_check_request(Mode), Options). 2340client_option(Option, Options) :- 2341 common_option(Option, Options).
2347server_option(type_check_response(Bool), Options) :- 2348 option(type_check_response(Bool), Options), 2349 must_be(boolean, Bool). 2350server_option(format_response(Bool), Options) :- 2351 option(format_response(Bool), Options), 2352 must_be(boolean, Bool). 2353server_option(Option, Options) :- 2354 common_option(Option, Options). 2355 2356common_option(server_url(URL), Options) :- 2357 option(server_url(URL), Options). 2358common_option(enum_case_sensitive(Bool), Options) :- 2359 option(enum_case_sensitive(Bool), Options). 2360common_option(enum_case(Case), Options) :- 2361 option(enum_case(Case), Options), 2362 must_be(oneof([lower,upper,preserve]), Case).
2368server_header(Stream, File, Options) :- 2369 ( option(httpd(true), Options) 2370 ; option(ui(true), Options) 2371 ), 2372 !, 2373 format(Stream, ':- use_module(library(http/thread_httpd)).~n', []), 2374 ( option(ui(true), Options) 2375 -> server_ui(Stream, File, Options) 2376 ; option(httpd(true), Options) 2377 -> server_restonly(Stream, Options) 2378 ; true 2379 ). 2380server_header(_,_,_). 2381 2382server_ui(Stream, File, _Options) :- 2383 format(Stream, ':- use_module(library(http/http_dispatch)).~n', []), 2384 format(Stream, ':- use_module(library(swagger_ui)).~n', []), 2385 format(Stream, ' 2386:- http_handler(root(.), 2387 http_redirect(see_other, root(\'swagger_ui\')), 2388 []). 2389:- http_handler(root(\'swagger.yaml\'), 2390 http_reply_file(~q, []), 2391 [id(swagger_config)]). 2392 2393server(Port) :- 2394 http_server(dispatch, 2395 [ port(Port) 2396 ]). 2397 2398dispatch(Request) :- 2399 openapi_dispatch(Request), 2400 !. 2401dispatch(Request) :- 2402 http_dispatch(Request). 2403 2404', [File]). 2405 2406server_restonly(Stream, _Options) :- 2407 format(Stream, ' 2408server(Port) :- 2409 http_server(openapi_dispatch, 2410 [ port(Port) 2411 ]). 2412 2413', []). 2414 2415 /******************************* 2416 * INTROSPECTION * 2417 *******************************/
2424% Server clauses 2425openapi_arg(M:OperationId, Index, Name, Type) :- 2426 Clause = openapi_handler(_Method, _PathList, _SegmentMatches, 2427 _Request, _HdrParams, _AsOption, _OptionParam, 2428 _Content, _Responses, _Security, Handler), 2429 clause(M:, true), 2430 functor(Handler, OperationId, _), 2431 clause_data(Clause, module(M), OperationId, Data, []), 2432 once(append(Inputs, [p(response, _, _)], Data.arguments)), 2433 nth1(Index, Inputs, p(Name, Type, _Description)). 2434% client clauses 2435openapi_arg(M:OperationId, ArgI, Arg, Type) :- 2436 Clause = openapi_type(Head), 2437 clause(M:, true), 2438 functor(Head, OperationId, _), 2439 arg(ArgI, Head, Arg:Type).
response(Code,
As, MediaType, Type)
, where
default
data
or error
2454openapi_response(M:OperationId, Responses) :- 2455 Clause = openapi_handler(_Method, _PathList, _SegmentMatches, 2456 _Request, _HdrParams, _AsOption, _OptionParam, 2457 _Content, Responses0, _Security, Handler), 2458 clause(M:, true), 2459 functor(Handler, OperationId, _), 2460 maplist(public_response, Responses0, Responses). 2461 2462public_response(response(Code, As, MediaType, Type, _Result, _Descr), 2463 response(Code, As, MediaType, Type)). 2464 2465 2466 2467 /******************************* 2468 * DOCUMENTATION GENERATION * 2469 *******************************/ 2470 2471:- meta_predicate 2472 prefix( , , , , ).
2476openapi_doc(OperationId, Data, Options) -->
2477 doc_mode(OperationId, Data.arguments),
2478 "\n%\n",
2479 doc_description(Data.doc),
2480 doc_security(Data.security),
2481 doc_args(Data.arguments),
2482 doc_path(Data.doc),
2483 "\n",
2484 server_skeleton(OperationId, Data.arguments, Options),
2485 "\n\n".
2491:- det(server_skeleton//3). 2492server_skeleton(_OperationId, _Args, Options) --> 2493 { option(mode(client), Options) }, 2494 !. 2495server_skeleton(OperationId, Args, Options) --> 2496 { option(mode(server), Options), 2497 maplist(server_arg_name, Args, ArgNames), 2498 Head =.. [OperationId|ArgNames], 2499 server_skeleton_clause(Head, Clause), 2500 ( string(Clause) 2501 -> string_codes(Clause, Codes) 2502 ; with_output_to(codes(Codes), 2503 portray_clause(Clause)) 2504 ) 2505 }, 2506 string(Codes).
2519:- det(server_skeleton_clause/2). 2520:- multifile 2521 user:openapi_server_clause/2. 2522server_skeleton_clause(Head, Clause) :- 2523 user:openapi_server_clause(Head, Clause), 2524 !. 2525server_skeleton_clause(Head, Clause) :- 2526 functor(Head, _, Arity), 2527 arg(Arity, Head, Response), 2528 Clause = (Head :- 2529 debug(openapi, "~p", [Head]), 2530 Response = status(404)). 2531 2532 2533doc_mode(OperationId, Args) --> 2534 "%! ", quoted_atom(OperationId), 2535 "(", mode_args(Args), ") is det.". 2536 2537mode_args([]) --> []. 2538mode_args([H|T]) --> 2539 mode_arg(H), 2540 ( {T==[]} 2541 -> [] 2542 ; ", ", 2543 mode_args(T) 2544 ). 2545 2546mode_arg(p(Name, _Type, _Descr)) --> 2547 mode(Name), camel_case(Name). 2548 2549mode(response) --> !, "-". 2550mode(_) --> "+". 2551 2552server_arg_name(p(Param, _Type, _Descr), '$VAR'(ArgName)) :- 2553 camel_case(Param, ArgName). 2554 2555quoted_atom(Atom, List, Tail) :- 2556 format(codes(List,Tail), '~q', [Atom]).
2562camel_case(Name) --> 2563 { camel_case(Name, Camel) }, 2564 atom(Camel). 2565 2566camel_case(Name, Camel) :- 2567 atom_codes(Name, Codes), 2568 phrase(camel(Codes), CamelCodes), 2569 atom_codes(Camel, CamelCodes). 2570 2571camel([]) --> []. 2572camel([H|T]) --> 2573 { code_type(H, to_lower(U)) }, 2574 [U], 2575 camel_skip(T). 2576 2577camel_skip([]) --> []. 2578camel_skip([0'_|T]) --> !, camel(T). 2579camel_skip([0'-|T]) --> !, camel(T). 2580camel_skip([H|T]) --> !, [H], camel_skip(T).
2588uncamel_case(In, Out) :- 2589 atom_codes(In, Codes), 2590 phrase(uncamel(UnCamel), Codes), 2591 atom_codes(Out, UnCamel). 2592 2593uncamel([H|T]) --> 2594 [U], 2595 { code_type(U, upper(H)) }, 2596 !, 2597 uncamel_(T). 2598uncamel(List) --> 2599 uncamel_(List). 2600 2601uncamel_([L,0'_,U1,U2|T]) --> 2602 [L,U1,U2], 2603 { code_type(L, lower), 2604 code_type(U1, upper), 2605 code_type(U2, upper) 2606 }, 2607 !, 2608 uncamel_(T). 2609uncamel_([L,0'_,Lower|T]) --> 2610 [L,U], 2611 { code_type(L, lower), 2612 code_type(U, upper(Lower)) 2613 }, 2614 !, 2615 uncamel_(T). 2616uncamel_([0'_|T]) --> 2617 "-", 2618 !, 2619 uncamel_(T). 2620uncamel_([H|T]) --> 2621 [H], 2622 !, 2623 uncamel_(T). 2624uncamel_([]) --> 2625 [].
2631doc_description(Doc) --> 2632 { memberchk(summary(Summary), Doc), 2633 memberchk(description(Desc), Doc) 2634 }, !, 2635 multiline_comment(Summary), 2636 multiline_comment(Desc), 2637 "%\n". 2638doc_description(Doc) --> 2639 { memberchk(description(Desc), Doc) 2640 }, !, 2641 multiline_comment(Desc), 2642 "%\n". 2643doc_description(Doc) --> 2644 { memberchk(summary(Summary), Doc) 2645 }, !, 2646 multiline_comment(Summary), 2647 "%\n". 2648doc_description(_) --> []. 2649 2650multiline_comment(Text) --> 2651 { string_lines(Text, Lines) 2652 }, 2653 lines(Lines, "% "). 2654 2655string_lines(String, Lines) :- 2656 split_string(String, "\n", "", Lines0), 2657 delete_empty_lines(Lines0, Lines1), 2658 reverse(Lines1, Lines2), 2659 delete_empty_lines(Lines2, Lines3), 2660 reverse(Lines3, Lines). 2661 2662delete_empty_lines([Line|T0], T) :- 2663 empty_line(Line), 2664 !, 2665 delete_empty_lines(T0, T). 2666delete_empty_lines(T, T). 2667 2668empty_line(Line) :- 2669 split_string(Line, " \t", " \t", [""]). 2670 2671lines([], _) --> []. 2672lines([H|T], Prefix) --> atom(Prefix), atom(H), "\n", lines(T, Prefix). 2673 2674doc_security([public]) --> 2675 !. 2676doc_security(List) --> 2677 "% Authentication options:\n", 2678 doc_security_list(List), 2679 "%\n". 2680 2681doc_security_list([]) --> 2682 []. 2683doc_security_list([H|T]) --> 2684 doc_security_option(H), 2685 doc_security_list(T). 2686 2687doc_security_option(public) --> 2688 "% - no authentication required\n". 2689doc_security_option(Term) --> 2690 { arg(2, Term, Name) }, 2691 "% - ", atom(Name), "\n". 2692 2693doc_args([]) --> []. 2694doc_args([H|T]) --> doc_arg(H), doc_args(T). 2695 2696doc_arg(p(Name, Type, Description)) --> 2697 indent(0), 2698 prefix(0, ("@arg ", camel_case(Name), " "), Indent), 2699 type(Type, Indent), "\n", 2700 arg_description(Description). 2701 2702doc_path(Doc) --> 2703 { memberchk(path(Path), Doc) }, 2704 !, 2705 "%\n% @see Path = ", atom(Path), "\n". 2706doc_path(_) --> 2707 []. 2708 2709arg_description(options(List)) --> 2710 !, 2711 arg_options(List). 2712arg_description(Description) --> 2713 { string_lines(Description, Lines) }, 2714 lines(Lines, "% "). 2715 2716arg_options([]) --> []. 2717arg_options([H|T]) --> arg_option(H), arg_options(T). 2718 2719arg_option(p(Name, Type, Description)) --> 2720 { string_lines(Description, Lines) }, 2721 "% - ", quoted_atom(Name), "(+", type(Type), ")", "\n", 2722 lines(Lines, "% ").
2726type(list(option)) --> !. 2727type(url(URL)) --> 2728 !, 2729 { file_base_name(URL, TypeName) }, 2730 atom(TypeName). 2731type(Type) --> 2732 type(Type, 0). 2733 2734type(array(Type, Opts), Indent) --> 2735 !, 2736 prefix(Indent, "array(", NewIndent), 2737 type(Type, NewIndent), ")", 2738 ( {Opts == []} 2739 -> [] 2740 ; " [", sequence(array_attr, ",", Opts), "]" 2741 ). 2742type(string([pattern(Pattern)]), _Indent) --> 2743 !, 2744 "/", atom(Pattern), "/". 2745type(string(Attrs), _Indent) --> 2746 { select(pattern(Pattern), Attrs, Attrs1) }, 2747 !, 2748 "/", atom(Pattern), "/ [", sequence(str_attr, ",", Attrs1), "]". 2749type(string(Attrs), _Indent) --> 2750 !, 2751 "string [", sequence(str_attr, ",", Attrs), "]". 2752type(enum(List,_,lower), _Indent) --> 2753 { maplist(downcase_atom, List, Lower) }, 2754 sequence(atom, "|", Lower). 2755type(object(Properties), Indent) --> 2756 !, 2757 prefix(Indent, "{ ", NewIndent), 2758 sequence(obj_property(NewIndent), (",", nl(NewIndent)), Properties), 2759 nl(Indent), "}". 2760type(oneOf(List), Indent) --> 2761 !, 2762 prefix(Indent, "( ", NewIndent), 2763 sequence(itype(NewIndent), (nl(Indent),"| "), List), 2764 nl(Indent), ")". 2765type(Type, _Indent, List, Tail) :- 2766 format(codes(List, Tail), '~p', [Type]). 2767 2768itype(Indent, Type) --> 2769 type(Type, Indent). 2770 2771obj_property(Indent, p(Name, Type, Opts)) --> 2772 atom(Name), ": ", 2773 { atom_length(Name, NameL), 2774 NewIndent is Indent+NameL+2 2775 }, 2776 type(Type, NewIndent), 2777 obj_property_attrs(Opts). 2778 2779obj_property_attrs([]) --> 2780 !. 2781obj_property_attrs(Opts) --> 2782 " [", sequence(obj_property_attr, "",Opts), "]". 2783 2784obj_property_attr(required) --> "R". 2785obj_property_attr(nullable) --> "N". 2786 2787str_attr(min_length(Len)) --> format(">=~w", [Len]). 2788str_attr(max_length(Len)) --> format("=<~w", [Len]). 2789 2790array_attr(min_items(Len)) --> format(">=~w", [Len]). 2791array_attr(max_items(Len)) --> format("=<~w", [Len]). 2792array_attr(unique_items(true)) --> "unique". 2793 2794prefix(Indent, Prefix, NewIndent) --> 2795 here(Start), 2796 , 2797 here(End), 2798 { diff_len(Start, End, 0, PLen), 2799 NewIndent is Indent+PLen 2800 }. 2801 2802diff_len(Here, End, Len, Len) :- 2803 Here == End, 2804 !. 2805diff_len([_|Here], End, Len0, Len) :- 2806 Len1 is Len0+1, 2807 diff_len(Here, End, Len1, Len). 2808 2809here(List,List,List). 2810 2811nl(Indent) --> 2812 "\n", indent(Indent). 2813 2814indent(Indent) --> 2815 "% ", spaces(Indent). 2816 2817spaces(Indent) --> 2818 format('~t~*|', [Indent]). 2819 2820format(Format, Args, List, Tail) :- 2821 format(codes(List, Tail), Format, Args).
2828doc_data(Clauses, OperationId, Data, Options) :- 2829 member(Clause, Clauses), 2830 clause_data(Clause, Clauses, OperationId, Data, Options). 2831 2832clause_data(Clause, Clauses, OperationId, Data, Options) :- 2833 Clause = openapi_handler(_Method, _PathList, Segments, 2834 Request, HdrParams, AsOption, OptionParam, 2835 Content, Responses, Security, Handler), 2836 Data = #{arguments:Params, doc:Doc, security:Security}, 2837 Handler =.. [OperationId|Args], 2838 ( ( Clauses = module(M) 2839 -> M:openapi_doc(OperationId, Doc) 2840 ; memberchk(openapi_doc(OperationId, Doc), Clauses) 2841 ), 2842 maplist(doc_param(from(Segments, 2843 Request, HdrParams, AsOption, OptionParam, 2844 Content, Responses), Options), Args, Params0), 2845 exclude(==(-), Params0, Params) 2846 -> true 2847 ; warning(openapi(doc_failed, OperationId), Options), 2848 fail 2849 ). 2850 2851doc_param(from(Segments, Request, HdrParams, AsOption, OptionParam, 2852 Content, Responses), Options, 2853 Arg, Param) :- 2854 ( segment_param(Arg, Segments, Param) 2855 ; request_param(Arg, Request, Param) 2856 ; OptionParam == Arg, 2857 option_param(AsOption, Param) 2858 ; content_param(Arg, Content, Param) 2859 ; header_param(Arg, HdrParams, Param) 2860 ; response_param(Arg, Responses, Param, Options) 2861 ; start_debugger_fail 2862 ), !. 2863 2864segment_param(Arg, Segments, p(Name, Type, Description)) :- 2865 member(segment(Type, _, Arg0, Name, Description), Segments), 2866 Arg == Arg0, !. 2867 2868request_param(Arg, Requests, Param) :- 2869 member(R, Requests), 2870 arg(1, R, Arg0), 2871 Arg == Arg0, !, 2872 doc_request_param(R, Param). 2873 2874param_json_type(Opts, Type) :- 2875 memberchk(openapi(Type), Opts), 2876 !. 2877param_json_type(Opts, Type) :- 2878 memberchk(list(openapi(Type0)), Opts), 2879 Type = array(Type0). 2880 2881option_param(AsOption, p(options, list(option), options(Options))) :- 2882 phrase(doc_request_params(AsOption), Options). 2883 2884doc_request_params([]) --> []. 2885doc_request_params([H|T]) --> 2886 { doc_request_param(H, Param) }, 2887 [ Param ], 2888 doc_request_params(T). 2889 2890doc_request_param(Request, p(Name,Type,Description)) :- 2891 Request =.. [Name,_Var,Options], 2892 ( param_json_type(Options, Type) 2893 -> true 2894 ; Type = string, 2895 warning(openapi(no_type, Name), []) 2896 ), 2897 ( memberchk(description(Description), Options) 2898 -> true 2899 ; Description = "" 2900 ). 2901 2902content_param(Arg, 2903 content(_MediaType, Scheme, Arg0, Description), 2904 p(request_body, Scheme, Description)) :- 2905 Arg == Arg0, !. 2906 2907header_param(Arg, HdrParams, Param) :- 2908 member(HdrParam, HdrParams), 2909 arg(1, HdrParam, Arg0), 2910 Arg == Arg0, 2911 !, 2912 doc_request_param(HdrParam, Param). 2913 2914response_param(Arg, Responses, -, Options) :- 2915 is_reponse_arg(Arg, Responses), 2916 option(mode(client), Options), 2917 \+ response_has_data(Responses), !. 2918response_param(Arg, Responses, p(response, Scheme, Description), _Options) :- 2919 member(response(Code,_As,_MediaType, Scheme, Arg0, Description), 2920 Responses), 2921 Arg == Arg0, 2922 between(200, 399, Code), !. 2923 2924is_reponse_arg(Arg, Responses) :- 2925 member(R, Responses), 2926 arg(5, R, Arg0), 2927 Arg == Arg0.
silent(true)
is an option, the error is
silently ignored.2935error(_Term, Options) :- 2936 option(silent(true), Options), 2937 !. 2938error(Term, _Options) :- 2939 print_message(error, Term).
silent(true)
is an option, the warning
is silently ignored.2946warning(_Term, Options) :- 2947 option(silent(true), Options), 2948 !. 2949warning(Term, _Options) :- 2950 print_message(warning, Term). 2951 2952:- if(current_prolog_flag(gui, true)). 2953start_debugger :- 2954 current_prolog_flag(debug, true), 2955 !, 2956 gtrace. 2957:- endif. 2958start_debugger. 2959 2960start_debugger_fail :- 2961 start_debugger, 2962 fail. 2963 2964 2965 /******************************* 2966 * ENABLE EXPANSION * 2967 *******************************/ 2968 2969:- multifile 2970 system:term_expansion/2. 2971 2972systemterm_expansion((:- openapi_server(File, Options)), Clauses) :- 2973 \+ current_prolog_flag(xref, true), 2974 expand_openapi_server(File, Options, Clauses). 2975systemterm_expansion((:- openapi_client(File, Options)), Clauses) :- 2976 \+ current_prolog_flag(xref, true), 2977 expand_openapi_client(File, Options, Clauses). 2978 2979 2980 /******************************* 2981 * MESSAGES * 2982 *******************************/ 2983 2984:- multifile 2985 prolog:message//1, 2986 prolog:error_message//1, 2987 prolog:message_context//1. 2988 2989prologmessage(openapi(path_failed, Path-_Spec)) --> 2990 [ 'OpenAPI: failed to generate clauses for path ~p'-[Path] ]. 2991prologmessage(openapi(no_operation_id, Method, Path, PredicateName)) --> 2992 [ 'OpenAPI: no operationId for ~p ~p, using ~p'- 2993 [Method, Path, PredicateName] ]. 2994prologmessage(openapi(doc_failed, OperationId)) --> 2995 [ 'OpenAPI: failed to generate documentation for operationId ~p'- 2996 [OperationId] ]. 2997prologmessage(openapi(no_type, Param)) --> 2998 [ 'OpenAPI: no type for parameter ~p (assuming "string")'-[Param] ]. 2999prologmessage(openapi(unknown_type, Type, -)) --> 3000 [ 'OpenAPI: unrecognized type `~p`'-[Type] ]. 3001prologmessage(openapi(unknown_type, Type, Format)) --> 3002 [ 'OpenAPI: unrecognized type `~p` with format `~p`'-[Type, Format] ]. 3003prologmessage(openapi(unknown_string_format, Format)) --> 3004 [ 'OpenAPI: Using plain "string" for string with format `~p`'-[Format] ]. 3005 3006prologerror_message(rest_error(missing_header(Name))) --> 3007 [ 'REST error: missing header: ', ansi(code, '~p', [Name]) ]. 3008prologerror_message(rest_error(Code, Term)) --> 3009 [ 'REST error: code: ~p, data: ~p'-[Code, Term] ]. 3010prologerror_message(openapi_invalid_reply(Code, ExCodes, Error)) --> 3011 [ 'OpenAPI: request replied code ~p (expected one of ~p)'-[Code, ExCodes], 3012 nl, 3013 ' Document: ~p'-[Error] 3014 ]. 3015prologmessage_context(rest(Name, Where, Type)) --> 3016 [ ' (REST '-[] ], 3017 rest_context(Name, Where, Type), 3018 [ ')'-[] ]. 3019 3020rest_context(body, request_body, json) --> 3021 [ 'invalid request body'-[] ]. 3022rest_context(body, request_body, _Type) --> 3023 [ 'request body'-[] ]. 3024rest_context(Name, Where, _Type) --> 3025 [ '~p parameter ~p'-[Where, Name] ]
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. */