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(functionwords, [
   17	functionword/1,
   18	variable/1,
   19	rawnumber_number/2,
   20	propername_prefix/2,
   21	noun_prefix/2,
   22	verb_prefix/1,
   23	modif_prefix/1
   24	]).

Function Words

This module stores the different kinds of function words.

author
- Kaarel Kaljurand
- Tobias Kuhn
version
- 2008-06-26 */
 functionword(?FunctionWord) is det
   39functionword(whose).
   40functionword(for).
   41functionword('There').
   42functionword(there).
   43functionword(and).
   44functionword(or).
   45functionword(not).
   46functionword(that).
   47functionword(than).
   48functionword(of).
   49functionword(s).
   50functionword('\'').
   51functionword('"').
   52functionword('/').
   53functionword('\\').
   54functionword('-').
   55functionword('+').
   56functionword('&').
   57functionword('*').
   58functionword('(').
   59functionword(')').
   60functionword('[').
   61functionword(']').
   62functionword('}').
   63functionword('{').
   64functionword('<').
   65functionword('=').
   66functionword('>').
   67functionword('.').
   68functionword('?').
   69functionword('!').
   70functionword(',').
   71functionword(':').
   72functionword('If').
   73functionword(if).
   74functionword(then).
   75functionword('such').
   76functionword('be').
   77functionword('isn').
   78functionword('aren').
   79functionword('doesn').
   80functionword('don').
   81functionword('provably').
   82functionword(more).
   83functionword(most).
   84functionword(least).
   85functionword(less).
   86functionword(but).
   87functionword(true).
   88functionword(false).
   89functionword(possible).
   90functionword(necessary).
   91functionword(recommended).
   92functionword(admissible).
   93functionword('-thing').
   94functionword('-body').
   95functionword('-one').
   96functionword('something').
   97functionword('somebody').
   98functionword('someone').
   99functionword('nothing').
  100functionword('nobody').
  101functionword('noone').
  102functionword('everything').
  103functionword('everybody').
  104functionword('everyone').
  105functionword('one').
  106functionword('A').
  107functionword('All').
  108functionword('An').
  109functionword('Are').
  110functionword('Can').
  111functionword('Do').
  112functionword('Does').
  113functionword('Each').
  114functionword('Every').
  115functionword('Exactly').
  116functionword('He').
  117functionword('Her').
  118functionword('His').
  119functionword('How').
  120functionword('Is').
  121functionword('It').
  122functionword('Its').
  123functionword('May').
  124functionword('Must').
  125functionword('No').
  126functionword('She').
  127functionword('Should').
  128functionword('Some').
  129functionword('The').
  130functionword('Their').
  131functionword('They').
  132functionword('What').
  133functionword('When').
  134functionword('Where').
  135functionword('Which').
  136functionword('Who').
  137functionword('Whose').
  138functionword(a).
  139functionword(all).
  140functionword(an).
  141functionword(are).
  142functionword(can).
  143functionword(do).
  144functionword(does).
  145functionword(each).
  146functionword(every).
  147functionword(exactly).
  148functionword(he).
  149functionword(her).
  150functionword(herself).
  151functionword(him).
  152functionword(himself).
  153functionword(his).
  154functionword(how).
  155functionword(is).
  156functionword(it).
  157functionword(its).
  158functionword(itself).
  159functionword(may).
  160functionword(must).
  161functionword(no).
  162functionword(she).
  163functionword(should).
  164functionword(some).
  165functionword(the).
  166functionword(their).
  167functionword(them).
  168functionword(themselves).
  169functionword(they).
  170functionword(what).
  171functionword(when).
  172functionword(where).
  173functionword(which).
  174functionword(who).
  175functionword(at).
  176functionword(by).
  177functionword(^).  % used interally to mark the beginning of a sentence
  178functionword('For').
  179functionword('At').
  180functionword('Less').
  181functionword('More').
  182functionword(you).
  183functionword('You').
  184functionword(your).
  185functionword('Your').
  186functionword(yourself).
  187functionword(yourselves).
  188functionword(to).  % e.g. "wants to"
  189functionword(own).  % e.g. "his own"
  190functionword(many).  % e.g. "how many"
  191functionword(much).  % e.g. "how much"
 variable(+Word) is det
  197variable(Word) :-
  198    atom(Word),
  199	atom_codes(Word, [First|Rest]),
  200	65 =< First,
  201	First =< 90,
  202	digits(Rest).
 digits(+String) is det
  208digits([]).
  209
  210digits([D|Rest]) :-
  211	48 =< D,
  212	D =< 57,
  213	digits(Rest).
 rawnumber_number(+RawNumber:term, -Number:integer) is det
