Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(vis2, []).
|
Daniel@0
|
20
|
Daniel@0
|
21 /** <module> DML Visualisation web service
|
Daniel@0
|
22 */
|
Daniel@0
|
23
|
Daniel@0
|
24
|
Daniel@0
|
25 :- use_module(library(http/html_write)).
|
Daniel@0
|
26 :- use_module(library(http/html_head)).
|
Daniel@0
|
27 :- use_module(library(http/http_dispatch)).
|
Daniel@0
|
28 :- use_module(library(http/http_parameters)).
|
Daniel@0
|
29 :- use_module(library(http/http_json)).
|
Daniel@0
|
30 :- use_module(library(http/json)).
|
Daniel@0
|
31 :- use_module(library(thread_pool)).
|
Daniel@0
|
32 :- use_module(library(sandbox)).
|
Daniel@0
|
33 :- use_module(library(dcg_core)).
|
Daniel@0
|
34 :- use_module(library(dcg_codes)).
|
Daniel@0
|
35 :- use_module(library(dcg_macros)).
|
Daniel@0
|
36 :- use_module(library(fileutils)).
|
Daniel@0
|
37 :- use_module(library(swipe)).
|
Daniel@0
|
38 :- use_module(library(memo)).
|
Daniel@0
|
39 :- use_module(library(rdfutils)).
|
Daniel@0
|
40 :- use_module(library(httpfiles)).
|
Daniel@0
|
41 :- use_module(library(dataset)).
|
Daniel@0
|
42 :- use_module(library(insist)).
|
Daniel@0
|
43 :- use_module(library(lambda)).
|
Daniel@0
|
44 :- use_module(library(dcg/basics), [string_without//2, integer//1]).
|
Daniel@0
|
45 :- use_module(library(solution_sequences)).
|
Daniel@0
|
46
|
Daniel@0
|
47 :- set_prolog_flag(double_quotes,codes).
|
Daniel@0
|
48 :- set_prolog_flag(back_quotes,string).
|
Daniel@0
|
49
|
Daniel@0
|
50 http:location(v2,api(v2),[]).
|
Daniel@0
|
51
|
Daniel@0
|
52 :- http_handler(v2(dataset), list_datasets, []).
|
Daniel@0
|
53 :- http_handler(v2(dataset/define), define_dataset, []).
|
Daniel@0
|
54 :- http_handler(v2(view/dataset/index), dataset_views, []).
|
Daniel@0
|
55 :- http_handler(v2(view/dataset/items), dataset_items, []).
|
Daniel@0
|
56 :- http_handler(v2(view/dataset/summary), dataset_summary, []).
|
Daniel@0
|
57 :- http_handler(v2(view/recording/index), recording_views, []).
|
Daniel@0
|
58 :- http_handler(v2(view/recording/properties), recording_properties, []).
|
Daniel@0
|
59
|
Daniel@0
|
60 :- initialization
|
Daniel@0
|
61 current_thread_pool(dmlvis), !;
|
Daniel@0
|
62 thread_pool_create(vis, 8, [backlog(100)]).
|
Daniel@0
|
63
|
Daniel@0
|
64 % ------------------------------------------------------------------------------------
|
Daniel@0
|
65 % Handlers with documentation
|
Daniel@0
|
66
|
Daniel@0
|
67 %% list_datasets(+Request) is det.
|
Daniel@0
|
68 % Lists previously defined datsets and the Prolog queries that define them.
|
Daniel@0
|
69 list_datasets(R) :- vis(list_datasets,R).
|
Daniel@0
|
70
|
Daniel@0
|
71 %% define_dataset(+Request) is det.
|
Daniel@0
|
72 % Define a dataset satisfying given search terms. Result is a dataset
|
Daniel@0
|
73 % ID, which may be the same as a previously defined dataset if it consists
|
Daniel@0
|
74 % of the same items.
|
Daniel@0
|
75 define_dataset(R) :- vis(define_dataset,R).
|
Daniel@0
|
76
|
Daniel@0
|
77 %% dataset_views(+Request) is det.
|
Daniel@0
|
78 % Lists available views for datasets.
|
Daniel@0
|
79 dataset_views(R) :- vis(list_views(dataset),R).
|
Daniel@0
|
80
|
Daniel@0
|
81 %% dataset_items(+Request) is det.
|
Daniel@0
|
82 % Lists items in a given dataset specified by its ID..
|
Daniel@0
|
83 dataset_items(R) :- vis(dataset_items,R).
|
Daniel@0
|
84
|
Daniel@0
|
85 %% dataset_summary(+Request) is det.
|
Daniel@0
|
86 % Returns some summary information about a dataset.
|
Daniel@0
|
87 dataset_summary(R) :- vis(dataset_summary,R).
|
Daniel@0
|
88
|
Daniel@0
|
89 %% recording_views(+Request) is det.
|
Daniel@0
|
90 % Lists available views for recordings.
|
Daniel@0
|
91 recording_views(R) :- vis(list_views(recording),R).
|
Daniel@0
|
92
|
Daniel@0
|
93 %% recording_properties(+Request) is det.
|
Daniel@0
|
94 % Returns all the properties currently held in the RDF graph about a given recording.
|
Daniel@0
|
95 recording_properties(R) :- vis(recording_properties,R).
|
Daniel@0
|
96
|
Daniel@0
|
97
|
Daniel@0
|
98 % ------------------------------------------------------------------------------------
|
Daniel@0
|
99
|
Daniel@0
|
100 %% vis(+Method,+Request) is det.
|
Daniel@0
|
101 %
|
Daniel@0
|
102 % Top level predicate for implementing VIS API. Handles common tasks
|
Daniel@0
|
103 % like determining the reply format, handling errors, and formatting the reply.
|
Daniel@0
|
104 vis(Method,Request) :-
|
Daniel@0
|
105 method_params_goal(Method,Params,Goal),
|
Daniel@0
|
106 vis(Params,Goal,Request).
|
Daniel@0
|
107
|
Daniel@0
|
108 vis(Params,Goal,Request) :-
|
Daniel@0
|
109 http_parameters(Request, [format(Format), callback(Callback) | Params],
|
Daniel@0
|
110 [attribute_declarations(param)]),
|
Daniel@0
|
111 (Format=jsonp -> Fmt=jsonp(Callback); Fmt=json),
|
Daniel@0
|
112 member(request_uri(Query),Request),
|
Daniel@0
|
113 catch( insist(call(Goal,Result,Status)),
|
Daniel@0
|
114 Ex, (error_result(Ex,Result), Status=error)),
|
Daniel@0
|
115 result_response(Fmt,Query,Result,Status,Response),
|
Daniel@0
|
116 write(Response).
|
Daniel@0
|
117
|
Daniel@0
|
118 result_response(Fmt,Q,Result,Status,Response) :-
|
Daniel@0
|
119 with_output_to(string(Response),
|
Daniel@0
|
120 reply_as(Fmt,Status,_{ query:Q, result: Result})).
|
Daniel@0
|
121
|
Daniel@0
|
122 reply_as(json,Status,Dict) :-
|
Daniel@0
|
123 write_headers([Status,type(json)]),
|
Daniel@0
|
124 json_write_dict(current_output, Dict).
|
Daniel@0
|
125 reply_as(jsonp(Cb),Status,Dict) :-
|
Daniel@0
|
126 write_headers([Status,type(jsonp)]),
|
Daniel@0
|
127 write(Cb), write('('),
|
Daniel@0
|
128 json_write_dict(current_output, Dict),
|
Daniel@0
|
129 write(');').
|
Daniel@0
|
130
|
Daniel@0
|
131
|
Daniel@0
|
132 error_result(dml_error(Code,Descriptor),_{ code: Code, desc:Desc }) :- !,
|
Daniel@0
|
133 format(string(Desc),'ERROR: ~w',[Descriptor]).
|
Daniel@0
|
134
|
Daniel@0
|
135 error_result(Ex, _{ code: 500, desc: Msg }) :-
|
Daniel@0
|
136 message_to_string(Ex,Msg).
|
Daniel@0
|
137
|
Daniel@0
|
138 % ------------------------------------------------------------------------------------
|
Daniel@0
|
139 % Implementation of methods
|
Daniel@0
|
140
|
Daniel@0
|
141 :- multifile param/2.
|
Daniel@0
|
142
|
Daniel@0
|
143 % general
|
Daniel@0
|
144 param( format, [oneof([json,jsonp]), default(jsonp), description('Reply format')]).
|
Daniel@0
|
145 param( callback, [atom,default(jsonp_cb), description('Callback for jsonp reply')]).
|
Daniel@0
|
146
|
Daniel@0
|
147 % define_dataset
|
Daniel@0
|
148 param( library, [oneof([beets,charm,bl,ilm]), default(bl), description('Library to search within')]).
|
Daniel@0
|
149 param( dv, [nonneg, optional(false), description('Database version ID')]).
|
Daniel@0
|
150 param( genres, [atom, default(*), description('Semicolon separated list of genre names, or "*"')]).
|
Daniel@0
|
151 param( years, [atom, default(*), description('Semicolon separeted list of release years or a range (Y1-Y2) or "*"')]).
|
Daniel@0
|
152 param( composers, [atom, default(*), description('Semicolon separated list of composers or "*"')]).
|
Daniel@0
|
153 param( performers,[atom, default(*), description('Semicolon separated list of performers or "*"')]).
|
Daniel@0
|
154
|
Daniel@0
|
155 param( cid, [atom, optional(false), description('Collection ID')]).
|
Daniel@0
|
156 param( cids, [atom, optional(false), description('Semicolon separated list of Collection IDs')]).
|
Daniel@0
|
157 param( uri, [atom, optional(false), description('Recording URI')]).
|
Daniel@0
|
158 param( limit, [integer, default(5000), description('Maximum number of things to return')]).
|
Daniel@0
|
159 param( offset, [integer, default(0), description('Offset within list')]).
|
Daniel@0
|
160
|
Daniel@0
|
161 method_params(listCollections, []).
|
Daniel@0
|
162 method_params(listPerspectives, [method(_)]).
|
Daniel@0
|
163 method_params(collection_id, [library(_),dv(_),genres(_),years(_),composers(_),performers(_)]).
|
Daniel@0
|
164 method_params(Method, [ pid(_) | Params ]) :-
|
Daniel@0
|
165 perspective(Method,_,_,_,_),
|
Daniel@0
|
166 setof(P, perspective_param_name(Method,P), Ps),
|
Daniel@0
|
167 maplist(param_name_term,Ps,Params).
|
Daniel@0
|
168
|
Daniel@0
|
169 param_name_term(Name,Term) :- functor(Term,Name,1).
|
Daniel@0
|
170 perspective_param_name(Method,Name) :-
|
Daniel@0
|
171 perspective(Method,_,_,Specs,_),
|
Daniel@0
|
172 member(S,Specs),
|
Daniel@0
|
173 optspec_name(S,Name).
|
Daniel@0
|
174
|
Daniel@0
|
175
|
Daniel@0
|
176 :- multifile perspective/5.
|
Daniel@0
|
177
|
Daniel@0
|
178 method_result(listCollections, _, _{ collections:List }, unstable) :-
|
Daniel@0
|
179 findall( _{ cid:Id, query:QA, dv:DV, size:SZ },
|
Daniel@0
|
180 ( browse(dataset:dataset(dmlvis:Q, DV, Id, SZ, _)),
|
Daniel@0
|
181 term_to_atom(Q,QA)
|
Daniel@0
|
182 ),
|
Daniel@0
|
183 List).
|
Daniel@0
|
184 method_result(Method,Opts,Result,stable) :-
|
Daniel@0
|
185 method_result(Method,Opts,Result).
|
Daniel@0
|
186
|
Daniel@0
|
187
|
Daniel@0
|
188
|
Daniel@0
|
189 method_result(listPerspectives, Opts, _{ perspectives:List }) :-
|
Daniel@0
|
190 option(method(Method), Opts),
|
Daniel@0
|
191 findall( P, perspective(Method,P,_,_,_), List).
|
Daniel@0
|
192
|
Daniel@0
|
193 method_result(collection_id, Opts, _{ cid:Id, size:Size }) :-
|
Daniel@0
|
194 option(dv(DBV),Opts),
|
Daniel@0
|
195 option(library(Coll),Opts),
|
Daniel@0
|
196 collection_query(Coll, Opts, Query),
|
Daniel@0
|
197 dataset_query_id( Query, DBV, Id),
|
Daniel@0
|
198 dataset_size(Id, Size).
|
Daniel@0
|
199
|
Daniel@0
|
200 options_optspec(_,Opts,\O) :- option(O,Opts).
|
Daniel@0
|
201 options_optspec(_,Opts,O-Def) :- option(O,Opts,Def).
|
Daniel@0
|
202 options_optspec(M,Opts,O>Goal) :- options_optspec(M,Opts,O), call(M:Goal).
|
Daniel@0
|
203
|
Daniel@0
|
204 optspec_name(\O,Name) :- functor(O,Name,1).
|
Daniel@0
|
205 optspec_name(O-_,Name) :- functor(O,Name,1).
|
Daniel@0
|
206 optspec_name(O>_,Name) :- optspec_name(O,Name).
|
Daniel@0
|
207
|
Daniel@0
|
208 perspective(getRecordingPerspective, properties, dmlvis, [\uri(URI)], recording_info(URI)).
|
Daniel@0
|
209 perspective(getCollectionPerspective, summary, dmlvis, [\cid(C)], collection_summary(C)).
|
Daniel@0
|
210 perspective(getCollectionPerspective, list, dmlvis, [\cid(C),limit(Lim)-5000,offset(Off)-0], collection_list(C,Lim,Off)).
|
Daniel@0
|
211 % perspective(getCollectionPairPerspective, summary, dmlvis, [\cids(A)>parse_atom(cids([C1,C2]),A)], binary(summary,C1,C2)).
|
Daniel@0
|
212 % perspective(getMultiCollectionPerspective, summary, dmlvis, [\cids(A)>parse_atom(cids(Cs),A)], multi(summary,Cs)).
|
Daniel@0
|
213
|
Daniel@0
|
214 collection_summary(Id,Result) :-
|
Daniel@0
|
215 insist(browse(dataset:dataset(Goal,DV,Id,Size,_)), unknown_collection(Id)),
|
Daniel@0
|
216 term_to_atom(Goal,GoalA),
|
Daniel@0
|
217 Result = _{cid:Id, size:Size, goal:GoalA, dv:DV }.
|
Daniel@0
|
218
|
Daniel@0
|
219 collection_list(Id, Lim, Offset, _{cid:Id, size:Size, items:Items}) :-
|
Daniel@0
|
220 dataset_size(Id,Size),
|
Daniel@0
|
221 findall(Item,limit(Lim,offset(Offset,dataset_item(Id,Item))),Items).
|
Daniel@0
|
222
|
Daniel@0
|
223 % --------------- recording_properties -----------------------------
|
Daniel@0
|
224
|
Daniel@0
|
225 recording_info(URI, Result) :-
|
Daniel@0
|
226 ( a(mo:'AudioFile',URI) -> G=audiofile_info(URI)
|
Daniel@0
|
227 ; a(mo:'Track',URI) -> G=track_info(URI)
|
Daniel@0
|
228 ; a(mo:'Signal',URI) -> G=signal_info(URI)
|
Daniel@0
|
229 ; rdf(URI,charm:file_name,_) -> G=charm_info(URI)
|
Daniel@0
|
230 ; throw(not_a_recording(URI))
|
Daniel@0
|
231 ),
|
Daniel@0
|
232 insist(call(G,Result),failed(G)).
|
Daniel@0
|
233
|
Daniel@0
|
234 audiofile_info(URI,Result) :-
|
Daniel@0
|
235 rdf_text(URI,beets:title,Title),
|
Daniel@0
|
236 rdf_text(URI,beets:album,AlbumName),
|
Daniel@0
|
237 rdf_text(URI,beets:artist,ArtistName),
|
Daniel@0
|
238 rdf_number(URI,beets:length,Duration),
|
Daniel@0
|
239 Result = _{ type:audiofile, title:Title, artist:ArtistName, album:AlbumName, duration:Duration }.
|
Daniel@0
|
240
|
Daniel@0
|
241 track_info(Track, Result) :-
|
Daniel@0
|
242 rdf_number(Track,mo:duration,DurationMs), Duration is DurationMs/1000.0,
|
Daniel@0
|
243 rdf_text(Track,dc:title,Title),
|
Daniel@0
|
244 rdf(Record,mo:track,Track),
|
Daniel@0
|
245 rdf(Release,mo:record,Record),
|
Daniel@0
|
246 rdf_text(Release,dc:title,AlbumName),
|
Daniel@0
|
247 rdf(Artist,foaf:made,Track),
|
Daniel@0
|
248 rdf_text(Artist,foaf:name,ArtistName),
|
Daniel@0
|
249 Result = _{ type:track, title:Title, artist:ArtistName, album:AlbumName, duration:Duration }.
|
Daniel@0
|
250
|
Daniel@0
|
251 signal_info(Signal, _{type:signal, tracks:Infos}) :-
|
Daniel@0
|
252 setof(T,rdf(T,mo:publication_of,Signal),Tracks),
|
Daniel@0
|
253 maplist(track_info,Tracks,Infos).
|
Daniel@0
|
254
|
Daniel@0
|
255 charm_info(URI, PropDict) :-
|
Daniel@0
|
256 setof(Pred-Vals,setof(Val1,Val^(rdf(URI,Pred,literal(Val)),atomise_literal(Val,Val1)),Vals),Info),
|
Daniel@0
|
257 dict_pairs(PropDict,_,Info).
|
Daniel@0
|
258
|
Daniel@0
|
259 atomise_literal(type(_,Val),Val) :- !.
|
Daniel@0
|
260 atomise_literal(lang(_,Val),Val) :- !.
|
Daniel@0
|
261 atomise_literal(Val,Val).
|
Daniel@0
|
262
|
Daniel@0
|
263 % -------------------- defining a dataset ------------------------------
|
Daniel@0
|
264
|
Daniel@0
|
265 qc(beets,Opts,X) :- maplist(filter(beets,X),Opts), a(mo:'AudioFile',X).
|
Daniel@0
|
266 qc(charm,Opts,X) :- maplist(filter(charm,X),Opts), rdf(X,charm:file_name,_).
|
Daniel@0
|
267 qc(bl,Opts,X) :- maplist(filter(bl,X),Opts), rdf(X,rdf:type,mo:'Signal',bl_p2r).
|
Daniel@0
|
268
|
Daniel@0
|
269 filter(_,_,genres(*)) :- true.
|
Daniel@0
|
270 filter(beets,X,genres(any(Gs))) :- member(G,Gs), rdf_has(X,beets:genre,literal(substring(G),_)).
|
Daniel@0
|
271
|
Daniel@0
|
272 filter(_,_,years(*)) :- true.
|
Daniel@0
|
273 filter(D,X,years(any(Ys))) :- member(Y,Ys), filter(D,X,years(Y-Y)).
|
Daniel@0
|
274 filter(D,X,years(L-U)) :- succ(U,U1), atom_number(LA,L), atom_number(U1A,U1), filter(D,X,years(LA,U1A)).
|
Daniel@0
|
275 filter(beets,X,years(L,U)) :- rdf(X, beets:original_year, literal(between(L,U),_)).
|
Daniel@0
|
276 filter(charm,X,years(L,U)) :- rdf(X, charm:recording_date, literal(between(L,U),_)).
|
Daniel@0
|
277 filter(bl,X,years(L,U)) :- rdf(X, dcterms:created, literal(between(L,U),_)).
|
Daniel@0
|
278
|
Daniel@0
|
279 filter(_,_,composers(*)) :- true.
|
Daniel@0
|
280 filter(D,X,composers(any(List))) :- member(C,List), filter(D,X,composer(C)).
|
Daniel@0
|
281 filter(charm,X,composer(C)) :- rdf(X, charm:composer, literal(prefix(C),_)).
|
Daniel@0
|
282 filter(bl,X,composer(C)) :- rdf(X, marcrel:cmp, literal(prefix(C),_)).
|
Daniel@0
|
283 filter(_,_,performers(*)) :- true.
|
Daniel@0
|
284 filter(D,X,performers(any(List))) :- member(C,List), filter(D,X,performer(C)).
|
Daniel@0
|
285 filter(charm,X,performer(C)) :- rdf(X, charm:performer, literal(prefix(C),_)).
|
Daniel@0
|
286 filter(bl,X,performer(C)) :- rdf(X, marcrel:prf, literal(prefix(C),_)).
|
Daniel@0
|
287 filter(beets,X,performer(C)) :- rdf(X, beets:artist, literal(prefix(C),_)).
|
Daniel@0
|
288 filter(charm,X,title(C)) :- rdf(X, charm:title, literal(substring(C),_)).
|
Daniel@0
|
289 filter(bl,X,title(C)) :- rdf(X, dc:title, literal(substring(C),_)).
|
Daniel@0
|
290 filter(beets,X,title(C)) :- rdf(X, beets:title, literal(like(C),_)).
|
Daniel@0
|
291
|
Daniel@0
|
292
|
Daniel@0
|
293 collection_query(Coll, Opts, qc(Coll,Filters)) :-
|
Daniel@0
|
294 seqmap(process_qopt(Opts),
|
Daniel@0
|
295 [ qo( genres(GA), genres(GS), genres(*), parse_atom(atoms(GS), GA))
|
Daniel@0
|
296 , qo( composers(CA), composers(CS), composers(*), parse_atom(atoms(CS), CA))
|
Daniel@0
|
297 , qo( performers(PA), performers(PS), performers(*), parse_atom(atoms(PS), PA))
|
Daniel@0
|
298 , qo( years(YA), years(YS), years(*), parse_atom(years(YS), YA))
|
Daniel@0
|
299 , qo( title(T), title(T), title(*), true)
|
Daniel@0
|
300 ],
|
Daniel@0
|
301 Filters, []).
|
Daniel@0
|
302
|
Daniel@0
|
303 process_qopt(Opts,qo(Opt,Filter,NullFilter,Goal)) -->
|
Daniel@0
|
304 {option(Opt,Opts,'*'), call(Goal)},
|
Daniel@0
|
305 ({Filter=NullFilter} -> []; [Filter]).
|
Daniel@0
|
306
|
Daniel@0
|
307
|
Daniel@0
|
308 % --------- parsers -----------
|
Daniel@0
|
309
|
Daniel@0
|
310 % cids(Ids) --> seqmap_with_sep(",",alphanum,Ids).
|
Daniel@0
|
311 cids(Ids) --> semicolon_sep(atom_codes,Ids).
|
Daniel@0
|
312
|
Daniel@0
|
313 atoms('*') --> "*", !.
|
Daniel@0
|
314 atoms(any(AS)) --> semicolon_sep(atom_codes,AS).
|
Daniel@0
|
315
|
Daniel@0
|
316 years('*') --> "*", !.
|
Daniel@0
|
317 years(L-U) --> integer(L), "-", integer(U).
|
Daniel@0
|
318 years(any(Ys)) --> semicolon_sep(number_codes,Ys).
|
Daniel@0
|
319
|
Daniel@0
|
320
|
Daniel@0
|
321
|
Daniel@0
|
322 % alphanum(X) --> string_without(",",S), {atom_string(X,S)}.
|
Daniel@0
|
323
|
Daniel@0
|
324 item(Conv,Item) --> string_without(";",Codes), {call(Conv,Item,Codes)}.
|
Daniel@0
|
325 semicolon_sep(Conv,Items) -->
|
Daniel@0
|
326 seqmap_with_sep(";",item(Conv),Items).
|
Daniel@0
|
327
|
Daniel@0
|
328
|
Daniel@0
|
329 parse_atom(Phrase,Atom) :-
|
Daniel@0
|
330 atom_codes(Atom,Codes),
|
Daniel@0
|
331 debug(vis,'Attempting to parse ~q with ~q...',[Atom,Phrase]),
|
Daniel@0
|
332 insist( phrase(Phrase,Codes), parse_failure(Phrase)),
|
Daniel@0
|
333 debug(vis,'...got ~q',[Phrase]).
|
Daniel@0
|
334
|