13
14:- module(wn_utilities, [
15 wn_word/1, 16 wn_measure/1, 17 check_wn_words/2, 18 wn_display_graph/1, 19 wn_maxDepth/2, 20 wn_max_wordnet_sense/3, 21 wn_virtual_root/2, 22 wn_convert_synsetID_to_representative/2, 23 wn_convert_synsetIDs_to_representatives/2, 24 atoms_functors_in_term/3, 25 bpl_predicates/3 26 ]
27 ).
28
30
40wn_word(Word) :-
41 atom(Word),
42 !,
43 wordnet:wn_s(_, _, Word, _, _, _).
44
45wn_word(Word:Type:Sense) :-
wordnet:wn_s(_, _, Word, Type, Sense, _).
54wn_measure(path).
55wn_measure(wup).
56wn_measure(lch).
66check_wn_words([], _).
67
68check_wn_words([Word|Words], WordNotFound) :-
69 wn_word(Word),
70 !,
71 check_wn_words(Words, WordNotFound).
72
73check_wn_words([Word|_Words], Word).
74
75
76
87
92
93
97pdf_displayer(PDFViewer) :-
98 getenv('PDFViewer', PDFViewer),
99 !
99.
100
101pdf_displayer('open -a Preview') :-
102 current_prolog_flag(apple, true), 103 !.
104
105pdf_displayer('xpdf') :-
106 current_prolog_flag(unix, true), 107 !.
108
109pdf_displayer('acrobat.exe /A "view=Fit"') :-
110 current_prolog_flag(windows, true), 111 !.
112
113:- if((getenv('OSTYPE',OSystem), OSystem = darwin16)).
115 pdf_displayer('open -a Preview').
116:- elif((getenv('OSTYPE',OSystem), OSystem = linux-gnu)).
118 pdf_displayer('xpdf').
119:- else.
121 pdf_displayer('acrobat.exe /A "view=Fit"').
122:- endif.
123
133wn_display_graph(Graph) :-
134 open('out.dot', write, Handle),
135 write(Handle, 'digraph G { size="1,1";'),
136 nl(Handle),
137 write_arcs(Handle, Graph),
138 write(Handle,'}'),
139 close(Handle),
140 141 display_dot_in_pdf.
142
143display_dot_in_pdf :-
144 ( write('Displaying graph...'),
145 nl,
146 shell('dot out.dot -Tpdf -o out.pdf'),
147 pdf_displayer(PDFViewer),
148 atom_concat(PDFViewer, ' out.pdf', PDFViewerCommand),
150 (shell(PDFViewerCommand) -> true
151 ; write('ERROR: Cannot start PDF viewer. Check the environment variable PDFViewer')
152 ),
153 !
154 ;
155 write('ERROR: Cannot generate PDF output file. Check that the dot program is accesible')
156 )
156.
157
158write_arcs(_Handle,[]).
159write_arcs(Handle,[arc(A,B)|R]):-
160 write(Handle,A),
161 write(Handle,' -> '),
162 write(Handle,B),
163 write(Handle,';'),
164 nl(Handle),
165 write_arcs(Handle,R).
166
173wn_maxDepth(n, 20). 174wn_maxDepth(v, 14). 175
176
183wn_max_wordnet_sense(Word, WType, MaxSense) :-
184 findall(WSense, wordnet:wn_s(_Synset_id, _WNum, Word, WType, WSense, _Tag_count), WSenseList),
185 max_list(WSenseList, MaxSense).
186
187
205wn_virtual_root(SynSet_ID, Virtual_Root_ID) :-
206 ((SynSet_ID > 100000000, SynSet_ID < 200000000) ->
207 Virtual_Root_ID = 100000000
208 ;
209 ((SynSet_ID > 200000000, SynSet_ID < 300000000) ->
210 Virtual_Root_ID = 200000000
211 ;
212 fail
213 )
214 ).
215
216
217%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
218
219%%% wn_convert_synsetID_to_representative(+SynSet_ID, -Word_string)
220%%%
221wn_convert_synsetID_to_representative(SynSet_ID, Word_string) :-
222 wordnet:wn_s(SynSet_ID, 1, Word, SS_type, Sense_num, _),
223 word_term_to_string(Word:SS_type:Sense_num, Word_string).
224
225
233wn_convert_synsetIDs_to_representatives([],[]).
234wn_convert_synsetIDs_to_representatives([SynSet_ID|SynSet_IDs],[Word_string|Representatives]):-
235 wn_convert_synsetID_to_representative(SynSet_ID, Word_string),
236 wn_convert_synsetIDs_to_representatives(SynSet_IDs, Representatives).
237
238
239%%% word_term_to_string(+Word:SS_type:Sense_num, -Word_string)
240%%%
241%%% Converts a word term Word:SS_type:Sense_num into a string "<Word>_<SS_type>_<Sense_num>".
242%%% For instance, the word term 'psychological feature':n:1 is converted into "psychological_feature_n_1".
243%%%
244word_term_to_string(Word:SS_type:Sense_num, Word_string):-
245 %% adapting Word, which may be a composed atom (e.g. 'psychological feature'
246 %% or 'Grimes\' golden')
247 atom_string(Word, S), split_string(S, "\' -", " ", L1), %% delimiters: \' and blank space character
248 list_strings_to_string(L1, S1),
249 string_concat(S1, "_", S2),
250 string_concat(S2, SS_type, S3),
251 string_concat(S3, "_", S4),
252 number_string(Sense_num, SN),
253 string_concat(S4, SN, Word_string).
254
255
259list_strings_to_string([],"").
260list_strings_to_string([Str],Str):- !.
261list_strings_to_string([Str|StrLists], String) :-
262 (Str="" ->
263 S=Str
264 ;
265 string_concat(Str, "_", S)
266 ),
267 list_strings_to_string(StrLists, SS),
268 string_concat(S, SS, String).
269
270
271
276
277atoms_functors_in_term(Term, Atoms, Functors) :-
278 atoms_functors_in_term(Term, [], DupAtoms, [], DupFunctors),
279 ordsets:list_to_ord_set(DupAtoms, Atoms),
280 ordsets:list_to_ord_set(DupFunctors, Functors).
281
282
283atoms_functors_in_term(Var, Atoms, Atoms, Functors, Functors):-
284 var(Var),
285 !.
286
287atoms_functors_in_term(Number, Atoms, Atoms, Functors, Functors):-
288 number(Number),
289 !.
290
291atoms_functors_in_term(Atom, Atoms, [Atom|Atoms], Functors, Functors):-
292 atom(Atom),
293 !.
294
295atoms_functors_in_term([], Atoms, Atoms, Functors, Functors) :-
296 !.
297
298atoms_functors_in_term([Term|Terms], AtomsIn, AtomsOut, FunctorsIn, FunctorsOut) :-
299 !,
300 atoms_functors_in_term_list([Term|Terms], AtomsIn, AtomsOut, FunctorsIn, FunctorsOut).
301
302atoms_functors_in_term(Term, AtomsIn, AtomsOut, FunctorsIn, FunctorsOut) :-
303 Term =.. [Functor|Terms],
304 atoms_functors_in_term_list(Terms, AtomsIn, AtomsOut, [Functor|FunctorsIn], FunctorsOut).
305
306
307atoms_functors_in_term_list([], Atoms, Atoms, Functors, Functors).
308
309atoms_functors_in_term_list([Term|Terms], AtomsIn, AtomsOut, FunctorsIn, FunctorsOut):-
310 atoms_functors_in_term(Term, AtomsIn, AtomsOut1, FunctorsIn, FunctorsOut1),
311 atoms_functors_in_term_list(Terms, AtomsOut1, AtomsOut, FunctorsOut1, FunctorsOut).
312
313
314
320
321bpl_predicates([], [], []).
322
323bpl_predicates([Functor|Functors], NonPredicates, [Predicate|Predicates]) :-
324 remove_program_prefix(Functor, Predicate),
325 Functor\==Predicate,
326 !,
327 bpl_predicates(Functors, NonPredicates, Predicates).
328
329bpl_predicates([NonPredicate|Functors], [NonPredicate|NonPredicates], Predicates) :-
330 bpl_predicates(Functors, NonPredicates, Predicates).
338remove_program_prefix(Atom, Result) :-
339 parser:program_prefix(Prefix),
340 atom_concat(Prefix, '_', PrefixUS),
341 atom_concat(PrefixUS, Result, Atom),
342 !.
343
344remove_program_prefix(Atom, Atom)