1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%% WN_CONNECT source v1.3 : wn_utilities module 
    3%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    4/*
    5AUTHORS: Pascual Julián-Iranzo (Universidad de Castilla-La Mancha, Spain)
    6Fernando Sáenz-Pérez  (Universidad Complutense de Madrid, Spain)
    7
    8WN_CONNECT is licensed for research and educational purposes only and it is
    9distributed with NO WARRANTY OF ANY KIND. You are freely allowed to use, copy
   10and distribute WN_CONNECT provided that you make no modifications to any of its
   11files and give credit to its original authors.
   12*******************************************************************************/
   13
   14:- module(wn_utilities, [
   15  	wn_word/1,              % ?Word
   16  	wn_measure/1,           % ?Measure
   17  	check_wn_words/2,       % +Words, -Word
   18  	wn_display_graph/1,     % +Graph
   19  	wn_maxDepth/2,          % (+Type, -MaxDepth)
   20  	wn_max_wordnet_sense/3, % (+Word, +Type, -MaxSense)
   21  	wn_virtual_root/2,      % (+List_HyperNymSynSets, -Virtual_Root_ID)
   22  	wn_convert_synsetID_to_representative/2,   % (+SynSet_ID, -Word_string)
   23  	wn_convert_synsetIDs_to_representatives/2, % (+List_SynSet_IDs, -List_representatives)
   24		atoms_functors_in_term/3, % +Term, -Atoms, -Functors
   25		bpl_predicates/3        % +Functors, -NonPredicates, -Predicates
   26	]
   27	).
   28	
   29%:- use_module(library(ordsets)).
   30	
   31%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   32%% PREDICATES USED IN THE AUTOMATIC GENERATION OF PROXIMITY EQUATIONS
   33%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 wn_word(?Word)
Unifies Word with one of the words in WordNet.
   40wn_word(Word) :-
   41  atom(Word),
   42  !,
   43  wordnet:wn_s(_, _, Word, _, _, _).
   44 
   45wn_word(Word:Type:Sense) :-
   46  wordnet:wn_s(_, _, Word, Type, Sense, _).
 wn_measure(?Measure)
Unifies Measure with one of the supported WordNet measures.
   54wn_measure(path).
   55wn_measure(wup).
   56wn_measure(lch).
 check_wn_words(+Words, -Word)