Arguments:
RawNumber- is either an integer or an English word denoting a small positive integer
Number- is an integer

Only integers 0-12 are supported as words.

  223rawnumber_number(RawNumber, RawNumber) :-
  224	number(RawNumber).
  225
  226rawnumber_number(null, 0).
  227rawnumber_number(zero, 0).
  228rawnumber_number(one, 1).
  229rawnumber_number(two, 2).
  230rawnumber_number(three, 3).
  231rawnumber_number(four, 4).
  232rawnumber_number(five, 5).
  233rawnumber_number(six, 6).
  234rawnumber_number(seven, 7).
  235rawnumber_number(eight, 8).
  236rawnumber_number(nine, 9).
  237rawnumber_number(ten, 10).
  238rawnumber_number(eleven, 11).
  239rawnumber_number(twelve, 12).
  240rawnumber_number(dozen, 12).
  241
  242% Capitalized versions of the number words
  243% as numbers can also be used at the beginning of
  244% the sentences, e.g. 'Four men wait.'
  245rawnumber_number('Null', 0).
  246rawnumber_number('Zero', 0).
  247rawnumber_number('One', 1).
  248rawnumber_number('Two', 2).
  249rawnumber_number('Three', 3).
  250rawnumber_number('Four', 4).
  251rawnumber_number('Five', 5).
  252rawnumber_number('Six', 6).
  253rawnumber_number('Seven', 7).
  254rawnumber_number('Eight', 8).
  255rawnumber_number('Nine', 9).
  256rawnumber_number('Ten', 10).
  257rawnumber_number('Eleven', 11).
  258rawnumber_number('Twelve', 12).
  259rawnumber_number('Dozen', 12).
 propername_prefix(+Prefix:atom, +Gender:atom, +Type:atom) is det
 noun_prefix(+Prefix:atom, +Gender:atom, +Type:atom) is det
 verb_prefix(+Prefix:atom, +Type:atom) is det
 modif_prefix(+Prefix:atom) is det
Definition of prefixes. Support for words which are not in the lexicon. Undefined words have to start with a prefix (e.g. `n' or `v'), e.g.
A man v:backs-up the n:web-page of the n:pizza-delivery-service.

Notes:

  279propername_prefix(pn, neutr).
  280propername_prefix(human, human).
  281propername_prefix(masc, masc).
  282propername_prefix(fem, fem).
  283propername_prefix(p, neutr).
  284propername_prefix(h, human).
  285propername_prefix(m, masc).
  286propername_prefix(f, fem).
  287propername_prefix(unknowncat, neutr).
  288propername_prefix(unknowncat, human).
  289propername_prefix(unknowncat, masc).
  290propername_prefix(unknowncat, fem).
  291
  292noun_prefix(noun, neutr).
  293noun_prefix(human, human).
  294noun_prefix(masc, masc).
  295noun_prefix(fem, fem).
  296noun_prefix(n, neutr).
  297noun_prefix(h, human).
  298noun_prefix(m, masc).
  299noun_prefix(f, fem).
  300noun_prefix(unknowncat, neutr).
  301noun_prefix(unknowncat, human).
  302noun_prefix(unknowncat, masc).
  303noun_prefix(unknowncat, fem).
  304
  305verb_prefix(verb).
  306verb_prefix(v).
  307verb_prefix(unknowncat).
  308
  309modif_prefix(a).
  310modif_prefix(unknowncat)