29
30:- module(plweb_api,
31 []). 32:- use_module(library(http/http_dispatch)). 33:- use_module(library(http/http_cors)). 34:- use_module(library(http/http_json)). 35:- use_module(library(http/http_parameters)). 36:- use_module(library(pldoc/man_index)). 37:- use_module(library(pldoc/doc_util)). 38:- use_module(library(prolog_code)). 39:- use_module(library(prolog_source)). 40:- use_module(library(apply)). 41:- use_module(library(error)). 42:- use_module(library(pairs)). 43:- use_module(library(option)). 44
45:- http_handler(root(doc_link), doc_link, []).
60doc_link(Request) :-
61 reply_options(Request, [get,post]),
62 !.
63doc_link(Request) :-
64 memberchk(method(post), Request),
65 !,
66 http_read_json_dict(Request, Atoms,
67 [value_string_as(atom)]),
68 cors_enable(Request, [methods([get,post])]),
69 must_be(list(atom), Atoms),
70 for_links(Atoms, Pairs),
71 dict_create(Dict, json, Pairs),
72 reply_json_dict(Dict).
73doc_link(Request) :-
74 http_parameters(Request,
75 [ for(For, [])
76 ]),
77 cors_enable(Request, [methods([get,post])]),
78 ( for_link(For, Link)
79 -> reply_json_dict(Link)
80 ; reply_json_dict(null, [status(404)])
81 ).
82
83for_links([], []).
84for_links([H|T0], [H-I|T]) :-
85 ( for_link(H, I)
86 -> true
87 ; I = null
88 ),
89 for_links(T0, T).
90
91for_link(For, Info) :-
92 atom_to_object(For, Obj),
93 current_man_object(Obj),
94 findall(Prop, obj_property(Obj, Prop), Props),
95 format(string(URL),
96 'https://www.swi-prolog.org/pldoc/doc_for?object=~w',
97 [For]),
98 dict_pairs(Info, json, [url-URL|Props]).
99
100obj_property(Obj, summary-Summary) :-
101 once(man_object_property(Obj, summary(Summary))).
102obj_property(PI, Prop) :-
103 pi_head(PI, Head0),
104 ( Head0 = M:_
105 -> Head = Head0
106 ; Head = M:Head0
107 ),
108 ( M=system,
109 predicate_property(Head, iso)
110 -> Prop = (class-iso)
111 ; M=system,
112 predicate_property(Head, built_in)
113 -> Prop = (class-builtin)
114 ; predicate_property(Head, autoload(File))
115 -> ( Prop = (class-autoload)
116 ; library_prop(File, Prop)
117 )
118 ; predicate_property(Head, file(File)),
119 predicate_property(Head, exported)
120 -> ( Prop = (class-library)
121 ; library_prop(File, Prop)
122 )
123 ).
124
125library_prop(File, library-LibS) :-
126 file_name_extension(File, pl, LibFile),
127 file_name_on_path(LibFile, library(Lib)),
128 format(string(LibS), '~w', [Lib]).
134reply_options(Request, Allowed) :-
135 option(method(options), Request),
136 !,
137 cors_enable(Request,
138 [ methods(Allowed)
139 ]),
140 format('Content-type: text/plain\r\n'),
141 format('~n').