1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%% WN_CONNECT source v1.3 : wn_sim_adjectives 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%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   14This module defines predicates that find the adjectives which are similar
   15in meaning to a input adjective. Do not confuse "similar" with "synonym".
   16Synonym words are grouped in a synset and they are words equals in meaning.
   17In other words, synonym words must have the maximum (top) degree of similarity.
   18
   19Most of predicates defined in this module a based on the operator "sim"
   20
   21-------------------------
   22sim(synset_id,synset_id).
   23-------------------------
   24The "sim" operator specifies that the second synset is similar in meaning
   25to the first synset. This means that the second synset is a satellite of
   26the first synset (or viceversa), which is the cluster head. This relation
   27only holds for adjective synsets contained in adjective clusters.
   28
   29The two addressed synsets are either two head synsets, or one head synset
   30and one satellite synset. There is no matching sim clause for two satellite
   31synsets. Because, if they would have similar meanings, they would be grouped
   32together in one synset.
   33
   34Therefore, the predicates defined in this module are for adjectives and do not
   35work for other parts of speech.
   36*******************************************************************************/
   37
   38
   39:- module(wn_similar_adjectives, [
   40    wn_sim_adjectives_of/2,         % (+Adjective, -List_sim_SynSets)
   41    wn_sim_adjectives_of/3,         % (+Adjective, +Verbosity, -List_sim_SynSets)
   42    wn_display_sim_adjectives_of/1, % (+Adjective)
   43    wn_display_sim_adjectives_of/2, % (+Adjective, +Verbosity)
   44    wn_display_graph_sim_adjectives_of/1, % (Adjective)
   45    wn_display_graph_cluster_of/1 %(Adjective)
   46]).   47
   48:- use_module(wn_synsets).   49
   50
   51
   52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   53%% wn_sim_adjectives_of(+Adjective, -List_sim_SynSets)
   54%% It is true if List_sim_SynSets is a list of similar adjectives synsets of the
   55%% adjective Adjective.
   56%% Only adjectives can be similar one of each other. That is, words of type "a" or "s".
   57%% There is no matching sim clause for two satellite synsets. Because, if they would
   58%% have similar meanings, they would be grouped together in one synset.
   59%%
   60%%% The word "Adjective" is a term with the following syntax:
   61%%%                      Word[:SS_type[:Sense_num]]
   62%%%%%%%%%%
   63
   64
   65wn_sim_adjectives_of(Adjective, List_sim_SynSets) :-
   66        wn_sim_adjectives_of(Adjective, verbose(yes), List_sim_SynSets).
   67
   68
   69%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   70%%% wn_sim_adjectives_of(+Adjective, +Verbosity, -List_sim_SynSets)
   71%%%
   72wn_sim_adjectives_of(Adjective, Verbosity, [Head_Adj_SynSet|List_sim_SynSets]) :-
   73    get_head_adjective_of(Adjective, Verbosity, Head_Adj_SynSet),
   74    wordnet:wn_s(Head_Adj_SynSet, _W_num, _Head_Adj, _SS_type, _SS_num, _W_Tag_count),
   75    findall(Synset_ID, wordnet:wn_sim(Head_Adj_SynSet, Synset_ID), List_sim_SynSets).
   76
   77
   78
   79
   80%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   81%%%  TEXTUAL REPRESENTATION OF LISTS OF SIMILAR ADJECTIVES
   82%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   83
   84%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   85%%% wn_display_sim_adjectives_of(+Adjective)
   86%%% Given a word (term) "Adjective", prints the list of representatives of its
   87%%% similar synsets. The head adjective is listed first.
   88%%%
   89%%% The word "Adjective" is a term with the following syntax:
   90%%%                      Word[:SS_type[:Sense_num]]
   91%%% as explained in the predicate wn_sim_adjectives_of/2
   92
   93
   94wn_display_sim_adjectives_of(Adjective) :-
   95    wn_display_sim_adjectives_of(Adjective, verbose(yes)).
   96
   97
   98%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   99%%% wn_display_sim_adjectives_of(+Adjective, +Verbosity)
  100%%%
  101wn_display_sim_adjectives_of(Adjective, Verbosity) :-
  102    wn_sim_adjectives_of(Adjective, Verbosity, List_sim_SynSets),
  103    display_sim_adjectives_list(Adjective, List_sim_SynSets).
  104
  105
  106
  107%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  108%%% display_sim_adjectives_list(List_sim_SynSets)
  109
  110display_sim_adjectives_list(Adjective, List_sim_SynSets) :-
  111    write(">>> SIMILAR ADJECTIVES OF "), write(Adjective), write(' :'), nl,
  112    display_sim_adjectives_list(List_sim_SynSets).
  113
  114display_sim_adjectives_list([]).
  115display_sim_adjectives_list([SynSet_ID|List_SynSet_IDs]):-
  116        wn_synsets:wn_synset_components(SynSet_ID, Synset_Words, verbose(yes)),
  117        write(' ~~ '),
  118        write(Synset_Words), nl,
  119        display_sim_adjectives_list(List_SynSet_IDs).
  120
  121
  122
  123
  124%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  125%%%  GRAPHICAL REPRESENTATION OF LISTS OF SIMILAR ADJECTIVES
  126%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  127
  128%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  129%%% wn_display_graph_sim_adjectives_of(+Adjective):
  130%%% Displays a graphical representation of all adjectives which are similar to "Adjective".
  131%%% This representation is shown as a hierarchy with the head adjective in the root and the
  132%%% satellite adjectives in the leaves.
  133%%%
  134wn_display_graph_sim_adjectives_of(Adjective) :-
  135    wn_sim_adjectives_of(Adjective, verbose(no), [Head_Adj_SynSet|List_sim_SynSets]),
  136    wn_convert_synsetID_to_representative(Head_Adj_SynSet, Representative),
  137    wn_convert_synsetIDs_to_representatives(List_sim_SynSets, List_Representatives),
  138    setof(arc(Representative,Y), member(Y, List_Representatives), Graph),
  139    wn_display_graph(Graph).
  140
  141
  142%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  143%%% wn_display_graph_cluster_of(+Adjective):
  144%%% Displays a graphical representation of the cluster to which the "Adjective" belongs.
  145%%% A cluster is formed by two head adjectives, which are antonyms one of each other,
  146%%% and their corresponding satellite adjectives in the leaves.
  147%%%
  148wn_display_graph_cluster_of(Adjective) :-
  150        wn_sim_adjectives_of(Adjective, verbose(no), [Head_Adj_SynSet|List_sim_SynSets]),
  151        wn_convert_synsetID_to_representative(Head_Adj_SynSet, Representative),
  152        wn_convert_synsetIDs_to_representatives(List_sim_SynSets, List_Representatives),
  153        setof(arc(Representative,Y), member(Y, List_Representatives), Graph1),
  154        write('Graph1 : '), write(Graph1), nl,
  156        wn_ant(Head_Adj_SynSet, _, Ant_Adjective, _),
  157        write('Ant_Adjective : '), write(Ant_Adjective), nl,
  159        findall(Synset_ID, wordnet:wn_sim(Ant_Adjective, Synset_ID), Ant_List_sim_SynSets),
  160        wn_convert_synsetID_to_representative(Ant_Adjective, Ant_Representative),
  161        wn_convert_synsetIDs_to_representatives(Ant_List_sim_SynSets, Ant_List_Representatives),
  162        setof(arc(Ant_Representative,Y), member(Y, Ant_List_Representatives), Graph2),
  163        write('Graph2 : '), write(Graph2), nl,
  165        app(Graph1, [arc(Representative,Ant_Representative),arc(Ant_Representative,Representative)|Graph2], Graph),
  166        wn_display_graph(Graph)
  166.
  167
  168
  169
  170
  171
  172%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  173%%%        AUXILIARY PREDICATES
  174%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  175
  176%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  177%% get_head_adjective_of(Adjective, Head_Adj_SynSet)
  178%% It is true if Head_Adj_SynSet is a similar head adjective synset of the adjective
  179%% Adjective.
  180%% If Adjective is a head adjective (that is of type "a") this predicate returns itself
  181%% Otherwise if Adjective is a satellite adjective (that is of type "s") it looks for
  182%% the corresponding head adjective and returns it.
  183%% Only adjectives can be similar one of each other. That is, words of type "a" or "s".
  184%% There is no matching sim clause for two satellite synsets. Because, if they would
  185%% have similar meanings, they would be grouped together in one synset.
  186%%
  187%%% The word "Adjective" is a term with the following syntax:
  188%%%                      Word[:SS_type[:Sense_num]]
  189%%%%%%%%%%
  190
  191get_head_adjective_of(Adjective:SS_type:SS_num, Verbosity, Head_Adj_SynSet) :-
  192    !,
  193    wordnet:wn_s(A_Synset_ID, _W_num, Adjective, SS_type, SS_num, _W_Tag_count),
  194    get_head_adjective_of(Adjective:SS_type:SS_num, A_Synset_ID, Verbosity, Head_Adj_SynSet).
  195
  196get_head_adjective_of(Adjective:SS_type, Verbosity, Head_Adj_SynSet) :-
  197    !,
  198    wordnet:wn_s(A_Synset_ID, _W_num, Adjective, SS_type, SS_num, _W_Tag_count),
  199    get_head_adjective_of(Adjective:SS_type:SS_num, A_Synset_ID, Verbosity, Head_Adj_SynSet).
  200
  201get_head_adjective_of(Adjective, Verbosity, Head_Adj_SynSet) :-
  202    wordnet:wn_s(A_Synset_ID, _W_num, Adjective, SS_type, SS_num, _W_Tag_count),
  203    get_head_adjective_of(Adjective:SS_type:SS_num, A_Synset_ID, Verbosity, Head_Adj_SynSet).
  204
  205%%%%%
  206get_head_adjective_of(Adjective:SS_type:SS_num, A_Synset_ID, Verbosity, Head_Adj_SynSet) :-
  207    ((SS_type=a) ->
  208        Head_Adj_SynSet = A_Synset_ID
  209        ;
  210        ((SS_type=s)  ->
  211            wordnet:wn_sim(Head_Adj_SynSet, A_Synset_ID)
  212            ;
  213            ((Verbosity = verbose(yes)) ->
  214            write(">>>> "), write(Adjective:SS_type:SS_num), nl,
  215            wordnet:wn_g(A_Synset_ID, Glos),
  216            write(Glos), nl,
  217            write("Only adjectives can have a head adjective and related by the 'sim' relation"),
  218            nl),
  219            fail
  220        )
  221    ).
  222
  223
  224%%%%%%%%%%%%%%%%%%%%%%%%%%
  225app(List1, List2, App_List) :- app(List1, List2, App_List, []).
  226
  227app(List1, List2) --> List1, List2