1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%% WN_CONNECT source v1.3 : wn_sim_measures 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_sim_measures, [
   15      	wn_path/3,        %(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   16		wn_path_nondet/3, %(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   17        wn_wup/3,         %(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   18        wn_wup_nondet/3,  %(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   19        wn_lch/3,         %(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   20        wn_lch_nondet/3   %(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   21   ]).   22
   23:- use_module(wn_hypernyms).   24:- use_module(wn_synsets).   25:- use_module(wn_utilities).   26
   27
   28
   29%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   30%%% PATH SIMILARIRY MEASURE
   31%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   32%%% wn_path(+Word1:SS_type1:W1_Sense_num, +Word2:SS_type2:W2_Sense_num, -Degree)
   33%%% This predicate implements the PATH similarity measure.
   34%%% Takes two concepts (terms -- Word:SS_type:Sense_num) and returns the degree of
   35%%% similarity between them.
   36%%%
   37%%% A concept can have different HyperTrees. Therefore, depending on the different HyperTrees
   38%%% of c1 and c2 involved in the computation, different similarity values can be obtained:
   39%%%
   40%%%     sim_PATH(c1, c2) = 1/len(c1, c2)
   41%%%
   42%%% where len(W1, W2) = (DepthW1-LCS_depth) + (DepthW2-LCS_depth) +1
   43%%%
   44%%% This predicate combines all HyperTrees of c1 and c2, computes the respective similarity
   45%%% values and returns the maximum (the task is done by the auxiliary predicate max_path/3).
   46%%%
   47%%% NOTE: "Word1:SS_type1:W1_Sense_num" denotes the concept c1 and "Word2:SS_type2:W2_Sense_num"
   48%%%       the concept c2. Note that we do not explicitly require information about
   49%%%       the synset type and sense number of a word.
   50%%%
   51%%%       We check that both Word1 and Word2 are nouns or verbs but not combinations of them.
   52%%%
   53
   54wn_path(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree) :-
   55((nonvar(Word1), nonvar(Word2)) ->
   56%  (lists:member((SS_type1,SS_type2), [(n,n), (v,v)]) ->
   57  (lists:member((SS_type1,SS_type2), [(n,n), (v,v)]),
   58    (var(W1_Sense_num) ->
   59        wn_max_wordnet_sense(Word1, SS_type1, W1MaxSense),
   61        between(1, W1MaxSense, W1_Sense_num),
   62        (var(W2_Sense_num) ->
   63            wn_max_wordnet_sense(Word2, SS_type2, W2MaxSense),
   65            between(1, W2MaxSense, W2_Sense_num),
   66            max_path(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
   67            ;
   68            max_path(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
   69        )
   70        ;
   71        (var(W2_Sense_num) ->
   72            wn_max_wordnet_sense(Word2, SS_type2, W2MaxSense),
   74            between(1, W2MaxSense, W2_Sense_num),
   75            max_path(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
   76            ;
   77            max_path(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
   78        )
   79    )
   80    ;
   81    write("ERROR: Both Word1 and Word2 must be either nouns or verbs (but not combinations of them or adjectives)"),
   82    nl
   83  )
   84  ;
   85  write("ERROR:  Word1 or Word2 is a variable. You must enter a specific word (either noun or verb)."),
   86  nl
   87)
   87.
   88
   89
   90%%%%%%%%%%%%%%%%%%%
   91%%% path(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
   92%%% Nondeterministic predicate. It inspects a pair of HyperTrees associated to 
   93%%% c1 and c2 and obtains the degree of similarity between c1 and c2
   94%%% (according to that pair of HyperTrees)
   95%%%
   96%%% The degree of similarity obtained depends on the HyperTrees of c1 and c2 involved
   97%%% in the computation.
   98%%%
   99%%%         sim_PATH(c1, c2) = 1/len(c1, c2)
  100%%%
  101%%% where len(W1, W2) = (DepthW1-LCS_depth) + (DepthW2-LCS_depth) +1
  102%%%
  103path(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  104    lcs(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, _, LCS_depth, DepthW1, DepthW2),
  105    Degree is (1 / ((DepthW1-LCS_depth) + (DepthW2-LCS_depth) +1)).
  106
  107
  108%%%%%%%%%%%%%%%%%%%
  109%%% max_path(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  110%%% It obtains the degree of similarity between the concepts Word1:SS_type:W1_Sense_num
  111%%% and Word2:SS_type:W2_Sense_num using the PATH measure.
  112%%%
  113%%% A concept can have more than one HyperTree, therefore several pairs of HyperTrees
  114%%% are possibly considered and a list of similarity degrees 'Degs' is obtained using path/3.
  115%%% Finally, the maximum degree in the list 'Degs' is selected as a result.
  116%%%
  117%%% NOTE: When this predicate is executed, it is intended that all variables in
  118%%%       Word1:SS_type:W1_Sense_num and in Word2:SS_type:W2_Sense_num are completely
  119%%%       instantiated.
  120%%%
  121max_path(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  122	findall(Deg ,path(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Deg), Degs),
  123	lists:max_list(Degs, Degree).
  124
  125
  126%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  127%%% wn_path_nondet(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  128%%% Inspects a pair of HyperTrees associated to c1 and c2 and obtains the degree
  129%%% of similarity between c1 and c2 (according to that pair of HyperTrees)
  130%%%
  131%%% NOTE: Nondeterministic predicate. It is the user interface to the local predicate path/3.
  132%%%
  133wn_path_nondet(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  134   ( (SS_type=n; SS_type=v) ->
  135    path(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree)
  136    ;
  137	write("ERROR: Both Word1 and Word2 must be nouns or verbs but not combinations of them"),
  138	nl
  139   ).
  140
  141
  142%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  143%%% WUP SIMILARIRY MEASURE
  144%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  145%%% wn_wup(+Word1, +Word2, -Degree)
  146%%% This predicate implements the WUP similarity measure.
  147%%% Takes two concepts (terms -- Word:SS_type:Sense_num) and returns the degree of
  148%%% similarity between them.
  149%%%
  150%%% A concept can have different HyperTrees. Therefore, depending on the different HyperTrees
  151%%% of c1 and c2 involved in the computation, different similarity values are obtained:
  152%%%
  153%%% sim_WUP(c1,c2)= 2*depth(lcs(c1,c2)) / (Depth(c1)+Depth(c2))
  154%%%
  155%%% This predicate combines all HyperTrees of c1 and c2, computes the respective similarity
  156%%% values and returns the maximum (the task is done by the auxiliary predicate max_wup/3).
  157%%%
  158%%% NOTE: "Word1:SS_type1:W1_Sense_num" denotes the concept c1 and "Word2:SS_type2:W2_Sense_num"
  159%%%       the concept c2. Note that we do not explicitly require information about
  160%%%       the synset type and sense number of a word.
  161%%%
  162%%%       We check that both Word1 and Word2 are nouns or verbs but not combinations of them.
  163%%%
  164
  165wn_wup(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree) :-
  166((nonvar(Word1), nonvar(Word2)) ->
  167%  (lists:member((SS_type1,SS_type2), [(n,n), (v,v)]) ->
  168  (lists:member((SS_type1,SS_type2), [(n,n), (v,v)]),
  169    (var(W1_Sense_num) ->
  170        wn_max_wordnet_sense(Word1, SS_type1, W1MaxSense),
  172        between(1, W1MaxSense, W1_Sense_num),
  173        (var(W2_Sense_num) ->
  174            wn_max_wordnet_sense(Word2, SS_type2, W2MaxSense),
  176            between(1, W2MaxSense, W2_Sense_num),
  177            max_wup(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  178            ;
  179            max_wup(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  180        )
  181        ;
  182        (var(W2_Sense_num) ->
  183            wn_max_wordnet_sense(Word2, SS_type2, W2MaxSense),
  185            between(1, W2MaxSense, W2_Sense_num),
  186            max_wup(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  187            ;
  188            max_wup(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  189        )
  190    )
  191    ;
  192    write("ERROR: Both Word1 and Word2 must be either nouns or verbs (but not combinations of them or adjectives)"),
  193    nl
  194  )
  195  ;
  196  write("ERROR: Word1 or Word2 is a variable. You must enter a specific word (either noun or verb)."),
  197  nl
  198)
  198.
  199
  200
  201%%%%%%%%%%%%%%%%%%%
  202%%% wup(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  203%%% Nondeterministic predicate. It inspects a pair of HyperTrees associated to
  204%%% c1 and c2 and obtains the degree of similarity between c1 and c2
  205%%% (according to that pair of HyperTrees)
  206%%%
  207%%% The degree of similarity obtained depends on the HyperTrees of c1 and c2 involved
  208%%% in the computation.
  209%%%
  210%%%     sim_WUP(c1,c2)= 2*depth(lcs(c1,c2)) / (Depth(c1)+Depth(c2))
  211%%%
  212%%%
  213wup(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  214    lcs(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, _, LCS_depth, DepthW1, DepthW2),
  215    Degree is (2 * LCS_depth / (DepthW1 + DepthW2)).
  216
  217
  218%%%%%%%%%%%%%%%%%%%
  219%%% max_wup(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  220%%% It obtains the degree of similarity between the concepts Word1:SS_type:W1_Sense_num
  221%%% and Word2:SS_type:W2_Sense_num using the WUP measure.
  222%%%
  223%%% A concept can have more than one HyperTree, therefore several pairs of HyperTrees
  224%%% are possibly considered and a list of similarity degrees 'Degs' is obtained using wup/3.
  225%%% Finally, the maximum degree in the list 'Degs' is selected as a result.
  226%%%
  227%%% NOTE: When this predicate is executed, it is intended that all variables in
  228%%%       Word1:SS_type:W1_Sense_num and in Word2:SS_type:W2_Sense_num are completely
  229%%%       instantiated.
  230%%%
  231max_wup(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  232    findall(Deg ,wup(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Deg), Degs),
  233    lists:max_list(Degs, Degree).
  234
  235
  236%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  237%%% wn_wup_nondet(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  238%%% Inspects a pair of HyperTrees associated to c1 and c2 and obtains the degree
  239%%% of similarity between c1 and c2 (according to that pair of HyperTrees)
  240%%%
  241%%% NOTE: Nondeterministic predicate. It is the user interface to the local predicate wup/3.
  242%%%
  243wn_wup_nondet(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  244 	( (SS_type=n; SS_type=v) ->
  245        wup(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree)
  246        ;
  247        write("ERROR: Both Word1 and Word2 must be nouns or verbs but not combinations of them"),
  248        nl
  249	).
  250
  251
  252%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  253%%% LCH SIMILARIRY MEASURE
  254%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  255%%% wn_lch(+Word1, +Word2, -Degree)
  256%%% This predicate implements the LCH similarity measure.
  257%%% Takes two concepts (terms -- Word:SS_type:Sense_num) and returns the degree of
  258%%% similarity between them. Note that we do not explicitly require information about
  259%%% the synset type and sense number of a word  (that can be variables).
  260%%%
  261%%% We check that both Word1 and Word2 are nouns or verbs but not combinations of them.
  262%%%
  263%%% sim_LCH (c1, c2) = −ln[ len(c1,c2) / (2 * max{depth(c)|c in WordNet})]
  264%%%
  265%%% where len(W1, W2) = (DepthW1-LCS_depth) + (DepthW2-LCS_depth) +1
  266%%% NOTE 1: max{depth(c)|c in WordNet} is the maximum depth of a concept in the WordNet
  267%%%         data base. In practice, is a fixed constant for each part of speech
  268%%%           MaxDepth(n) = 20    (Nouns)
  269%%%           MaxDepth(v) = 14    (Verbs)
  270%%%
  271%%% This predicate combines all HyperTrees of c1 and c2, computes the respective similarity
  272%%% values and returns the maximum (the task is done by the auxiliary predicate max_lch/3).
  273%%%
  274%%% NOTE 2: "Word1:SS_type1:W1_Sense_num" denotes the concept c1 and "Word2:SS_type2:W2_Sense_num"
  275%%%       the concept c2. Note that we do not explicitly require information about
  276%%%       the synset type and sense number of a word.
  277%%%
  278%%%       We check that both Word1 and Word2 are nouns or verbs but not combinations of them.
  279%%%
  280
  281wn_lch(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree) :-
  282((nonvar(Word1), nonvar(Word2)) ->
  283%  (lists:member((SS_type1,SS_type2), [(n,n), (v,v)]) ->
  284  (lists:member((SS_type1,SS_type2), [(n,n), (v,v)]),
  285    (var(W1_Sense_num) ->
  286        wn_max_wordnet_sense(Word1, SS_type1, W1MaxSense),
  288        between(1, W1MaxSense, W1_Sense_num),
  289        (var(W2_Sense_num) ->
  290            wn_max_wordnet_sense(Word2, SS_type2, W2MaxSense),
  292            between(1, W2MaxSense, W2_Sense_num),
  293            max_lch(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  294            ;
  295            max_lch(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  296        )
  297        ;
  298        (var(W2_Sense_num) ->
  299            wn_max_wordnet_sense(Word2, SS_type2, W2MaxSense),
  301            between(1, W2MaxSense, W2_Sense_num),
  302            max_lch(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  303            ;
  304            max_lch(Word1:SS_type1:W1_Sense_num, Word2:SS_type2:W2_Sense_num, Degree)
  305        )
  306    )
  307    ;
  308    write("ERROR: Both Word1 and Word2 must be either nouns or verbs (but not combinations of them or adjectives)"),
  309    nl
  310  )
  311  ;
  312  write("ERROR: Word1 or Word2 is a variable. You must enter a specific word (either noun or verb)."),
  313  nl
  314)
  314.
  315
  316
  317%%%%%%%%%%%%%%%%%%%
  318%%% lch(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  319%%% Nondeterministic predicate. It inspects a pair of HyperTrees associated to
  320%%% c1 and c2 and obtains the degree of similarity between c1 and c2
  321%%% (according to that pair of HyperTrees)
  322%%%
  323%%% The degree of similarity obtained depends on the HyperTrees of c1 and c2 involved
  324%%% in the computation.
  325%%%
  326%%% sim_LCH (c1, c2) = −ln[ len(c1,c2) / (2 * max{depth(c)|c in WordNet})]
  327%%%
  328%%% where len(W1, W2) = (DepthW1-LCS_depth) + (DepthW2-LCS_depth) +1
  329%%% NOTE 1: max{depth(c)|c in WordNet} is the maximum depth of a concept in the WordNet
  330%%%         data base. In practice, is a fixed constant for each part of speech
  331%%%           MaxDepth(n) = 20    (Nouns)
  332%%%           MaxDepth(v) = 14    (Verbs)
  333%%%
  334lch(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  335    lcs(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, _, LCS_depth, DepthW1, DepthW2),
  336    Len_W1_W2 is ((DepthW1-LCS_depth) + (DepthW2-LCS_depth) + 1),
  337    wn_maxDepth(SS_type, MaxDepth),
  338    Degree is ((-1) * log(Len_W1_W2 / (2 * MaxDepth))).
  339
  340%%%%%%%%%%%%%%%%%%%
  341%%% max_lch(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  342%%% It obtains the degree of similarity between the concepts Word1:SS_type:W1_Sense_num 
  343%%% and Word2:SS_type:W2_Sense_num using the LCH measure.
  344%%%
  345%%% A concept can have more than one HyperTree, therefore several pairs of HyperTrees
  346%%% are possibly considered and a list of similarity degrees 'Degs' is obtained using lch/3.
  347%%% Finally, the maximum degree in the list 'Degs' is selected as a result.
  348%%%
  349%%% NOTE: When this predicate is executed, it is intended that all variables in
  350%%%       Word1:SS_type:W1_Sense_num and in Word2:SS_type:W2_Sense_num are completely
  351%%%       instantiated.
  352%%%
  353max_lch(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  354	findall(Deg ,lch(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Deg), Degs),
  355	lists:max_list(Degs, Degree).
  356
  357
  358%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  359%%% wn_lch_nondet(+Word1:SS_type:W1_Sense_num, +Word2:SS_type:W2_Sense_num, -Degree)
  360%%% Inspects a pair of HyperTrees associated to c1 and c2 and obtains the degree
  361%%% of similarity between c1 and c2 (according to that pair of HyperTrees)
  362%%%
  363%%% NOTE: Nondeterministic predicate. It is the user interface to the local predicate lch/3.
  364%%%
  365wn_lch_nondet(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree) :-
  366	( (SS_type=n; SS_type=v) ->
  367		lch(Word1:SS_type:W1_Sense_num, Word2:SS_type:W2_Sense_num, Degree)
  368		;
  369		write("Both Word1 and Word2 must be nouns or verbs but not combinations of them"),
  370		nl
  371	).
  372
  373%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  374%%% END OF MODULE MAIN PREDICATES
  375%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  376
  377
  378%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  379%%% PREDICATES FOR COMPUTING THE LESS COMMON SUBSUMER (LCS) OF TWO WORDS
  380%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  381%%%
  382%%% The following predicates are USEFUL FOR COMPUTING SIMILARITY MEASURES. They compute
  383%%% the Less Common Subsumer (LCS) of two words. For efficience reasons they also compute
  384%%% some counting quantities as the depth of the words from the root of a HyperTree.
  385%%%
  386%%% They extend / speciallize predicates from the module wn_hypernyms.pl
  387%%%
  388%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  389%%% lcs(+Word1, +Word2, -LCS, -LCS_depth, -DepthW1, -DepthW2)
  390%%% Returns the Less Common Subsumer LCS of two words and its depth LCS_depth from the
  391%%% root of the HyperTree
  392%%%
  393%%% This predicate, additionally, returns the depth of Word1 and Word2 by efficiency
  394%%% reasons. We want to go through the hyperonym lists only once, so we calculate these
  395%%% quantities at the same time we calculate the LCS.
  396%%%
  397%%% NOTE 1:
  398%%% This predicate is nondeterministic.
  399%%% It can be used without specifying the Type and Sense of a Word, but in this case
  400%%% the LCS for all combinations of types and senses of these two words are obtained.
  401%%%
  402%%% If you want to obtain the LCS for two precise concepts introduce Word1:W1_Type:W1_Sense
  403%%% and Word2:W2_Type:W2_Sense
  404%%%
  405lcs(Word1, Word2, LCS, LCS_depth, DepthW1, DepthW2) :-
  406    wn_hypernyms(Word1, verbose(no), List_HyperNymSynSets1),
  407    wn_hypernyms(Word2, verbose(no), List_HyperNymSynSets2),
  408    head(List_HyperNymSynSets1, H_SynSet_ID),
  409    wn_virtual_root(H_SynSet_ID, Root),
  410    find_lcs([Root|List_HyperNymSynSets1], [Root|List_HyperNymSynSets2], LCS, LCS_depth, DepthW1, DepthW2).
  411
  412head([H|_], H).
  413
  414%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  415%%% find_lcs(+List_HyperNymSynSets1, +List_HyperNymSynSets2, -LCS, -LCS_depth, -DepthW1, -DepthW2)
  416%%%
  417%%% List_HyperNymSynSets1 and List_HyperNymSynSets2 are lists of synset_IDs which are the hypernyms
  418%%% of the the concepts (associated to the words) W1 and W2.
  419%%% LCS is the less common subsumer (a specific synset_ID).
  420%%% LCS_depth is the depth of LCS, that is its length from the root of the HyperTree to the LCS.
  421%%% DepthW1 and DepthW2 are the depth of the concepts (associated to the words) W1 and W2.
  422%%%
  423%%% INITIALIZATION:
  424%%% LCS is initialized to zero (a virtual synset_ID).
  425%%% LCS_depth is initialized to 0 in order to consider the effect of adding a virtual root synset.
  426%%%
  427
  428find_lcs(L_SynSets1, L_SynSets2, LCS, LCS_depth, DepthW1, DepthW2) :-
  429    find_lcs(L_SynSets1, L_SynSets2, 0, 0, LCS, LCS_depth, DepthW1, DepthW2).
  430
  431
  432%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  433%%% find_lcs(+L_SynSets1, +L_SynSets2, +LCS_Acc, +LCS_depth_Acc, -LCS, -LCS_depth, -DepthW1, -DepthW2).
  434%%%
  435%%% Compares two lists of (HyperNym) SynSets, element by element, until a mismatch is
  436%%% found. Then, the LCS and its depth (which where accumulated) are returned.
  437%%%
  438%%% LCS_Acc and LCS_depth_Acc accumulate the last synset inspected and its depth respectively.
  439%%% Initially LCS_Acc=0 (a virtual root synset) and LCS_depth_Acc=0 (the depth of the virtual root 0).
  440%%%
  441
  442find_lcs([], L_SynSets2, LCS_Acc, LCS_depth_Acc, LCS_Acc, LCS_depth_Acc, DepthW1, DepthW2):-
  443    !,
  444    DepthW1 = LCS_depth_Acc,
  445    length(L_SynSets2, Length_L_SynSets2),
  446    DepthW2 is LCS_depth_Acc + Length_L_SynSets2.
  447
  448find_lcs(L_SynSets1, [], LCS_Acc, LCS_depth_Acc, LCS_Acc, LCS_depth_Acc, DepthW1, DepthW2):-
  449    !,
  450    length(L_SynSets1, Length_L_SynSets1),
  451    DepthW1 is LCS_depth_Acc + Length_L_SynSets1,
  452    DepthW2 = LCS_depth_Acc.
  453
  454find_lcs([SS1|L_SynSets1], [SS2|L_SynSets2], _, LCS_depth_Acc, LCS, LCS_depth, DepthW1, DepthW2) :-
  455    SS1=:=SS2, !,
  456    New_LCS_depth_Acc is LCS_depth_Acc +1,
  457    find_lcs(L_SynSets1, L_SynSets2, SS1, New_LCS_depth_Acc, LCS, LCS_depth, DepthW1, DepthW2).
  458
  459find_lcs(L_SynSets1, L_SynSets2, LCS_Acc, LCS_depth_Acc, LCS_Acc, LCS_depth_Acc, DepthW1, DepthW2):-
  460    length(L_SynSets1, Length_L_SynSets1),
  461    DepthW1 is LCS_depth_Acc + Length_L_SynSets1,
  462    length(L_SynSets2, Length_L_SynSets2),
  463    DepthW2 is LCS_depth_Acc + Length_L_SynSets2