1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2013, Attempto Group, University of Zurich (see http://attempto.ifi.uzh.ch).
    3%
    4% The Attempto Parsing Engine (APE) is free software: you can redistribute it and/or modify it
    5% under the terms of the GNU Lesser General Public License as published by the Free Software
    6% Foundation, either version 3 of the License, or (at your option) any later version.
    7%
    8% The Attempto Parsing Engine (APE) is distributed in the hope that it will be useful, but WITHOUT
    9% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
   10% PURPOSE. See the GNU Lesser General Public License for more details.
   11%
   12% You should have received a copy of the GNU Lesser General Public License along with the Attempto
   13% Parsing Engine (APE). If not, see http://www.gnu.org/licenses/.
   14
   15
   16:- module(ulex, [
   17		read_ulex/1,            % +LexiconStream
   18		add_lexicon_entries/1,  % +LexEntryList
   19		add_lexicon_entry/1,    % +LexEntry
   20		discard_ulex/0
   21	]).   22
   23:- use_module(functionwords).   24:- use_module('../logger/error_logger').

User Lexicon Interface

This module contains the predicates for the dynamic management of the user lexicon that is not compiled into the executable.

author
- Tobias Kuhn
version
- 2009-11-18 */
   36% The predicates for the lexicon entries are declared dynamic.
   37
   38:- dynamic adv/2.   39:- dynamic adv_comp/2.   40:- dynamic adv_sup/2.   41:- dynamic adj_itr/2.   42:- dynamic adj_itr_comp/2.   43:- dynamic adj_itr_sup/2.   44:- dynamic adj_tr/3.   45:- dynamic adj_tr_comp/3.   46:- dynamic adj_tr_sup/3.   47:- dynamic noun_sg/3.   48:- dynamic noun_pl/3.   49:- dynamic noun_mass/3.   50:- dynamic mn_sg/2.   51:- dynamic mn_pl/2.   52:- dynamic pn_sg/3.   53:- dynamic pn_pl/3.   54:- dynamic pndef_sg/3.   55:- dynamic pndef_pl/3.   56:- dynamic iv_finsg/2.   57:- dynamic iv_infpl/2.   58:- dynamic tv_finsg/2.   59:- dynamic tv_infpl/2.   60:- dynamic tv_pp/2.   61:- dynamic dv_finsg/3.   62:- dynamic dv_infpl/3.   63:- dynamic dv_pp/3.   64:- dynamic prep/2.
 read_ulex(+LexiconStream)
Reads a lexicon file as a stream and loads all the contained entries.
   71read_ulex(LexiconStream) :-
   72	catch(
   73		(
   74			read_lexicon_entries(LexiconStream)
   75		),
   76		_CatchType,
   77		(
   78			line_count(LexiconStream, MalformedLineNum),
   79			with_output_to(atom(Message), format("The user lexicon file is not a valid Prolog file. Check line ~d", [MalformedLineNum])),
   80			add_error_message_once(lexicon, '', 'Malformed file.', Message)
   81		)
   82	), !.
   83read_ulex(_).
 read_lexicon_entries(+Stream)
Loads the lexicon entries reading from the stream.
   90read_lexicon_entries(Stream) :-
   91    read(Stream, LexEntry),
   92    ( LexEntry == end_of_file ->
   93	true
   94    ;
   95	add_lexicon_entry(LexEntry),
   96	read_lexicon_entries(Stream)
   97    ).
 add_lexicon_entries(+LexEntryList)
Arguments:
LexEntryList-

Adds all the lexicon entries of the list to the dynamic lexicon.

  106add_lexicon_entries([]).
  107
  108add_lexicon_entries([LexEntry|Rest]) :-
  109    add_lexicon_entry(LexEntry),
  110    add_lexicon_entries(Rest).
 add_lexicon_entry(+LexEntry)
Arguments:
LexEntry-

Adds the lexicon entry to the dynamic lexicon.

  119add_lexicon_entry(LexEntry) :-
  120    ground(LexEntry),
  121	lexicon_template(LexEntry),
  122	!,
  123    check_intersections(LexEntry),
  124    assert(LexEntry).
  125
  126add_lexicon_entry(LexEntry) :-
  127	with_output_to(atom(Message), format("User lexicon entry is malformed: ~w", [LexEntry])),
  128	add_error_message_once(lexicon, '', 'Malformed entry.', Message).
 discard_ulex
Discards all the lexicon entries.
  135discard_ulex :-
  136    lexicon_template(LexiconTemplate),
  137    retractall(LexiconTemplate),
  138    fail.
  139
  140discard_ulex.
 lexicon_template(+LexiconTemplate)
  146lexicon_template(adv(_, _)).
  147lexicon_template(adv_comp(_, _)).
  148lexicon_template(adv_sup(_, _)).
  149lexicon_template(adj_itr(_, _)).
  150lexicon_template(adj_itr_comp(_, _)).
  151lexicon_template(adj_itr_sup(_, _)).
  152lexicon_template(adj_tr(_, _, _)).
  153lexicon_template(adj_tr_comp(_, _, _)).
  154lexicon_template(adj_tr_sup(_, _, _)).
  155lexicon_template(noun_sg(_, _, _)).
  156lexicon_template(noun_pl(_, _, _)).
  157lexicon_template(noun_mass(_, _, _)).
  158lexicon_template(mn_sg(_, _)).
  159lexicon_template(mn_pl(_, _)).
  160lexicon_template(pn_sg(_, _, _)).
  161lexicon_template(pn_pl(_, _, _)).
  162lexicon_template(pndef_sg(_, _, _)).
  163lexicon_template(pndef_pl(_, _, _)).
  164lexicon_template(iv_finsg(_, _)).
  165lexicon_template(iv_infpl(_, _)).
  166lexicon_template(tv_finsg(_, _)).
  167lexicon_template(tv_infpl(_, _)).
  168lexicon_template(tv_pp(_, _)).
  169lexicon_template(dv_finsg(_, _, _)).
  170lexicon_template(dv_infpl(_, _, _)).
  171lexicon_template(dv_pp(_, _, _)).
  172lexicon_template(prep(_, _)).
 check_intersection(+Entry)
Checks if the new entry leads to a conflict. There is a conflict if
  182check_intersections(Entry) :-
  183    Entry =.. [_,Word|_],
  184    unredefinable_fw(Word),
  185    add_warning_message(lexicon, '', Word, 'This function word should not be redefined in the user lexicon.').
  186
  187check_intersections(adv(Word,_)) :-
  188    ( adv(Word,_) ; adv_comp(Word,_) ; adv_sup(Word,_) ),
  189    add_warning_message(lexicon, '', Word, 'This adverb is defined twice.').
  190
  191check_intersections(adv_comp(Word,_)) :-
  192    ( adv(Word,_) ; adv_comp(Word,_) ; adv_sup(Word,_) ),
  193    add_warning_message(lexicon, '', Word, 'This adverb is defined twice.').
  194
  195check_intersections(adv_sup(Word,_)) :-
  196    ( adv(Word,_) ; adv_comp(Word,_) ; adv_sup(Word,_) ),
  197    add_warning_message(lexicon, '', Word, 'This adverb is defined twice.').
  198
  199check_intersections(adj_itr(Word,_)) :-
  200    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  201    add_warning_message(lexicon, '', Word, 'This intransitive adjective is defined twice.').
  202
  203check_intersections(adj_itr_comp(Word,_)) :-
  204    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  205    add_warning_message(lexicon, '', Word, 'This intransitive adjective is defined twice.').
  206
  207check_intersections(adj_itr_sup(Word,_)) :-
  208    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  209    add_warning_message(lexicon, '', Word, 'This intransitive adjective is defined twice.').
  210
  211check_intersections(adj_tr(Word,_,_)) :-
  212    ( adj_tr(Word,_,_) ; adj_tr_comp(Word,_,_) ; adj_tr_sup(Word,_,_) ),
  213    add_warning_message(lexicon, '', Word, 'This transitive adjective is defined twice.').
  214
  215check_intersections(adj_tr_comp(Word,_,_)) :-
  216    ( adj_tr(Word,_,_) ; adj_tr_comp(Word,_,_) ; adj_tr_sup(Word,_,_) ),
  217    add_warning_message(lexicon, '', Word, 'This transitive adjective is defined twice.').
  218
  219check_intersections(adj_tr_sup(Word,_,_)) :-
  220    ( adj_tr(Word,_,_) ; adj_tr_comp(Word,_,_) ; adj_tr_sup(Word,_,_) ),
  221    add_warning_message(lexicon, '', Word, 'This transitive adjective is defined twice.').
  222
  223check_intersections(noun_sg(Word,_,_)) :-
  224    noun_sg(Word,_,_),
  225    add_warning_message(lexicon, '', Word, 'This singular noun is defined twice.').
  226
  227check_intersections(noun_pl(Word,_,_)) :-
  228    noun_pl(Word,_,_),
  229    add_warning_message(lexicon, '', Word, 'This plural noun is defined twice.').
  230
  231check_intersections(noun_mass(Word,_,_)) :-
  232    noun_mass(Word,_,_),
  233    add_warning_message(lexicon, '', Word, 'This mass noun is defined twice.').
  234
  235check_intersections(mn_sg(Word,_)) :-
  236    mn_sg(Word,_),
  237    add_warning_message(lexicon, '', Word, 'This singular measurement noun is defined twice.').
  238
  239check_intersections(mn_pl(Word,_)) :-
  240    mn_pl(Word,_),
  241    add_warning_message(lexicon, '', Word, 'This plural measurement noun is defined twice.').
  242
  243check_intersections(pn_sg(Word,_,_)) :-
  244    ( pn_sg(Word,_,_) ; pn_pl(Word,_,_) ),
  245    add_warning_message(lexicon, '', Word, 'This proper name is defined twice.').
  246
  247check_intersections(pn_pl(Word,_,_)) :-
  248    ( pn_sg(Word,_,_) ; pn_pl(Word,_,_) ),
  249    add_warning_message(lexicon, '', Word, 'This proper name is defined twice.').
  250
  251check_intersections(pndef_sg(Word,_,_)) :-
  252    ( pndef_sg(Word,_,_) ; pndef_pl(Word,_,_) ),
  253    add_warning_message(lexicon, '', Word, 'This proper name is defined twice.').
  254
  255check_intersections(pndef_pl(Word,_,_)) :-
  256    ( pndef_sg(Word,_,_) ; pndef_pl(Word,_,_) ),
  257    add_warning_message(lexicon, '', Word, 'This proper name is defined twice.').
  258
  259check_intersections(iv_finsg(Word,_)) :-
  260    iv_finsg(Word,_),
  261    add_warning_message(lexicon, '', Word, 'This singular form of an intransitive verb is defined twice.').
  262
  263check_intersections(iv_infpl(Word,_)) :-
  264    iv_infpl(Word,_),
  265    add_warning_message(lexicon, '', Word, 'This plural form of an intransitive verb is defined twice.').
  266
  267check_intersections(tv_finsg(Word,_)) :-
  268    tv_finsg(Word,_),
  269    add_warning_message(lexicon, '', Word, 'This singular form of a transitive verb is defined twice.').
  270
  271check_intersections(tv_infpl(Word,_)) :-
  272    tv_infpl(Word,_),
  273    add_warning_message(lexicon, '', Word, 'This plural form of a transitive verb is defined twice.').
  274
  275check_intersections(tv_pp(Word,_)) :-
  276    tv_pp(Word,_),
  277    add_warning_message(lexicon, '', Word, 'This past participle form of a transitive verb is defined twice.').
  278
  279check_intersections(dv_finsg(Word,_,'')) :-
  280    dv_finsg(Word,_,''),
  281    add_warning_message(lexicon, '', Word, 'This singular form of a ditransitive verb is defined twice.').
  282
  283check_intersections(dv_infpl(Word,_,'')) :-
  284    dv_infpl(Word,_,''),
  285    add_warning_message(lexicon, '', Word, 'This plural form of a ditransitive verb is defined twice.').
  286
  287check_intersections(dv_pp(Word,_,'')) :-
  288    dv_pp(Word,_,''),
  289    add_warning_message(lexicon, '', Word, 'This past participle form of a ditransitive verb is defined twice.').
  290
  291check_intersections(dv_finsg(Word,_,Prep)) :-
  292    dv_finsg(Word,_,Prep),
  293    Prep \== '',
  294    add_warning_message(lexicon, '', Word, 'This singular form of a ditransitive verb is defined twice.').
  295
  296check_intersections(dv_infpl(Word,_,Prep)) :-
  297    dv_infpl(Word,_,Prep),
  298    Prep \== '',
  299    add_warning_message(lexicon, '', Word, 'This plural form of a ditransitive verb is defined twice.').
  300
  301check_intersections(dv_pp(Word,_,Prep)) :-
  302    dv_pp(Word,_,Prep),
  303    Prep \== '',
  304    add_warning_message(lexicon, '', Word, 'This past participle form of a ditransitive verb is defined twice.').
  305
  306check_intersections(prep(Word,_)) :-
  307    prep(Word,_),
  308    add_warning_message(lexicon, '', Word, 'This preposition is defined twice.').
  309
  310check_intersections(adv(Word,_)) :-
  311    noun_sg(Word,_,_),
  312    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and singular noun.').
  313
  314check_intersections(noun_sg(Word,_,_)) :-
  315    adv(Word,_),
  316    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and singular noun.').
  317
  318check_intersections(adv(Word,_)) :-
  319    noun_pl(Word,_,_),
  320    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and plural noun.').
  321
  322check_intersections(noun_pl(Word,_,_)) :-
  323    adv(Word,_),
  324    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and plural noun.').
  325
  326check_intersections(adv(Word,_)) :-
  327    noun_mass(Word,_,_),
  328    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and mass noun.').
  329
  330check_intersections(noun_mass(Word,_,_)) :-
  331    adv(Word,_),
  332    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and mass noun.').
  333
  334check_intersections(adv(Word,_)) :-
  335    iv_finsg(Word,_),
  336    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and singular intransitive verb.').
  337
  338check_intersections(iv_finsg(Word,_)) :-
  339    adv(Word,_),
  340    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and singular intransitive verb.').
  341
  342check_intersections(adv(Word,_)) :-
  343    iv_infpl(Word,_),
  344    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and plural intransitive verb.').
  345
  346check_intersections(iv_infpl(Word,_)) :-
  347    adv(Word,_),
  348    add_warning_message(lexicon, '', Word, 'Bad intersection: adverb and plural intransitive verb.').
  349
  350check_intersections(adj_itr(Word,_)) :-
  351    ( adj_tr(Word,_,_) ; adj_tr_comp(Word,_,_); adj_tr_sup(Word,_,_) ),
  352    add_warning_message(lexicon, '', Word, 'Bad intersection: intransitive adjective and transitive adjective.').
  353
  354check_intersections(adj_itr_comp(Word,_)) :-
  355    ( adj_tr(Word,_,_) ; adj_tr_comp(Word,_,_); adj_tr_sup(Word,_,_) ),
  356    add_warning_message(lexicon, '', Word, 'Bad intersection: intransitive adjective and transitive adjective.').
  357
  358check_intersections(adj_itr_sup(Word,_)) :-
  359    ( adj_tr(Word,_,_) ; adj_tr_comp(Word,_,_); adj_tr_sup(Word,_,_) ),
  360    add_warning_message(lexicon, '', Word, 'Bad intersection: intransitive adjective and transitive adjective.').
  361
  362check_intersections(adj_tr(Word,_,_)) :-
  363    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  364    add_warning_message(lexicon, '', Word, 'Bad intersection: intransitive adjective and transitive adjective.').
  365
  366check_intersections(adj_tr_comp(Word,_,_)) :-
  367    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  368    add_warning_message(lexicon, '', Word, 'Bad intersection: intransitive adjective and transitive adjective.').
  369
  370check_intersections(adj_tr_sup(Word,_,_)) :-
  371    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  372    add_warning_message(lexicon, '', Word, 'Bad intersection: intransitive adjective and transitive adjective.').
  373
  374check_intersections(prep(Word,_)) :-
  375    ( adj_itr(Word,_) ; adj_itr_comp(Word,_) ; adj_itr_sup(Word,_) ),
  376    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and intransitive adjective.').
  377
  378check_intersections(adj_itr(Word,_)) :-
  379    prep(Word,_),
  380    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and intransitive adjective.').
  381
  382check_intersections(adj_itr_comp(Word,_)) :-
  383    prep(Word,_),
  384    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and intransitive adjective.').
  385
  386check_intersections(adj_itr_sup(Word,_)) :-
  387    prep(Word,_),
  388    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and intransitive adjective.').
  389
  390check_intersections(prep(Word,_)) :-
  391    ( tv_finsg(Word,_) ; tv_infpl(Word,_) ),
  392    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and transitive verb.').
  393
  394check_intersections(tv_finsg(Word,_)) :-
  395    prep(Word,_),
  396    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and transitive verb.').
  397
  398check_intersections(tv_infpl(Word,_)) :-
  399    prep(Word,_),
  400    add_warning_message(lexicon, '', Word, 'Bad intersection: preposition and transitive verb.').
  401
  402check_intersections(pndef_sg(Word,_,_)) :-
  403    ( noun_sg(Word,_,_) ; noun_pl(Word,_,_) ; noun_mass(Word,_,_) ),
  404    add_warning_message(lexicon, '', Word, 'Bad intersection: proper name with definite article and noun.').
  405
  406check_intersections(pndef_pl(Word,_,_)) :-
  407    ( noun_sg(Word,_,_) ; noun_pl(Word,_,_) ; noun_mass(Word,_,_) ),
  408    add_warning_message(lexicon, '', Word, 'Bad intersection: proper name with definite article and noun.').
  409
  410check_intersections(_).
  411
  412
  413unredefinable_fw(null).
  414unredefinable_fw(zero).
  415unredefinable_fw(one).
  416unredefinable_fw(two).
  417unredefinable_fw(three).
  418unredefinable_fw(four).
  419unredefinable_fw(five).
  420unredefinable_fw(six).
  421unredefinable_fw(seven).
  422unredefinable_fw(eight).
  423unredefinable_fw(nine).
  424unredefinable_fw(ten).
  425unredefinable_fw(eleven).
  426unredefinable_fw(twelve).
  427unredefinable_fw(dozen).
  428unredefinable_fw('Null').
  429unredefinable_fw('Zero').
  430unredefinable_fw('One').
  431unredefinable_fw('Two').
  432unredefinable_fw('Three').
  433unredefinable_fw('Four').
  434unredefinable_fw('Five').
  435unredefinable_fw('Six').
  436unredefinable_fw('Seven').
  437unredefinable_fw('Eight').
  438unredefinable_fw('Nine').
  439unredefinable_fw('Ten').
  440unredefinable_fw('Eleven').
  441unredefinable_fw('Twelve').
  442unredefinable_fw('Dozen').
  443unredefinable_fw('There').
  444unredefinable_fw(there).
  445unredefinable_fw(and).
  446unredefinable_fw(or).
  447unredefinable_fw(not).
  448unredefinable_fw(that).
  449unredefinable_fw(than).
  450unredefinable_fw(of).
  451unredefinable_fw('If').
  452unredefinable_fw(if).
  453unredefinable_fw(then).
  454unredefinable_fw(such).
  455unredefinable_fw(be).
  456unredefinable_fw(provably).
  457unredefinable_fw(more).
  458unredefinable_fw(most).
  459unredefinable_fw(least).
  460unredefinable_fw(less).
  461unredefinable_fw(are).
  462unredefinable_fw('Are').
  463unredefinable_fw(is).
  464unredefinable_fw('Is').
  465unredefinable_fw(the).
  466unredefinable_fw('The').
  467unredefinable_fw(a).
  468unredefinable_fw('A').
  469unredefinable_fw(an).
  470unredefinable_fw('An').
  471unredefinable_fw(some).
  472unredefinable_fw('Some').
  473unredefinable_fw(no).
  474unredefinable_fw('No').
  475unredefinable_fw(every).
  476unredefinable_fw('Every').
  477unredefinable_fw(all).
  478unredefinable_fw('All').
  479unredefinable_fw(each).
  480unredefinable_fw('Each').
  481unredefinable_fw(which).
  482unredefinable_fw('Which').
  483unredefinable_fw(its).
  484unredefinable_fw('Its').
  485unredefinable_fw(his).
  486unredefinable_fw('His').
  487unredefinable_fw(her).
  488unredefinable_fw('Her').
  489unredefinable_fw(their).
  490unredefinable_fw('Their').
  491unredefinable_fw(whose).
  492unredefinable_fw('Whose').
  493unredefinable_fw(it).
  494unredefinable_fw('It').
  495unredefinable_fw(he).
  496unredefinable_fw('He').
  497unredefinable_fw(she).
  498unredefinable_fw('She').
  499unredefinable_fw(they).
  500unredefinable_fw('They').
  501unredefinable_fw(him).
  502unredefinable_fw(them).
  503unredefinable_fw(itself).
  504unredefinable_fw(himself).
  505unredefinable_fw(herself).
  506unredefinable_fw(themselves).
  507unredefinable_fw(someone).
  508unredefinable_fw('Someone').
  509unredefinable_fw(somebody).
  510unredefinable_fw('Somebody').
  511unredefinable_fw(something).
  512unredefinable_fw('Something').
  513unredefinable_fw(nobody).
  514unredefinable_fw('Nobody').
  515unredefinable_fw(nothing).
  516unredefinable_fw('Nothing').
  517unredefinable_fw(everyone).
  518unredefinable_fw('Everyone').
  519unredefinable_fw(everybody).
  520unredefinable_fw('Everybody').
  521unredefinable_fw(everything).
  522unredefinable_fw('Everything').
  523unredefinable_fw(what).
  524unredefinable_fw('What').
  525unredefinable_fw(who).
  526unredefinable_fw('Who').
  527unredefinable_fw(how).
  528unredefinable_fw('How').
  529unredefinable_fw(where).
  530unredefinable_fw('Where').
  531unredefinable_fw(when).
  532unredefinable_fw('When').
  533unredefinable_fw(many).
  534unredefinable_fw(much)