Return in Word the first word in the list Words which is not found in WordNet. If all words are found, Word will not be unified.
   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
   77%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   78% PREDICATES FOR GRAPHICAL DISPLAY OF GRAPHS
   79%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   80%
   81% Use:
   82%   wn_display_graph(Graph), where Graph=[arc(v1,v2),...,arc(vn-1,vn)]
   83%
   84% Examples:
   85%   ?- findall(arc(X,Y),(wn_hypernyms(man,List),append(_,[X,Y|_],List)),Graph), wn_display_graph(Graph).
   86%   ?- setof(arc(X,Y),List^H^T^(wn_hypernyms(man,List),append(H,[X,Y|T],List)),Graph), wn_display_graph(Graph).
   87
   88% Requires:
   89% - PDF displayer (as indicated in pdf_displayer/1 fact and accesible in the path).
   90% - dot (part of Graphviz, accesible in the path)
   91% - dot2tex (for generating a LaTeX version of the graph). If LaTeX output is enabled (disabled by default)
   92
   93
   94%%% 'PDFViewer' is a user defined environment variable that must be exported to
   95%%% be accesible by the son process that executes SWI-Prolog. It stores the command
   96%%% to launch the specific PDF viewer of the operating system we are using.
   97pdf_displayer(PDFViewer) :-
   98    getenv('PDFViewer', PDFViewer),
   99    !
   99.
  100
  101pdf_displayer('open -a Preview') :-
  102    current_prolog_flag(apple, true), % MacOS system
  103    !.
  104
  105pdf_displayer('xpdf') :-
  106    current_prolog_flag(unix, true), % Linux system
  107    !.
  108
  109pdf_displayer('acrobat.exe /A "view=Fit"') :-
  110    current_prolog_flag(windows, true), % Windows system
  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
  124% wn_display_graph(+Graph)
  125%   Graph is a list of arc(From,To)
  126%   Displays a PDF containing the graphical representation of Graph
  127%   Creates the files:
  128%   - out.dot: A file with the graph in DOT format (graph description language)
  129%   - out.pdf: The PDF document with the graph representation
  130%   - out.tex: The LaTeX document with the graph representation.
  131%              Disabled for now (just uncomment it below for enabling)
  132%
  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    % shell('dot2tex out.dot > out.tex'),
  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
  167%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  168%%%        PARAMETERS AND OTHER AUXILIARY PREDICATES
  169%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  170%%% wn_maxDepth(+Type, -MaxDepth)
  171%%% Returns the maximum depth of a concept in the hierachies of nouns (Type=n) and verbs (Type=v).
  172%%%
  173wn_maxDepth(n, 20).     % (max depth for nouns in WordNet HyperTrees is 20)
  174wn_maxDepth(v, 14).     % (max depth for verbs in WordNet HyperTrees is 14)
  175
  176
  177%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  178%%% wn_max_wordnet_sense(+Word, +Type, -MaxSense)
  179%%% Returns the maximum number of senses, 'MaxSense', of a word, 'Word', of type, 'Type'.
  180%%% If the parameters 'Word' and 'Type' are not instantiated then it returns the maximum
  181%%% number of senses for a word in the WordNet data base.
  182%%%
  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
  188%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  189%%% wn_virtual_root(SynSet_ID, -Virtual_Root_ID)
  190%%% Given a SynSet_ID and, acording to it, generates a virtual Root ID
  191%%%
  192%%% NOTE 1 (PROBLEMS WITH the Root of the hierarchy):
  193%%% Verbs do not have an explicit root. It may be that two verbs
  194%%% do not share a Less Common Subsumer. In this case LCS=Root and Root is assigned
  195%%% to a virtual root for verbs (Synset_ID = 200000000). Note that in this case, the
  196%%% information content of the LCS is 0 and the similarity of these two verbs should
  197%%% be around 0 also.
  198%%% On the other hand, nouns have a unique root hierarchy which is "entity" (synset_ID =
  199%%% 100001740). However, by uniformity of treatment we introduce a virtual root for names
  200%%% (Synset_ID = 100000000).
  201%%%
  202%%% NOTE 2: This predicate is useful when computing similarity measures and information
  203%%% content of words.
  204%%%
  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
  226%%% wn_convert_synsetIDs_to_representatives(+List_SynSet_IDs, -List_representatives)
  227%%% List_SynSet_IDs is a list of synset_IDs (which usually are hypernyms or hyponyms of a given word).
  228%%% This predicate converts List_SynSet_IDs into a list of representative words.
  229%%%
  230%%% We mean by "representative word" the first word of the synset. The one with W_num=1. This is
  231%%% usually the most representative word of the sysntet.
  232%%%
  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):-
  246    
  247    atom_string(Word, S), split_string(S, "\' -", " ", L1),
  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)
  253.
  254
  255
  256%%% list_strings_to_string(+Lis_of_strings, +String)
  257%%% Concatenates the Lis_of_strings into one String.
  258%%%
  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
  272%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  273% atoms_functors_in_term(+Term, -Atoms,-Functors) 
  274%   Returns all the atoms in Term
  275%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  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
  315%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  316% bpl_predicates(+Functors, -NonPredicates, -Predicates)
  317%   Returns non-predicate functors in NonPredicates,
  318%   and predicate functors in Predicates
  319%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  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).
 remove_program_prefix(+Atom, -Result)
Removes the current program prefix from Atom and returns in Result. If Atom does not include the program prefix, just returns Atom.
  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)