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
   15adj_itr('grown-up', 'grown-up').
   16adj_itr(accepted, accepted).
   17adj_itr(active, active).
   18adj_itr(allowed, allowed).
   19adj_itr(angry, angry).
   20adj_itr(approximate, approximate).
   21adj_itr(associated, associated).
   22adj_itr(authenticated, authenticated).
   23adj_itr(automatic, automatic).
   24adj_itr(average, average).
   25adj_itr(bad, bad).
   26adj_itr(beat, beat).
   27adj_itr(big, big).
   28adj_itr(bitten, bitten).
   29adj_itr(blue, blue).
   30adj_itr(boiled, boiled).
   31adj_itr(bought, bought).
   32adj_itr(cancelled, cancelled).
   33adj_itr(cellular, cellular).
   34adj_itr(charged, charged).
   35adj_itr(clean, clean).
   36adj_itr(clever, clever).
   37adj_itr(cold, cold).
   38adj_itr(come, come).
   39adj_itr(considered, considered).
   40adj_itr(contained, contained).
   41adj_itr(content, content).
   42adj_itr(correct, correct).
   43adj_itr(criminal, criminal).
   44adj_itr(deep, deep).
   45adj_itr(dirty, dirty).
   46adj_itr(drinkable, drinkable).
   47adj_itr(empty, empty).
   48adj_itr(enormous, enormous).
   49adj_itr(entered, entered).
   50adj_itr(evil, evil).
   51adj_itr(expensive, expensive).
   52adj_itr(expired, expired).
   53adj_itr(fair, fair).
   54adj_itr(false, false).
   55adj_itr(famous, famous).
   56adj_itr(far, far).
   57adj_itr(fast, fast).
   58adj_itr(feared, feared).
   59adj_itr(feed, feed).
   60adj_itr(female, female).
   61adj_itr(flat, flat).
   62adj_itr(fly, fly).
   63adj_itr(given, given).
   64adj_itr(good, good).
   65adj_itr(great, great).
   66adj_itr(green, green).
   67adj_itr(happy, happy).
   68adj_itr(hard, hard).
   69adj_itr(hated, hated).
   70adj_itr(hit, hit).
   71adj_itr(human, human).
   72adj_itr(hungry, hungry).
   73adj_itr(important, important).
   74adj_itr(impossible, impossible).
   75adj_itr(interested, interested).
   76adj_itr(invalid, invalid).
   77adj_itr(known, known).
   78adj_itr(large, large).
   79adj_itr(liked, liked).
   80adj_itr(live, live).
   81adj_itr(living, living).
   82adj_itr(long, long).
   83adj_itr(lost, lost).
   84adj_itr(loved, loved).
   85adj_itr(mat, mat).
   86adj_itr(meet, meet).
   87adj_itr(natural, natural).
   88adj_itr(necessary, necessary).
   89adj_itr(new, new).
   90adj_itr(nice, nice).
   91adj_itr(numb, numb).
   92adj_itr(numeric, numeric).
   93adj_itr(old, old).
   94adj_itr(only, only).
   95adj_itr(open, open).
   96adj_itr(owned, owned).
   97adj_itr(permitted, permitted).
   98adj_itr(personal, personal).
   99adj_itr(provable, provable).
  100adj_itr(public, public).
  101adj_itr(quick, quick).
  102adj_itr(raw, raw).
  103adj_itr(read, read).
  104adj_itr(real, real).
  105adj_itr(red, red).
  106adj_itr(rich, rich).
  107adj_itr(run, run).
  108adj_itr(sad, sad).
  109adj_itr(seen, seen).
  110adj_itr(sent, sent).
  111adj_itr(set, set).
  112adj_itr(small, small).
  113adj_itr(smart, smart).
  114adj_itr(syntactic, syntactic).
  115adj_itr(taken, taken).
  116adj_itr(tall, tall).
  117adj_itr(tired, tired).
  118adj_itr(true, true).
  119adj_itr(unnecessary, unnecessary).
  120adj_itr(used, used).
  121adj_itr(valid, valid).
  122adj_itr(warm, warm).
  123adj_itr(wet, wet).
  124adj_itr(white, white).
  125adj_itr(written, written).
  126adj_itr(young, young).
  127adj_itr_comp(angrier, angry).
  128adj_itr_comp(better, good).
  129adj_itr_comp(bigger, big).
  130adj_itr_comp(bluer, blue).
  131adj_itr_comp(cleaner, clean).
  132adj_itr_comp(cleverer, clever).
  133adj_itr_comp(colder, cold).
  134adj_itr_comp(deeper, deep).
  135adj_itr_comp(dirtier, dirty).
  136adj_itr_comp(elder, old).
  137adj_itr_comp(fairer, fair).
  138adj_itr_comp(falser, false).
  139adj_itr_comp(farther, far).
  140adj_itr_comp(faster, fast).
  141adj_itr_comp(flier, fly).
  142adj_itr_comp(further, far).
  143adj_itr_comp(greater, great).
  144adj_itr_comp(greener, green).
  145adj_itr_comp(happier, happy).
  146adj_itr_comp(harder, hard).
  147adj_itr_comp(larger, large).
  148adj_itr_comp(longer, long).
  149adj_itr_comp(newer, new).
  150adj_itr_comp(nicer, nice).
  151adj_itr_comp(number, numb).
  152adj_itr_comp(older, old).
  153adj_itr_comp(redder, red).
  154adj_itr_comp(richer, rich).
  155adj_itr_comp(sadder, sad).
  156adj_itr_comp(smaller, small).
  157adj_itr_comp(smarter, smart).
  158adj_itr_comp(taller, tall).
  159adj_itr_comp(truer, true).
  160adj_itr_comp(warmer, warm).
  161adj_itr_comp(wetter, wet).
  162adj_itr_comp(whiter, white).
  163adj_itr_comp(worse, bad).
  164adj_itr_comp(younger, young).
  165adj_itr_sup(angriest, angry).
  166adj_itr_sup(best, good).
  167adj_itr_sup(biggest, big).
  168adj_itr_sup(bluest, blue).
  169adj_itr_sup(cleanest, clean).
  170adj_itr_sup(cleverest, clever).
  171adj_itr_sup(coldest, cold).
  172adj_itr_sup(deepest, deep).
  173adj_itr_sup(dirtiest, dirty).
  174adj_itr_sup(eldest, old).
  175adj_itr_sup(fairest, fair).
  176adj_itr_sup(falsest, false).
  177adj_itr_sup(farthest, far).
  178adj_itr_sup(fastest, fast).
  179adj_itr_sup(fliest, fly).
  180adj_itr_sup(furthest, far).
  181adj_itr_sup(greatest, great).
  182adj_itr_sup(greenest, green).
  183adj_itr_sup(happiest, happy).
  184adj_itr_sup(hardest, hard).
  185adj_itr_sup(largest, large).
  186adj_itr_sup(longest, long).
  187adj_itr_sup(newest, new).
  188adj_itr_sup(nicest, nice).
  189adj_itr_sup(numbest, numb).
  190adj_itr_sup(oldest, old).
  191adj_itr_sup(reddest, red).
  192adj_itr_sup(richest, rich).
  193adj_itr_sup(saddest, sad).
  194adj_itr_sup(smallest, small).
  195adj_itr_sup(smartest, smart).
  196adj_itr_sup(tallest, tall).
  197adj_itr_sup(truest, true).
  198adj_itr_sup(warmest, warm).
  199adj_itr_sup(wettest, wet).
  200adj_itr_sup(whitest, white).
  201adj_itr_sup(worst, bad).
  202adj_itr_sup(youngest, young).
  203adj_tr('fond-of', 'fond-of', of).
  204adj_tr('interested-in', 'interested-in', in).
  205adj_tr('mad-about', 'mad-about', about).
  206adj_tr_comp('fonder-of', 'fond-of', of).
  207adj_tr_comp('madder-about', 'mad-about', about).
  208adj_tr_sup('fondest-of', 'fond-of', of).
  209adj_tr_sup('maddest-about', 'mad-about', about).
  210adv('as-soon-as-possible', 'as-soon-as-possible').
  211adv(always, always).
  212adv(anon, anon).
  213adv(carefully, carefully).
  214adv(easily, easily).
  215adv(exactly, exactly).
  216adv(extremely, extremely).
  217adv(false, false).
  218adv(far, far).
  219adv(fast, fast).
  220adv(fitfully, fitfully).
  221adv(happily, happily).
  222adv(hard, hard).
  223adv(large, large).
  224adv(less, less).
  225adv(long, long).
  226adv(loudly, loudly).
  227adv(manually, manually).
  228adv(often, often).
  229adv(patiently, patiently).
  230adv(quickly, quickly).
  231adv(safely, safely).
  232adv(silently, silently).
  233adv(soundly, soundly).
  234adv(speedily, speedily).
  235adv(usually, usually).
  236adv(vaguely, vaguely).
  237adv(wisely, wisely).
  238adv_comp(deeper, deep).
  239adv_comp(farther, far).
  240adv_comp(faster, fast).
  241adv_comp(further, far).
  242adv_comp(harder, hard).
  243adv_comp(quicker, quick).
  244adv_comp(worse, bad).
  245adv_sup(deepest, deep).
  246adv_sup(farthest, far).
  247adv_sup(fastest, fast).
  248adv_sup(furthest, far).
  249adv_sup(hardest, hard).
  250adv_sup(quickest, quick).
  251adv_sup(worst, bad).
  252dv_finsg(allows, allow, '').
  253dv_finsg(assigns, assign, '').
  254dv_finsg(assigns, assign, to).
  255dv_finsg(brings, bring, '').
  256dv_finsg(buys, buy, '').
  257dv_finsg(charges, charge, '').
  258dv_finsg(delivers, deliver, '').
  259dv_finsg(drops, drop, '').
  260dv_finsg(feeds, feed, '').
  261dv_finsg(gets, get, '').
  262dv_finsg(gives, give, '').
  263dv_finsg(gives, give, to).
  264dv_finsg(hands, hand, '').
  265dv_finsg(loses, lose, '').
  266dv_finsg(mails, mail, '').
  267dv_finsg(offers, offer, '').
  268dv_finsg(offers, offer, to).
  269dv_finsg(pays, pay, '').
  270dv_finsg(pays, pay, to).
  271dv_finsg(permits, permit, '').
  272dv_finsg(reads, read, '').
  273dv_finsg(runs, run, as).
  274dv_finsg(sells, sell, '').
  275dv_finsg(sends, send, '').
  276dv_finsg(sends, send, to).
  277dv_finsg(serves, serve, '').
  278dv_finsg(serves, serve, to).
  279dv_finsg(succeeds, succeed, as).
  280dv_finsg(takes, take, '').
  281dv_finsg(tells, tell, '').
  282dv_finsg(wins, win, '').
  283dv_finsg(writes, write, '').
  284dv_infpl(allow, allow, '').
  285dv_infpl(assign, assign, '').
  286dv_infpl(assign, assign, to).
  287dv_infpl(bring, bring, '').
  288dv_infpl(buy, buy, '').
  289dv_infpl(charge, charge, '').
  290dv_infpl(deliver, deliver, '').
  291dv_infpl(drop, drop, '').
  292dv_infpl(feed, feed, '').
  293dv_infpl(get, get, '').
  294dv_infpl(give, give, '').
  295dv_infpl(give, give, to).
  296dv_infpl(hand, hand, '').
  297dv_infpl(lose, lose, '').
  298dv_infpl(mail, mail, '').
  299dv_infpl(offer, offer, '').
  300dv_infpl(offer, offer, to).
  301dv_infpl(pay, pay, '').
  302dv_infpl(pay, pay, to).
  303dv_infpl(permit, permit, '').
  304dv_infpl(read, read, '').
  305dv_infpl(run, run, as).
  306dv_infpl(sell, sell, '').
  307dv_infpl(send, send, '').
  308dv_infpl(send, send, to).
  309dv_infpl(serve, serve, '').
  310dv_infpl(serve, serve, to).
  311dv_infpl(succeed, succeed, as).
  312dv_infpl(take, take, '').
  313dv_infpl(tell, tell, '').
  314dv_infpl(win, win, '').
  315dv_infpl(write, write, '').
  316dv_pp(allowed, allow, '').
  317dv_pp(assigned, assign, '').
  318dv_pp(assigned, assign, to).
  319dv_pp(bought, buy, '').
  320dv_pp(brought, bring, '').
  321dv_pp(charged, charge, '').
  322dv_pp(delivered, deliver, '').
  323dv_pp(dropped, drop, '').
  324dv_pp(fed, feed, '').
  325dv_pp(feed, feed, '').
  326dv_pp(given, give, '').
  327dv_pp(given, give, to).
  328dv_pp(got, get, '').
  329dv_pp(gotten, get, '').
  330dv_pp(handed, hand, '').
  331dv_pp(lost, lose, '').
  332dv_pp(mailed, mail, '').
  333dv_pp(offered, offer, '').
  334dv_pp(offered, offer, to).
  335dv_pp(paid, pay, '').
  336dv_pp(paid, pay, to).
  337dv_pp(permitted, permit, '').
  338dv_pp(read, read, '').
  339dv_pp(run, run, as).
  340dv_pp(sent, send, '').
  341dv_pp(sent, send, to).
  342dv_pp(served, serve, '').
  343dv_pp(served, serve, to).
  344dv_pp(sold, sell, '').
  345dv_pp(succeeded, succeed, as).
  346dv_pp(taken, take, '').
  347dv_pp(told, tell, '').
  348dv_pp(won, win, '').
  349dv_pp(written, write, '').
  350iv_finsg('fills-in', 'fill-in').
  351iv_finsg(accepts, accept).
  352iv_finsg(ages, age).
  353iv_finsg(appears, appear).
  354iv_finsg(approaches, approach).
  355iv_finsg(approximates, approximate).
  356iv_finsg(arrives, arrive).
  357iv_finsg(awaits, await).
  358iv_finsg(balls, ball).
  359iv_finsg(banks, bank).
  360iv_finsg(barks, bark).
  361iv_finsg(beats, beat).
  362iv_finsg(belongs, belong).
  363iv_finsg(blinks, blink).
  364iv_finsg(blues, blue).
  365iv_finsg(boils, boil).
  366iv_finsg(bones, bone).
  367iv_finsg(books, book).
  368iv_finsg(boxes, box).
  369iv_finsg(buttons, button).
  370iv_finsg(cancels, cancel).
  371iv_finsg(carries, carry).
  372iv_finsg(charges, charge).
  373iv_finsg(checks, check).
  374iv_finsg(cleans, clean).
  375iv_finsg(collapses, collapse).
  376iv_finsg(comes, come).
  377iv_finsg(contracts, contract).
  378iv_finsg(counts, count).
  379iv_finsg(dances, dance).
  380iv_finsg(dates, date).
  381iv_finsg(drinks, drink).
  382iv_finsg(drives, drive).
  383iv_finsg(drops, drop).
  384iv_finsg(eases, ease).
  385iv_finsg(eats, eat).
  386iv_finsg(empties, empty).
  387iv_finsg(enters, enter).
  388iv_finsg(exists, exist).
  389iv_finsg(expires, expire).
  390iv_finsg(fasts, fast).
  391iv_finsg(fears, fear).
  392iv_finsg(feeds, feed).
  393iv_finsg(flies, fly).
  394iv_finsg(flowers, flower).
  395iv_finsg(flows, flow).
  396iv_finsg(forms, form).
  397iv_finsg(gardens, garden).
  398iv_finsg(gives, give).
  399iv_finsg(goes, go).
  400iv_finsg(grasses, grass).
  401iv_finsg(grates, grate).
  402iv_finsg(groups, group).
  403iv_finsg(happens, happen).
  404iv_finsg(hits, hit).
  405iv_finsg(holds, hold).
  406iv_finsg(hurries, hurry).
  407iv_finsg(keeps, keep).
  408iv_finsg(knows, know).
  409iv_finsg(lifts, lift).
  410iv_finsg(lives, live).
  411iv_finsg(looks, look).
  412iv_finsg(loses, lose).
  413iv_finsg(loves, love).
  414iv_finsg(lunches, lunch).
  415iv_finsg(mates, mate).
  416iv_finsg(mats, mat).
  417iv_finsg(meets, meet).
  418iv_finsg(mouses, mouse).
  419iv_finsg(moves, move).
  420iv_finsg(numbs, numb).
  421iv_finsg(objects, object).
  422iv_finsg(opens, open).
  423iv_finsg(parks, park).
  424iv_finsg(pays, pay).
  425iv_finsg(pets, pet).
  426iv_finsg(places, place).
  427iv_finsg(plays, play).
  428iv_finsg(points, point).
  429iv_finsg(rats, rat).
  430iv_finsg(reads, read).
  431iv_finsg(reasons, reason).
  432iv_finsg(referees, referee).
  433iv_finsg(rooms, room).
  434iv_finsg(rots, rot).
  435iv_finsg(runs, run).
  436iv_finsg(scores, score).
  437iv_finsg(sees, see).
  438iv_finsg(sells, sell).
  439iv_finsg(serves, serve).
  440iv_finsg(sets, set).
  441iv_finsg(signs, sign).
  442iv_finsg(sinks, sink).
  443iv_finsg(sits, sit).
  444iv_finsg(sleeps, sleep).
  445iv_finsg(smarts, smart).
  446iv_finsg(smells, smell).
  447iv_finsg(smiles, smile).
  448iv_finsg(snores, snore).
  449iv_finsg(softens, soften).
  450iv_finsg(speeds, speed).
  451iv_finsg(steals, steal).
  452iv_finsg(succeeds, succeed).
  453iv_finsg(sugars, sugar).
  454iv_finsg(surfaces, surface).
  455iv_finsg(takes, take).
  456iv_finsg(talks, talk).
  457iv_finsg(tires, tire).
  458iv_finsg(trains, train).
  459iv_finsg(tries, try).
  460iv_finsg(understands, understand).
  461iv_finsg(varies, vary).
  462iv_finsg(visits, visit).
  463iv_finsg(waits, wait).
  464iv_finsg(walks, walk).
  465iv_finsg(warms, warm).
  466iv_finsg(washes, wash).
  467iv_finsg(watches, watch).
  468iv_finsg(waters, water).
  469iv_finsg(wins, win).
  470iv_finsg(works, work).
  471iv_finsg(writes, write).
  472iv_infpl('fill-in', 'fill-in').
  473iv_infpl(accept, accept).
  474iv_infpl(age, age).
  475iv_infpl(appear, appear).
  476iv_infpl(approach, approach).
  477iv_infpl(approximate, approximate).
  478iv_infpl(arrive, arrive).
  479iv_infpl(await, await).
  480iv_infpl(ball, ball).
  481iv_infpl(bank, bank).
  482iv_infpl(bark, bark).
  483iv_infpl(beat, beat).
  484iv_infpl(belong, belong).
  485iv_infpl(blink, blink).
  486iv_infpl(blue, blue).
  487iv_infpl(boil, boil).
  488iv_infpl(bone, bone).
  489iv_infpl(book, book).
  490iv_infpl(box, box).
  491iv_infpl(button, button).
  492iv_infpl(cancel, cancel).
  493iv_infpl(carry, carry).
  494iv_infpl(charge, charge).
  495iv_infpl(check, check).
  496iv_infpl(clean, clean).
  497iv_infpl(collapse, collapse).
  498iv_infpl(come, come).
  499iv_infpl(contract, contract).
  500iv_infpl(count, count).
  501iv_infpl(dance, dance).
  502iv_infpl(date, date).
  503iv_infpl(drink, drink).
  504iv_infpl(drive, drive).
  505iv_infpl(drop, drop).
  506iv_infpl(ease, ease).
  507iv_infpl(eat, eat).
  508iv_infpl(empty, empty).
  509iv_infpl(enter, enter).
  510iv_infpl(exist, exist).
  511iv_infpl(expire, expire).
  512iv_infpl(fear, fear).
  513iv_infpl(feed, feed).
  514iv_infpl(flow, flow).
  515iv_infpl(flower, flower).
  516iv_infpl(fly, fly).
  517iv_infpl(form, form).
  518iv_infpl(garden, garden).
  519iv_infpl(give, give).
  520iv_infpl(go, go).
  521iv_infpl(grass, grass).
  522iv_infpl(grate, grate).
  523iv_infpl(group, group).
  524iv_infpl(happen, happen).
  525iv_infpl(hit, hit).
  526iv_infpl(hold, hold).
  527iv_infpl(hurry, hurry).
  528iv_infpl(keep, keep).
  529iv_infpl(know, know).
  530iv_infpl(lift, lift).
  531iv_infpl(live, live).
  532iv_infpl(look, look).
  533iv_infpl(lose, lose).
  534iv_infpl(love, love).
  535iv_infpl(lunch, lunch).
  536iv_infpl(mat, mat).
  537iv_infpl(mate, mate).
  538iv_infpl(meet, meet).
  539iv_infpl(mouse, mouse).
  540iv_infpl(move, move).
  541iv_infpl(numb, numb).
  542iv_infpl(object, object).
  543iv_infpl(open, open).
  544iv_infpl(park, park).
  545iv_infpl(pay, pay).
  546iv_infpl(pet, pet).
  547iv_infpl(place, place).
  548iv_infpl(play, play).
  549iv_infpl(point, point).
  550iv_infpl(rat, rat).
  551iv_infpl(read, read).
  552iv_infpl(reason, reason).
  553iv_infpl(referee, referee).
  554iv_infpl(room, room).
  555iv_infpl(rot, rot).
  556iv_infpl(run, run).
  557iv_infpl(score, score).
  558iv_infpl(see, see).
  559iv_infpl(sell, sell).
  560iv_infpl(serve, serve).
  561iv_infpl(set, set).
  562iv_infpl(sign, sign).
  563iv_infpl(sink, sink).
  564iv_infpl(sit, sit).
  565iv_infpl(sleep, sleep).
  566iv_infpl(smart, smart).
  567iv_infpl(smell, smell).
  568iv_infpl(smile, smile).
  569iv_infpl(snore, snore).
  570iv_infpl(soften, soften).
  571iv_infpl(speed, speed).
  572iv_infpl(steal, steal).
  573iv_infpl(succeed, succeed).
  574iv_infpl(sugar, sugar).
  575iv_infpl(surface, surface).
  576iv_infpl(take, take).
  577iv_infpl(talk, talk).
  578iv_infpl(tire, tire).
  579iv_infpl(train, train).
  580iv_infpl(try, try).
  581iv_infpl(understand, understand).
  582iv_infpl(vary, vary).
  583iv_infpl(visit, visit).
  584iv_infpl(wait, wait).
  585iv_infpl(walk, walk).
  586iv_infpl(warm, warm).
  587iv_infpl(wash, wash).
  588iv_infpl(watch, watch).
  589iv_infpl(water, water).
  590iv_infpl(win, win).
  591iv_infpl(work, work).
  592iv_infpl(write, write).
  593mn_pl('L', l).
  594mn_pl('°C', '°C').
  595mn_pl(cm, cm).
  596mn_pl(h, h).
  597mn_pl(kg, kg).
  598mn_pl(km, km).
  599mn_pl(l, l).
  600mn_pl(m, m).
  601mn_pl(mm, mm).
  602mn_pl(mol, mol).
  603mn_pl(s, s).
  604mn_pl(sec, s).
  605mn_pl(t, t).
  606mn_sg('L', l).
  607mn_sg('°C', '°C').
  608mn_sg(cm, cm).
  609mn_sg(h, h).
  610mn_sg(kg, kg).
  611mn_sg(km, km).
  612mn_sg(l, l).
  613mn_sg(m, m).
  614mn_sg(mm, mm).
  615mn_sg(mol, mol).
  616mn_sg(s, s).
  617mn_sg(sec, s).
  618mn_sg(t, t).
  619noun_mass(absinth, absinth, neutr).
  620noun_mass(access, access, neutr).
  621noun_mass(age, age, neutr).
  622noun_mass(bark, bark, neutr).
  623noun_mass(beer, beer, neutr).
  624noun_mass(blame, blame, neutr).
  625noun_mass(blue, blue, neutr).
  626noun_mass(body, body, neutr).
  627noun_mass(cake, cake, neutr).
  628noun_mass(carry, carry, neutr).
  629noun_mass(cheese, cheese, neutr).
  630noun_mass(code, code, neutr).
  631noun_mass(cold, cold, neutr).
  632noun_mass(color, color, neutr).
  633noun_mass(content, content, neutr).
  634noun_mass(country, country, neutr).
  635noun_mass(cover, cover, neutr).
  636noun_mass(dance, dance, neutr).
  637noun_mass(day, day, neutr).
  638noun_mass(declaration, declaration, neutr).
  639noun_mass(delivery, delivery, neutr).
  640noun_mass(description, description, neutr).
  641noun_mass(development, development, neutr).
  642noun_mass(doe, doe, neutr).
  643noun_mass(drink, drink, neutr).
  644noun_mass(drive, drive, neutr).
  645noun_mass(ease, ease, neutr).
  646noun_mass(egg, egg, neutr).
  647noun_mass(evening, evening, neutr).
  648noun_mass(evil, evil, neutr).
  649noun_mass(fear, fear, neutr).
  650noun_mass(feed, feed, neutr).
  651noun_mass(flow, flow, neutr).
  652noun_mass(food, food, neutr).
  653noun_mass(form, form, neutr).
  654noun_mass(furniture, furniture, neutr).
  655noun_mass(give, give, neutr).
  656noun_mass(good, good, neutr).
  657noun_mass(grass, grass, neutr).
  658noun_mass(green, green, neutr).
  659noun_mass(hate, hate, neutr).
  660noun_mass(height, height, neutr).
  661noun_mass(hurry, hurry, neutr).
  662noun_mass(institution, institution, neutr).
  663noun_mass(instruction, instruction, neutr).
  664noun_mass(interest, interest, neutr).
  665noun_mass(keep, keep, neutr).
  666noun_mass(laundry, laundry, neutr).
  667noun_mass(life, life, neutr).
  668noun_mass(living, living, neutr).
  669noun_mass(love, love, neutr).
  670noun_mass(lunch, lunch, neutr).
  671noun_mass(mail, mail, neutr).
  672noun_mass(meal, meal, neutr).
  673noun_mass(meat, meat, neutr).
  674noun_mass(milk, milk, neutr).
  675noun_mass(money, money, neutr).
  676noun_mass(morning, morning, neutr).
  677noun_mass(paper, paper, neutr).
  678noun_mass(patricide, patricide, neutr).
  679noun_mass(pay, pay, neutr).
  680noun_mass(pizza, pizza, neutr).
  681noun_mass(price, price, neutr).
  682noun_mass(reason, reason, neutr).
  683noun_mass(rice, rice, neutr).
  684noun_mass(room, room, neutr).
  685noun_mass(rot, rot, neutr).
  686noun_mass(sand, sand, neutr).
  687noun_mass(school, school, neutr).
  688noun_mass(service, service, neutr).
  689noun_mass(size, size, neutr).
  690noun_mass(sleep, sleep, neutr).
  691noun_mass(smell, smell, neutr).
  692noun_mass(space, space, neutr).
  693noun_mass(speed, speed, neutr).
  694noun_mass(string, string, neutr).
  695noun_mass(subscription, subscription, neutr).
  696noun_mass(sugar, sugar, neutr).
  697noun_mass(talk, talk, neutr).
  698noun_mass(text, text, neutr).
  699noun_mass(title, title, neutr).
  700noun_mass(town, town, neutr).
  701noun_mass(type, type, neutr).
  702noun_mass(use, use, neutr).
  703noun_mass(value, value, neutr).
  704noun_mass(want, want, neutr).
  705noun_mass(wash, wash, neutr).
  706noun_mass(watch, watch, neutr).
  707noun_mass(water, water, neutr).
  708noun_mass(wealth, wealth, neutr).
  709noun_mass(wet, wet, neutr).
  710noun_mass(white, white, neutr).
  711noun_mass(wine, wine, neutr).
  712noun_mass(work, work, neutr).
  713noun_mass(year, year, neutr).
  714noun_mass(zip, zip, neutr).
  715noun_pl('VisaCards', 'visa-card', neutr).
  716noun_pl('grown-ups', 'grown-up', human).
  717noun_pl('personae-non-grata', 'persona-non-grata', human).
  718noun_pl('personal-codes', 'personal-code', neutr).
  719noun_pl('visa-cards', 'visa-card', neutr).
  720noun_pl('zip-codes', 'zip-code', neutr).
  721noun_pl(abaci, abacus, neutr).
  722noun_pl(abacuses, abacus, neutr).
  723noun_pl(accounts, account, neutr).
  724noun_pl(addresses, address, neutr).
  725noun_pl(aeries, aerie, neutr).
  726noun_pl(ages, age, neutr).
  727noun_pl(aircraft, aircraft, neutr).
  728noun_pl(airlines, airline, neutr).
  729noun_pl(altos, alto, human).
  730noun_pl(ancestors, ancestor, human).
  731noun_pl(animals, animal, neutr).
  732noun_pl(apes, ape, neutr).
  733noun_pl(apples, apple, neutr).
  734noun_pl(approaches, approach, neutr).
  735noun_pl(articles, article, neutr).
  736noun_pl(assets, asset, neutr).
  737noun_pl(automatics, automatic, neutr).
  738noun_pl(averages, average, neutr).
  739noun_pl(balls, ball, neutr).
  740noun_pl(banks, bank, neutr).
  741noun_pl(barks, bark, neutr).
  742noun_pl(beats, beat, neutr).
  743noun_pl(beds, bed, neutr).
  744noun_pl(beers, beer, neutr).
  745noun_pl(bens, ben, neutr).
  746noun_pl(bikes, bike, neutr).
  747noun_pl(bites, bite, neutr).
  748noun_pl(blinks, blink, neutr).
  749noun_pl(blues, blue, neutr).
  750noun_pl(bodies, body, neutr).
  751noun_pl(boils, boil, neutr).
  752noun_pl(bones, bone, neutr).
  753noun_pl(books, book, neutr).
  754noun_pl(bosses, boss, human).
  755noun_pl(boxes, box, neutr).
  756noun_pl(boys, boy, masc).
  757noun_pl(branches, branch, neutr).
  758noun_pl(bretheren, brother, human).
  759noun_pl(brothers, brother, masc).
  760noun_pl(buttons, button, neutr).
  761noun_pl(buys, buy, neutr).
  762noun_pl(cakes, cake, neutr).
  763noun_pl(cans, can, neutr).
  764noun_pl(cards, card, neutr).
  765noun_pl(carnivores, carnivore, neutr).
  766noun_pl(carries, carry, neutr).
  767noun_pl(cars, car, neutr).
  768noun_pl(cases, case, neutr).
  769noun_pl(cashiers, cashier, human).
  770noun_pl(cats, cat, neutr).
  771noun_pl(caves, cave, neutr).
  772noun_pl(charges, charge, neutr).
  773noun_pl(chases, chase, neutr).
  774noun_pl(checks, check, neutr).
  775noun_pl(cheeses, cheese, neutr).
  776noun_pl(children, child, human).
  777noun_pl(circles, circle, neutr).
  778noun_pl(circumferences, circumference, neutr).
  779noun_pl(cities, city, neutr).
  780noun_pl(cleans, clean, neutr).
  781noun_pl(clerks, clerk, human).
  782noun_pl(codes, code, neutr).
  783noun_pl(colds, cold, neutr).
  784noun_pl(collapses, collapse, neutr).
  785noun_pl(colors, color, neutr).
  786noun_pl(companies, company, human).
  787noun_pl(computers, computer, neutr).
  788noun_pl(contents, content, neutr).
  789noun_pl(contracts, contract, neutr).
  790noun_pl(countries, country, neutr).
  791noun_pl(counts, count, human).
  792noun_pl(covers, cover, neutr).
  793noun_pl(cows, cow, human).
  794noun_pl(criminals, criminal, human).
  795noun_pl(customers, customer, human).
  796noun_pl(dances, dance, neutr).
  797noun_pl(databases, database, neutr).
  798noun_pl(dates, date, neutr).
  799noun_pl(days, day, neutr).
  800noun_pl(declarations, declaration, neutr).
  801noun_pl(deeps, deep, neutr).
  802noun_pl(deliveries, delivery, neutr).
  803noun_pl(descriptions, description, neutr).
  804noun_pl(desks, desk, neutr).
  805noun_pl(developments, development, neutr).
  806noun_pl(diameters, diameter, neutr).
  807noun_pl(displays, display, neutr).
  808noun_pl(doctors, doctor, human).
  809noun_pl(does, doe, neutr).
  810noun_pl(dogs, dog, neutr).
  811noun_pl(donkeys, donkey, neutr).
  812noun_pl(drinks, drink, neutr).
  813noun_pl(drives, drive, neutr).
  814noun_pl(drops, drop, neutr).
  815noun_pl(dummies, dummy, human).
  816noun_pl(eggs, egg, neutr).
  817noun_pl(elements, element, neutr).
  818noun_pl(empties, empty, neutr).
  819noun_pl(errors, error, neutr).
  820noun_pl(evenings, evening, neutr).
  821noun_pl(evils, evil, neutr).
  822noun_pl(eyes, eye, neutr).
  823noun_pl(eyries, aerie, neutr).
  824noun_pl(fairs, fair, neutr).
  825noun_pl(farmers, farmer, human).
  826noun_pl(fasts, fast, neutr).
  827noun_pl(fathers, father, masc).
  828noun_pl(fears, fear, neutr).
  829noun_pl(feeds, feed, neutr).
  830noun_pl(females, female, human).
  831noun_pl(flats, flat, neutr).
  832noun_pl(flies, fly, neutr).
  833noun_pl(flowers, flower, neutr).
  834noun_pl(flows, flow, neutr).
  835noun_pl(foods, food, neutr).
  836noun_pl(forms, form, neutr).
  837noun_pl(foxes, fox, neutr).
  838noun_pl(fridges, fridge, neutr).
  839noun_pl(friends, friend, human).
  840noun_pl(gales, gale, neutr).
  841noun_pl(gardens, garden, neutr).
  842noun_pl(girls, girl, fem).
  843noun_pl(goals, goal, neutr).
  844noun_pl(goats, goat, neutr).
  845noun_pl(goods, good, neutr).
  846noun_pl(grasses, grass, neutr).
  847noun_pl(grates, grate, neutr).
  848noun_pl(greens, green, neutr).
  849noun_pl(groups, group, neutr).
  850noun_pl(hands, hand, neutr).
  851noun_pl(hates, hate, neutr).
  852noun_pl(heights, height, neutr).
  853noun_pl(heroes, hero, human).
  854noun_pl(hits, hit, neutr).
  855noun_pl(holds, hold, neutr).
  856noun_pl(horses, horse, neutr).
  857noun_pl(hours, hour, neutr).
  858noun_pl(houses, house, neutr).
  859noun_pl(humans, human, human).
  860noun_pl(hurries, hurry, neutr).
  861noun_pl(husbands, husband, masc).
  862noun_pl(inserts, insert, neutr).
  863noun_pl(institutions, institution, neutr).
  864noun_pl(instructions, instruction, neutr).
  865noun_pl(integers, integer, neutr).
  866noun_pl(interests, interest, neutr).
  867noun_pl(invalids, invalid, human).
  868noun_pl(invites, invite, neutr).
  869noun_pl(keeps, keep, neutr).
  870noun_pl(laundries, laundry, neutr).
  871noun_pl(lifts, lift, neutr).
  872noun_pl(likes, like, neutr).
  873noun_pl(lists, list, neutr).
  874noun_pl(lives, life, neutr).
  875noun_pl(livings, living, neutr).
  876noun_pl(looks, look, neutr).
  877noun_pl(loves, love, neutr).
  878noun_pl(lunches, lunch, neutr).
  879noun_pl(machines, machine, neutr).
  880noun_pl(mails, mail, neutr).
  881noun_pl(managers, manager, human).
  882noun_pl(masters, master, human).
  883noun_pl(mates, mate, human).
  884noun_pl(mats, mat, neutr).
  885noun_pl(meals, meal, neutr).
  886noun_pl(meats, meat, neutr).
  887noun_pl(meets, meet, neutr).
  888noun_pl(members, member, human).
  889noun_pl(men, man, human).
  890noun_pl(merchants, merchant, human).
  891noun_pl(messages, message, neutr).
  892noun_pl(mice, mouse, neutr).
  893noun_pl(milks, milk, neutr).
  894noun_pl(monies, money, neutr).
  895noun_pl(mornings, morning, neutr).
  896noun_pl(mothers, mother, fem).
  897noun_pl(moves, move, neutr).
  898noun_pl(musts, must, neutr).
  899noun_pl(names, name, neutr).
  900noun_pl(naturals, natural, neutr).
  901noun_pl(needs, need, neutr).
  902noun_pl(numbers, number, neutr).
  903noun_pl(objects, object, neutr).
  904noun_pl(offers, offer, neutr).
  905noun_pl(offices, office, neutr).
  906noun_pl(opens, open, neutr).
  907noun_pl(owners, owner, human).
  908noun_pl(papers, paper, neutr).
  909noun_pl(parents, parent, human).
  910noun_pl(parks, park, neutr).
  911noun_pl(passwords, password, neutr).
  912noun_pl(patricides, patricide, neutr).
  913noun_pl(pencils, pencil, neutr).
  914noun_pl(percent, percent, neutr).
  915noun_pl(permits, permit, neutr).
  916noun_pl(personals, personal, neutr).
  917noun_pl(personas, persona, neutr).
  918noun_pl(persons, person, human).
  919noun_pl(pets, pet, neutr).
  920noun_pl(pizzas, pizza, neutr).
  921noun_pl(places, place, neutr).
  922noun_pl(plays, play, neutr).
  923noun_pl(points, point, neutr).
  924noun_pl(prices, price, neutr).
  925noun_pl(processes, process, neutr).
  926noun_pl(programs, program, neutr).
  927noun_pl(propositions, proposition, neutr).
  928noun_pl(publics, public, human).
  929noun_pl(queens, queen, human).
  930noun_pl(ratios, ratio, neutr).
  931noun_pl(rats, rat, neutr).
  932noun_pl(reals, real, neutr).
  933noun_pl(reasons, reason, neutr).
  934noun_pl(reds, red, human).
  935noun_pl(referees, referee, human).
  936noun_pl(rejects, reject, human).
  937noun_pl(rentals, rental, neutr).
  938noun_pl(resources, resource, neutr).
  939noun_pl(rooks, rook, human).
  940noun_pl(rooms, room, neutr).
  941noun_pl(runs, run, neutr).
  942noun_pl(sands, sand, neutr).
  943noun_pl(schools, school, neutr).
  944noun_pl(scores, score, neutr).
  945noun_pl(screens, screen, neutr).
  946noun_pl(sees, see, neutr).
  947noun_pl(sentences, sentence, neutr).
  948noun_pl(serves, serve, neutr).
  949noun_pl(services, service, neutr).
  950noun_pl(sets, set, neutr).
  951noun_pl(sheep, sheep, neutr).
  952noun_pl(signs, sign, neutr).
  953noun_pl(sinks, sink, neutr).
  954noun_pl(sisters, sister, fem).
  955noun_pl(sizes, size, neutr).
  956noun_pl(slots, slot, neutr).
  957noun_pl(smalls, small, neutr).
  958noun_pl(smells, smell, neutr).
  959noun_pl(smiles, smile, neutr).
  960noun_pl(snores, snore, neutr).
  961noun_pl(spaces, space, neutr).
  962noun_pl(speeds, speed, neutr).
  963noun_pl(stations, station, neutr).
  964noun_pl(streets, street, neutr).
  965noun_pl(strings, string, neutr).
  966noun_pl(subscriptions, subscription, neutr).
  967noun_pl(sugars, sugar, neutr).
  968noun_pl(surfaces, surface, neutr).
  969noun_pl(tables, table, neutr).
  970noun_pl(tails, tail, neutr).
  971noun_pl(takes, take, neutr).
  972noun_pl(talks, talk, neutr).
  973noun_pl(tellers, teller, human).
  974noun_pl(temperatures, temperature, neutr).
  975noun_pl(terms, term, neutr).
  976noun_pl(tests, test, neutr).
  977noun_pl(texts, text, neutr).
  978noun_pl(things, thing, neutr).
  979noun_pl(tires, tire, neutr).
  980noun_pl(titles, title, neutr).
  981noun_pl(tons, ton, neutr).
  982noun_pl(towns, town, neutr).
  983noun_pl(trains, train, neutr).
  984noun_pl(tries, try, neutr).
  985noun_pl(trues, true, neutr).
  986noun_pl(types, type, neutr).
  987noun_pl(uncles, uncle, masc).
  988noun_pl(users, user, human).
  989noun_pl(uses, use, neutr).
  990noun_pl(values, value, neutr).
  991noun_pl(vehicles, vehicle, neutr).
  992noun_pl(villages, village, neutr).
  993noun_pl(visas, visa, neutr).
  994noun_pl(visits, visit, neutr).
  995noun_pl(waits, wait, neutr).
  996noun_pl(walks, walk, neutr).
  997noun_pl(wants, want, neutr).
  998noun_pl(washes, wash, neutr).
  999noun_pl(watches, watch, neutr).
 1000noun_pl(waters, water, neutr).
 1001noun_pl(whites, white, neutr).
 1002noun_pl(wines, wine, neutr).
 1003noun_pl(wins, win, neutr).
 1004noun_pl(wives, wife, human).
 1005noun_pl(wolves, wolf, neutr).
 1006noun_pl(women, woman, human).
 1007noun_pl(works, work, neutr).
 1008noun_pl(years, year, neutr).
 1009noun_pl(zips, zip, neutr).
 1010noun_sg('VisaCard', 'visa-card', neutr).
 1011noun_sg('grown-up', 'grown-up', human).
 1012noun_sg('persona-non-grata', 'persona-non-grata', human).
 1013noun_sg('personal-code', 'personal-code', neutr).
 1014noun_sg('visa-card', 'visa-card', neutr).
 1015noun_sg('zip-code', 'zip-code', neutr).
 1016noun_sg(abacus, abacus, neutr).
 1017noun_sg(account, account, neutr).
 1018noun_sg(address, address, neutr).
 1019noun_sg(aerie, aerie, neutr).
 1020noun_sg(aery, aerie, neutr).
 1021noun_sg(age, age, neutr).
 1022noun_sg(aircraft, aircraft, neutr).
 1023noun_sg(airline, airline, neutr).
 1024noun_sg(alto, alto, human).
 1025noun_sg(ancestor, ancestor, human).
 1026noun_sg(animal, animal, neutr).
 1027noun_sg(ape, ape, neutr).
 1028noun_sg(apple, apple, neutr).
 1029noun_sg(approach, approach, neutr).
 1030noun_sg(article, article, neutr).
 1031noun_sg(asset, asset, neutr).
 1032noun_sg(automatic, automatic, neutr).
 1033noun_sg(average, average, neutr).
 1034noun_sg(bad, bad, neutr).
 1035noun_sg(ball, ball, neutr).
 1036noun_sg(bank, bank, neutr).
 1037noun_sg(bark, bark, neutr).
 1038noun_sg(beat, beat, neutr).
 1039noun_sg(bed, bed, neutr).
 1040noun_sg(beer, beer, neutr).
 1041noun_sg(ben, ben, neutr).
 1042noun_sg(bike, bike, neutr).
 1043noun_sg(bite, bite, neutr).
 1044noun_sg(blink, blink, neutr).
 1045noun_sg(blue, blue, neutr).
 1046noun_sg(body, body, neutr).
 1047noun_sg(boil, boil, neutr).
 1048noun_sg(bone, bone, neutr).
 1049noun_sg(book, book, neutr).
 1050noun_sg(boss, boss, human).
 1051noun_sg(box, box, neutr).
 1052noun_sg(boy, boy, masc).
 1053noun_sg(branch, branch, neutr).
 1054noun_sg(brother, brother, masc).
 1055noun_sg(button, button, neutr).
 1056noun_sg(buy, buy, neutr).
 1057noun_sg(cake, cake, neutr).
 1058noun_sg(can, can, neutr).
 1059noun_sg(car, car, neutr).
 1060noun_sg(card, card, neutr).
 1061noun_sg(carnivore, carnivore, neutr).
 1062noun_sg(carry, carry, neutr).
 1063noun_sg(case, case, neutr).
 1064noun_sg(cashier, cashier, human).
 1065noun_sg(cat, cat, neutr).
 1066noun_sg(cave, cave, neutr).
 1067noun_sg(charge, charge, neutr).
 1068noun_sg(chase, chase, neutr).
 1069noun_sg(check, check, neutr).
 1070noun_sg(cheese, cheese, neutr).
 1071noun_sg(child, child, human).
 1072noun_sg(circle, circle, neutr).
 1073noun_sg(circumference, circumference, neutr).
 1074noun_sg(city, city, neutr).
 1075noun_sg(clean, clean, neutr).
 1076noun_sg(clerk, clerk, human).
 1077noun_sg(code, code, neutr).
 1078noun_sg(cold, cold, neutr).
 1079noun_sg(collapse, collapse, neutr).
 1080noun_sg(color, color, neutr).
 1081noun_sg(company, company, human).
 1082noun_sg(computer, computer, neutr).
 1083noun_sg(content, content, neutr).
 1084noun_sg(contract, contract, neutr).
 1085noun_sg(count, count, human).
 1086noun_sg(country, country, neutr).
 1087noun_sg(cover, cover, neutr).
 1088noun_sg(cow, cow, human).
 1089noun_sg(credential, credential, neutr).
 1090noun_sg(criminal, criminal, human).
 1091noun_sg(customer, customer, human).
 1092noun_sg(dance, dance, neutr).
 1093noun_sg(database, database, neutr).
 1094noun_sg(date, date, neutr).
 1095noun_sg(day, day, neutr).
 1096noun_sg(declaration, declaration, neutr).
 1097noun_sg(deep, deep, neutr).
 1098noun_sg(delivery, delivery, neutr).
 1099noun_sg(description, description, neutr).
 1100noun_sg(desk, desk, neutr).
 1101noun_sg(development, development, neutr).
 1102noun_sg(diameter, diameter, neutr).
 1103noun_sg(display, display, neutr).
 1104noun_sg(doctor, doctor, human).
 1105noun_sg(doe, doe, neutr).
 1106noun_sg(dog, dog, neutr).
 1107noun_sg(donkey, donkey, neutr).
 1108noun_sg(drink, drink, neutr).
 1109noun_sg(drive, drive, neutr).
 1110noun_sg(drop, drop, neutr).
 1111noun_sg(dummy, dummy, human).
 1112noun_sg(egg, egg, neutr).
 1113noun_sg(element, element, neutr).
 1114noun_sg(empty, empty, neutr).
 1115noun_sg(error, error, neutr).
 1116noun_sg(evening, evening, neutr).
 1117noun_sg(evil, evil, neutr).
 1118noun_sg(eye, eye, neutr).
 1119noun_sg(eyrie, aerie, neutr).
 1120noun_sg(eyry, aerie, neutr).
 1121noun_sg(fair, fair, neutr).
 1122noun_sg(farmer, farmer, human).
 1123noun_sg(father, father, masc).
 1124noun_sg(fear, fear, neutr).
 1125noun_sg(feed, feed, neutr).
 1126noun_sg(female, female, human).
 1127noun_sg(flat, flat, neutr).
 1128noun_sg(flow, flow, neutr).
 1129noun_sg(flower, flower, neutr).
 1130noun_sg(fly, fly, neutr).
 1131noun_sg(food, food, neutr).
 1132noun_sg(form, form, neutr).
 1133noun_sg(fox, fox, neutr).
 1134noun_sg(fridge, fridge, neutr).
 1135noun_sg(friend, friend, human).
 1136noun_sg(gale, gale, neutr).
 1137noun_sg(garden, garden, neutr).
 1138noun_sg(girl, girl, fem).
 1139noun_sg(go, go, neutr).
 1140noun_sg(goal, goal, neutr).
 1141noun_sg(goat, goat, neutr).
 1142noun_sg(good, good, neutr).
 1143noun_sg(grass, grass, neutr).
 1144noun_sg(grate, grate, neutr).
 1145noun_sg(green, green, neutr).
 1146noun_sg(group, group, neutr).
 1147noun_sg(hand, hand, neutr).
 1148noun_sg(hate, hate, neutr).
 1149noun_sg(height, height, neutr).
 1150noun_sg(hero, hero, human).
 1151noun_sg(hit, hit, neutr).
 1152noun_sg(hold, hold, neutr).
 1153noun_sg(horse, horse, neutr).
 1154noun_sg(hour, hour, neutr).
 1155noun_sg(house, house, neutr).
 1156noun_sg(human, human, human).
 1157noun_sg(hurry, hurry, neutr).
 1158noun_sg(husband, husband, masc).
 1159noun_sg(id, id, neutr).
 1160noun_sg(insert, insert, neutr).
 1161noun_sg(institution, institution, neutr).
 1162noun_sg(instruction, instruction, neutr).
 1163noun_sg(integer, integer, neutr).
 1164noun_sg(interest, interest, neutr).
 1165noun_sg(invalid, invalid, human).
 1166noun_sg(invite, invite, neutr).
 1167noun_sg(keep, keep, neutr).
 1168noun_sg(know, know, neutr).
 1169noun_sg(laundry, laundry, neutr).
 1170noun_sg(life, life, neutr).
 1171noun_sg(lift, lift, neutr).
 1172noun_sg(like, like, neutr).
 1173noun_sg(list, list, neutr).
 1174noun_sg(living, living, neutr).
 1175noun_sg(look, look, neutr).
 1176noun_sg(love, love, neutr).
 1177noun_sg(lunch, lunch, neutr).
 1178noun_sg(machine, machine, neutr).
 1179noun_sg(mail, mail, neutr).
 1180noun_sg(man, man, masc).
 1181noun_sg(manager, manager, human).
 1182noun_sg(master, master, human).
 1183noun_sg(mat, mat, neutr).
 1184noun_sg(mate, mate, human).
 1185noun_sg(meal, meal, neutr).
 1186noun_sg(meat, meat, neutr).
 1187noun_sg(meet, meet, neutr).
 1188noun_sg(member, member, human).
 1189noun_sg(merchant, merchant, human).
 1190noun_sg(message, message, neutr).
 1191noun_sg(milk, milk, neutr).
 1192noun_sg(money, money, neutr).
 1193noun_sg(morning, morning, neutr).
 1194noun_sg(mother, mother, fem).
 1195noun_sg(mouse, mouse, neutr).
 1196noun_sg(move, move, neutr).
 1197noun_sg(must, must, neutr).
 1198noun_sg(name, name, neutr).
 1199noun_sg(natural, natural, neutr).
 1200noun_sg(need, need, neutr).
 1201noun_sg(number, number, neutr).
 1202noun_sg(object, object, neutr).
 1203noun_sg(offer, offer, neutr).
 1204noun_sg(office, office, neutr).
 1205noun_sg(old, old, neutr).
 1206noun_sg(open, open, neutr).
 1207noun_sg(owner, owner, human).
 1208noun_sg(paper, paper, neutr).
 1209noun_sg(parent, parent, human).
 1210noun_sg(park, park, neutr).
 1211noun_sg(password, password, neutr).
 1212noun_sg(patricide, patricide, neutr).
 1213noun_sg(pencil, pencil, neutr).
 1214noun_sg(percent, percent, neutr).
 1215noun_sg(permit, permit, neutr).
 1216noun_sg(person, person, human).
 1217noun_sg(persona, persona, neutr).
 1218noun_sg(personal, personal, neutr).
 1219noun_sg(pet, pet, neutr).
 1220noun_sg(pizza, pizza, neutr).
 1221noun_sg(place, place, neutr).
 1222noun_sg(play, play, neutr).
 1223noun_sg(point, point, neutr).
 1224noun_sg(price, price, neutr).
 1225noun_sg(process, process, neutr).
 1226noun_sg(program, program, neutr).
 1227noun_sg(proposition, proposition, neutr).
 1228noun_sg(public, public, human).
 1229noun_sg(queen, queen, human).
 1230noun_sg(quick, quick, neutr).
 1231noun_sg(rat, rat, neutr).
 1232noun_sg(ratio, ratio, neutr).
 1233noun_sg(raw, raw, neutr).
 1234noun_sg(read, read, neutr).
 1235noun_sg(real, real, neutr).
 1236noun_sg(reason, reason, neutr).
 1237noun_sg(red, red, human).
 1238noun_sg(referee, referee, human).
 1239noun_sg(reject, reject, human).
 1240noun_sg(rental, rental, neutr).
 1241noun_sg(resource, resource, neutr).
 1242noun_sg(rook, rook, human).
 1243noun_sg(room, room, neutr).
 1244noun_sg(run, run, neutr).
 1245noun_sg(sand, sand, neutr).
 1246noun_sg(say, say, neutr).
 1247noun_sg(school, school, neutr).
 1248noun_sg(score, score, neutr).
 1249noun_sg(screen, screen, neutr).
 1250noun_sg(see, see, neutr).
 1251noun_sg(sell, sell, neutr).
 1252noun_sg(sentence, sentence, neutr).
 1253noun_sg(serve, serve, neutr).
 1254noun_sg(service, service, neutr).
 1255noun_sg(set, set, neutr).
 1256noun_sg(sheep, sheep, neutr).
 1257noun_sg(sign, sign, neutr).
 1258noun_sg(sink, sink, neutr).
 1259noun_sg(sister, sister, fem).
 1260noun_sg(size, size, neutr).
 1261noun_sg(slot, slot, neutr).
 1262noun_sg(small, small, neutr).
 1263noun_sg(smart, smart, neutr).
 1264noun_sg(smell, smell, neutr).
 1265noun_sg(smile, smile, neutr).
 1266noun_sg(snore, snore, neutr).
 1267noun_sg(space, space, neutr).
 1268noun_sg(speed, speed, neutr).
 1269noun_sg(station, station, neutr).
 1270noun_sg(street, street, neutr).
 1271noun_sg(string, string, neutr).
 1272noun_sg(subscription, subscription, neutr).
 1273noun_sg(sugar, sugar, neutr).
 1274noun_sg(surface, surface, neutr).
 1275noun_sg(table, table, neutr).
 1276noun_sg(tail, tail, neutr).
 1277noun_sg(take, take, neutr).
 1278noun_sg(talk, talk, neutr).
 1279noun_sg(teller, teller, human).
 1280noun_sg(temperature, temperature, neutr).
 1281noun_sg(term, term, neutr).
 1282noun_sg(test, test, neutr).
 1283noun_sg(text, text, neutr).
 1284noun_sg(thing, thing, neutr).
 1285noun_sg(tire, tire, neutr).
 1286noun_sg(title, title, neutr).
 1287noun_sg(ton, ton, neutr).
 1288noun_sg(town, town, neutr).
 1289noun_sg(train, train, neutr).
 1290noun_sg(true, true, neutr).
 1291noun_sg(try, try, neutr).
 1292noun_sg(type, type, neutr).
 1293noun_sg(uncle, uncle, masc).
 1294noun_sg(use, use, neutr).
 1295noun_sg(user, user, human).
 1296noun_sg(value, value, neutr).
 1297noun_sg(vehicle, vehicle, neutr).
 1298noun_sg(village, village, neutr).
 1299noun_sg(visa, visa, neutr).
 1300noun_sg(visit, visit, neutr).
 1301noun_sg(wait, wait, neutr).
 1302noun_sg(walk, walk, neutr).
 1303noun_sg(want, want, neutr).
 1304noun_sg(wash, wash, neutr).
 1305noun_sg(watch, watch, neutr).
 1306noun_sg(water, water, neutr).
 1307noun_sg(white, white, neutr).
 1308noun_sg(wife, wife, fem).
 1309noun_sg(win, win, neutr).
 1310noun_sg(wine, wine, neutr).
 1311noun_sg(wolf, wolf, neutr).
 1312noun_sg(woman, woman, fem).
 1313noun_sg(work, work, neutr).
 1314noun_sg(year, year, neutr).
 1315noun_sg(young, young, neutr).
 1316noun_sg(zip, zip, neutr).
 1317pn_pl('APEs', 'APE', neutr).
 1318pn_pl('Augusts', 'August', neutr).
 1319pn_pl('Christmases', 'Christmas', neutr).
 1320pn_pl('VisaCards', 'VisaCard', neutr).
 1321pn_sg('APE', 'APE', neutr).
 1322pn_sg('August', 'August', neutr).
 1323pn_sg('Berlin', 'Berlin', neutr).
 1324pn_sg('Bill', 'Bill', masc).
 1325pn_sg('Christmas', 'Christmas', neutr).
 1326pn_sg('John', 'John', masc).
 1327pn_sg('Kaarel', 'Kaarel', masc).
 1328pn_sg('Mary', 'Mary', fem).
 1329pn_sg('Mr-Miller', 'Mr-Miller', masc).
 1330pn_sg('Paris', 'Paris', neutr).
 1331pn_sg('SM', 'SimpleMat', neutr).
 1332pn_sg('SimpleMat', 'SimpleMat', neutr).
 1333pn_sg('Sue', 'Sue', fem).
 1334pn_sg('VisaCard', 'VisaCard', neutr).
 1335pn_sg('Sun', 'Sun', neutr).
 1336pndef_sg('Sun', 'Sun', neutr).
 1337pndef_sg('Limmat', 'Limmat', neutr).
 1338pndef_pl('United-Nations', 'United-Nations', neutr).
 1339tv_finsg('comes-from', 'come-from').
 1340tv_finsg('fills-in', 'fill-in').
 1341tv_finsg('lives-at', 'live-at').
 1342tv_finsg('looks-at', 'look-at').
 1343tv_finsg('relates-to', 'relate-to').
 1344tv_finsg('waits-for', 'wait-for').
 1345tv_finsg('works-at', 'work-at').
 1346tv_finsg(accepts, accept).
 1347tv_finsg(accesses, access).
 1348tv_finsg(addresses, address).
 1349tv_finsg(ages, age).
 1350tv_finsg(allows, allow).
 1351tv_finsg(apes, ape).
 1352tv_finsg(approaches, approach).
 1353tv_finsg(approximates, approximate).
 1354tv_finsg(articles, article).
 1355tv_finsg(asks, ask).
 1356tv_finsg(assigns, assign).
 1357tv_finsg(assumes, assume).
 1358tv_finsg(authenticates, authenticate).
 1359tv_finsg(averages, average).
 1360tv_finsg(awaits, await).
 1361tv_finsg(balls, ball).
 1362tv_finsg(banks, bank).
 1363tv_finsg(barks, bark).
 1364tv_finsg(beats, beat).
 1365tv_finsg(beds, bed).
 1366tv_finsg(belies, belie).
 1367tv_finsg(believes, believe).
 1368tv_finsg(bikes, bike).
 1369tv_finsg(bites, bite).
 1370tv_finsg(blames, blame).
 1371tv_finsg(blues, blue).
 1372tv_finsg(boils, boil).
 1373tv_finsg(books, book).
 1374tv_finsg(boxes, box).
 1375tv_finsg(brings, bring).
 1376tv_finsg(buttons, button).
 1377tv_finsg(buys, buy).
 1378tv_finsg(cancels, cancel).
 1379tv_finsg(cans, can).
 1380tv_finsg(cards, card).
 1381tv_finsg(carries, carry).
 1382tv_finsg(cases, case).
 1383tv_finsg(cashiers, cashier).
 1384tv_finsg(caves, cave).
 1385tv_finsg(charges, charge).
 1386tv_finsg(chases, chase).
 1387tv_finsg(checks, check).
 1388tv_finsg(circles, circle).
 1389tv_finsg(cleans, clean).
 1390tv_finsg(codes, code).
 1391tv_finsg(collapses, collapse).
 1392tv_finsg(colors, color).
 1393tv_finsg(considers, consider).
 1394tv_finsg(contains, contain).
 1395tv_finsg(contents, content).
 1396tv_finsg(contracts, contract).
 1397tv_finsg(corrects, correct).
 1398tv_finsg(counts, count).
 1399tv_finsg(covers, cover).
 1400tv_finsg(cows, cow).
 1401tv_finsg(dances, dance).
 1402tv_finsg(dates, date).
 1403tv_finsg(delivers, deliver).
 1404tv_finsg(dirties, dirty).
 1405tv_finsg(displays, display).
 1406tv_finsg(doctors, doctor).
 1407tv_finsg(dogs, dog).
 1408tv_finsg(downloads, download).
 1409tv_finsg(drinks, drink).
 1410tv_finsg(drives, drive).
 1411tv_finsg(drops, drop).
 1412tv_finsg(eases, ease).
 1413tv_finsg(eats, eat).
 1414tv_finsg(eggs, egg).
 1415tv_finsg(empties, empty).
 1416tv_finsg(enters, enter).
 1417tv_finsg(expires, expire).
 1418tv_finsg(eyes, eye).
 1419tv_finsg(fasts, fast).
 1420tv_finsg(fathers, father).
 1421tv_finsg(fears, fear).
 1422tv_finsg(feeds, feed).
 1423tv_finsg(flies, fly).
 1424tv_finsg(flowers, flower).
 1425tv_finsg(forms, form).
 1426tv_finsg(foxes, fox).
 1427tv_finsg(gets, get).
 1428tv_finsg(gives, give).
 1429tv_finsg(goes, go).
 1430tv_finsg(grasses, grass).
 1431tv_finsg(grates, grate).
 1432tv_finsg(groups, group).
 1433tv_finsg(hands, hand).
 1434tv_finsg(has, have).
 1435tv_finsg(hates, hate).
 1436tv_finsg(hears, hear).
 1437tv_finsg(hits, hit).
 1438tv_finsg(holds, hold).
 1439tv_finsg(houses, house).
 1440tv_finsg(hurries, hurry).
 1441tv_finsg(husbands, husband).
 1442tv_finsg(implies, imply).
 1443tv_finsg(inserts, insert).
 1444tv_finsg(interests, interest).
 1445tv_finsg(invalids, invalid).
 1446tv_finsg(invites, invite).
 1447tv_finsg(keeps, keep).
 1448tv_finsg(knows, know).
 1449tv_finsg(lifts, lift).
 1450tv_finsg(likes, like).
 1451tv_finsg(lists, list).
 1452tv_finsg(lives, live).
 1453tv_finsg(loses, lose).
 1454tv_finsg(loves, love).
 1455tv_finsg(machines, machine).
 1456tv_finsg(mails, mail).
 1457tv_finsg(mans, man).
 1458tv_finsg(masters, master).
 1459tv_finsg(mates, mate).
 1460tv_finsg(mats, mat).
 1461tv_finsg(meets, meet).
 1462tv_finsg(milks, milk).
 1463tv_finsg(mothers, mother).
 1464tv_finsg(moves, move).
 1465tv_finsg(names, name).
 1466tv_finsg(needs, need).
 1467tv_finsg(numbers, number).
 1468tv_finsg(numbs, numb).
 1469tv_finsg(offers, offer).
 1470tv_finsg(opens, open).
 1471tv_finsg(owns, own).
 1472tv_finsg(papers, paper).
 1473tv_finsg(parks, park).
 1474tv_finsg(pays, pay).
 1475tv_finsg(permits, permit).
 1476tv_finsg(pets, pet).
 1477tv_finsg(places, place).
 1478tv_finsg(plays, play).
 1479tv_finsg(points, point).
 1480tv_finsg(prices, price).
 1481tv_finsg(processes, process).
 1482tv_finsg(programs, program).
 1483tv_finsg(propositions, proposition).
 1484tv_finsg(proves, prove).
 1485tv_finsg(queens, queen).
 1486tv_finsg(rats, rat).
 1487tv_finsg(reads, read).
 1488tv_finsg(referees, referee).
 1489tv_finsg(rejects, reject).
 1490tv_finsg(replaces, replace).
 1491tv_finsg(rooks, rook).
 1492tv_finsg(rooms, room).
 1493tv_finsg(rots, rot).
 1494tv_finsg(runs, run).
 1495tv_finsg(sands, sand).
 1496tv_finsg(says, say).
 1497tv_finsg(schools, school).
 1498tv_finsg(scores, score).
 1499tv_finsg(screens, screen).
 1500tv_finsg(sees, see).
 1501tv_finsg(sells, sell).
 1502tv_finsg(sends, send).
 1503tv_finsg(sentences, sentence).
 1504tv_finsg(serves, serve).
 1505tv_finsg(services, service).
 1506tv_finsg(sets, set).
 1507tv_finsg(signs, sign).
 1508tv_finsg(sinks, sink).
 1509tv_finsg(sits, sit).
 1510tv_finsg(sizes, size).
 1511tv_finsg(sleeps, sleep).
 1512tv_finsg(slots, slot).
 1513tv_finsg(smarts, smart).
 1514tv_finsg(smells, smell).
 1515tv_finsg(softens, soften).
 1516tv_finsg(spaces, space).
 1517tv_finsg(speeds, speed).
 1518tv_finsg(steals, steal).
 1519tv_finsg(succeeds, succeed).
 1520tv_finsg(sugars, sugar).
 1521tv_finsg(surfaces, surface).
 1522tv_finsg(tables, table).
 1523tv_finsg(tails, tail).
 1524tv_finsg(takes, take).
 1525tv_finsg(talks, talk).
 1526tv_finsg(tells, tell).
 1527tv_finsg(tests, test).
 1528tv_finsg(tires, tire).
 1529tv_finsg(trains, train).
 1530tv_finsg(transmits, transmit).
 1531tv_finsg(tries, try).
 1532tv_finsg(trues, true).
 1533tv_finsg(types, type).
 1534tv_finsg(understands, understand).
 1535tv_finsg(uses, use).
 1536tv_finsg(values, value).
 1537tv_finsg(varies, vary).
 1538tv_finsg(visits, visit).
 1539tv_finsg(waits, wait).
 1540tv_finsg(walks, walk).
 1541tv_finsg(wants, want).
 1542tv_finsg(warms, warm).
 1543tv_finsg(washes, wash).
 1544tv_finsg(watches, watch).
 1545tv_finsg(waters, water).
 1546tv_finsg(wets, wet).
 1547tv_finsg(wines, wine).
 1548tv_finsg(wins, win).
 1549tv_finsg(wolfs, wolf).
 1550tv_finsg(works, work).
 1551tv_finsg(writes, write).
 1552tv_finsg(zips, zip).
 1553tv_infpl('come-from', 'come-from').
 1554tv_infpl('fill-in', 'fill-in').
 1555tv_infpl('live-at', 'live-at').
 1556tv_infpl('look-at', 'look-at').
 1557tv_infpl('relate-to', 'relate-to').
 1558tv_infpl('wait-for', 'wait-for').
 1559tv_infpl('work-at', 'work-at').
 1560tv_infpl(accept, accept).
 1561tv_infpl(access, access).
 1562tv_infpl(address, address).
 1563tv_infpl(age, age).
 1564tv_infpl(allow, allow).
 1565tv_infpl(ape, ape).
 1566tv_infpl(approach, approach).
 1567tv_infpl(approximate, approximate).
 1568tv_infpl(article, article).
 1569tv_infpl(ask, ask).
 1570tv_infpl(assign, assign).
 1571tv_infpl(assume, assume).
 1572tv_infpl(authenticate, authenticate).
 1573tv_infpl(average, average).
 1574tv_infpl(await, await).
 1575tv_infpl(ball, ball).
 1576tv_infpl(bank, bank).
 1577tv_infpl(bark, bark).
 1578tv_infpl(beat, beat).
 1579tv_infpl(bed, bed).
 1580tv_infpl(belie, belie).
 1581tv_infpl(believe, believe).
 1582tv_infpl(bike, bike).
 1583tv_infpl(bite, bite).
 1584tv_infpl(blame, blame).
 1585tv_infpl(blue, blue).
 1586tv_infpl(boil, boil).
 1587tv_infpl(book, book).
 1588tv_infpl(box, box).
 1589tv_infpl(bring, bring).
 1590tv_infpl(button, button).
 1591tv_infpl(buy, buy).
 1592tv_infpl(can, can).
 1593tv_infpl(cancel, cancel).
 1594tv_infpl(card, card).
 1595tv_infpl(carry, carry).
 1596tv_infpl(case, case).
 1597tv_infpl(cashier, cashier).
 1598tv_infpl(cave, cave).
 1599tv_infpl(charge, charge).
 1600tv_infpl(chase, chase).
 1601tv_infpl(check, check).
 1602tv_infpl(circle, circle).
 1603tv_infpl(clean, clean).
 1604tv_infpl(code, code).
 1605tv_infpl(collapse, collapse).
 1606tv_infpl(color, color).
 1607tv_infpl(consider, consider).
 1608tv_infpl(contain, contain).
 1609tv_infpl(content, content).
 1610tv_infpl(contract, contract).
 1611tv_infpl(correct, correct).
 1612tv_infpl(count, count).
 1613tv_infpl(cover, cover).
 1614tv_infpl(cow, cow).
 1615tv_infpl(dance, dance).
 1616tv_infpl(date, date).
 1617tv_infpl(deliver, deliver).
 1618tv_infpl(dirty, dirty).
 1619tv_infpl(display, display).
 1620tv_infpl(doctor, doctor).
 1621tv_infpl(dog, dog).
 1622tv_infpl(download, download).
 1623tv_infpl(drink, drink).
 1624tv_infpl(drive, drive).
 1625tv_infpl(drop, drop).
 1626tv_infpl(ease, ease).
 1627tv_infpl(eat, eat).
 1628tv_infpl(egg, egg).
 1629tv_infpl(empty, empty).
 1630tv_infpl(enter, enter).
 1631tv_infpl(expire, expire).
 1632tv_infpl(eye, eye).
 1633tv_infpl(fast, fast).
 1634tv_infpl(father, father).
 1635tv_infpl(fear, fear).
 1636tv_infpl(feed, feed).
 1637tv_infpl(flower, flower).
 1638tv_infpl(fly, fly).
 1639tv_infpl(form, form).
 1640tv_infpl(fox, fox).
 1641tv_infpl(get, get).
 1642tv_infpl(give, give).
 1643tv_infpl(go, go).
 1644tv_infpl(grass, grass).
 1645tv_infpl(grate, grate).
 1646tv_infpl(group, group).
 1647tv_infpl(hand, hand).
 1648tv_infpl(hate, hate).
 1649tv_infpl(have, have).
 1650tv_infpl(hear, hear).
 1651tv_infpl(hit, hit).
 1652tv_infpl(hold, hold).
 1653tv_infpl(house, house).
 1654tv_infpl(hurry, hurry).
 1655tv_infpl(husband, husband).
 1656tv_infpl(imply, imply).
 1657tv_infpl(insert, insert).
 1658tv_infpl(interest, interest).
 1659tv_infpl(invalid, invalid).
 1660tv_infpl(invite, invite).
 1661tv_infpl(keep, keep).
 1662tv_infpl(know, know).
 1663tv_infpl(lift, lift).
 1664tv_infpl(like, like).
 1665tv_infpl(list, list).
 1666tv_infpl(live, live).
 1667tv_infpl(lose, lose).
 1668tv_infpl(love, love).
 1669tv_infpl(machine, machine).
 1670tv_infpl(mail, mail).
 1671tv_infpl(man, man).
 1672tv_infpl(master, master).
 1673tv_infpl(mat, mat).
 1674tv_infpl(mate, mate).
 1675tv_infpl(meet, meet).
 1676tv_infpl(milk, milk).
 1677tv_infpl(mother, mother).
 1678tv_infpl(move, move).
 1679tv_infpl(name, name).
 1680tv_infpl(need, need).
 1681tv_infpl(numb, numb).
 1682tv_infpl(number, number).
 1683tv_infpl(offer, offer).
 1684tv_infpl(open, open).
 1685tv_infpl(own, own).
 1686tv_infpl(paper, paper).
 1687tv_infpl(park, park).
 1688tv_infpl(pay, pay).
 1689tv_infpl(permit, permit).
 1690tv_infpl(pet, pet).
 1691tv_infpl(place, place).
 1692tv_infpl(play, play).
 1693tv_infpl(point, point).
 1694tv_infpl(price, price).
 1695tv_infpl(process, process).
 1696tv_infpl(program, program).
 1697tv_infpl(proposition, proposition).
 1698tv_infpl(prove, prove).
 1699tv_infpl(queen, queen).
 1700tv_infpl(rat, rat).
 1701tv_infpl(read, read).
 1702tv_infpl(referee, referee).
 1703tv_infpl(reject, reject).
 1704tv_infpl(replace, replace).
 1705tv_infpl(rook, rook).
 1706tv_infpl(room, room).
 1707tv_infpl(rot, rot).
 1708tv_infpl(run, run).
 1709tv_infpl(sand, sand).
 1710tv_infpl(say, say).
 1711tv_infpl(school, school).
 1712tv_infpl(score, score).
 1713tv_infpl(screen, screen).
 1714tv_infpl(see, see).
 1715tv_infpl(sell, sell).
 1716tv_infpl(send, send).
 1717tv_infpl(sentence, sentence).
 1718tv_infpl(serve, serve).
 1719tv_infpl(service, service).
 1720tv_infpl(set, set).
 1721tv_infpl(sign, sign).
 1722tv_infpl(sink, sink).
 1723tv_infpl(sit, sit).
 1724tv_infpl(size, size).
 1725tv_infpl(sleep, sleep).
 1726tv_infpl(slot, slot).
 1727tv_infpl(smart, smart).
 1728tv_infpl(smell, smell).
 1729tv_infpl(soften, soften).
 1730tv_infpl(space, space).
 1731tv_infpl(speed, speed).
 1732tv_infpl(steal, steal).
 1733tv_infpl(succeed, succeed).
 1734tv_infpl(sugar, sugar).
 1735tv_infpl(surface, surface).
 1736tv_infpl(table, table).
 1737tv_infpl(tail, tail).
 1738tv_infpl(take, take).
 1739tv_infpl(talk, talk).
 1740tv_infpl(tell, tell).
 1741tv_infpl(test, test).
 1742tv_infpl(tire, tire).
 1743tv_infpl(train, train).
 1744tv_infpl(transmit, transmit).
 1745tv_infpl(true, true).
 1746tv_infpl(try, try).
 1747tv_infpl(type, type).
 1748tv_infpl(understand, understand).
 1749tv_infpl(use, use).
 1750tv_infpl(value, value).
 1751tv_infpl(vary, vary).
 1752tv_infpl(visit, visit).
 1753tv_infpl(wait, wait).
 1754tv_infpl(walk, walk).
 1755tv_infpl(want, want).
 1756tv_infpl(warm, warm).
 1757tv_infpl(wash, wash).
 1758tv_infpl(watch, watch).
 1759tv_infpl(water, water).
 1760tv_infpl(wet, wet).
 1761tv_infpl(win, win).
 1762tv_infpl(wine, wine).
 1763tv_infpl(wolf, wolf).
 1764tv_infpl(work, work).
 1765tv_infpl(write, write).
 1766tv_infpl(zip, zip).
 1767tv_pp(accepted, accept).
 1768tv_pp(addressed, address).
 1769tv_pp(aged, age).
 1770tv_pp(allowed, allow).
 1771tv_pp(aped, ape).
 1772tv_pp(approached, approach).
 1773tv_pp(approximated, approximate).
 1774tv_pp(articled, article).
 1775tv_pp(assigned, assign).
 1776tv_pp(assumed, assume).
 1777tv_pp(authenticated, authenticate).
 1778tv_pp(averaged, average).
 1779tv_pp(awaited, await).
 1780tv_pp(banked, bank).
 1781tv_pp(barked, bark).
 1782tv_pp(beaten, beat).
 1783tv_pp(bedded, bed).
 1784tv_pp(belied, belie).
 1785tv_pp(believed, believe).
 1786tv_pp(biked, bike).
 1787tv_pp(bitten, bite).
 1788tv_pp(blamed, blame).
 1789tv_pp(blued, blue).
 1790tv_pp(boiled, boil).
 1791tv_pp(booked, book).
 1792tv_pp(bought, buy).
 1793tv_pp(boxed, box).
 1794tv_pp(brought, bring).
 1795tv_pp(buttoned, button).
 1796tv_pp(cancelled, cancel).
 1797tv_pp(canned, can).
 1798tv_pp(carded, card).
 1799tv_pp(carried, carry).
 1800tv_pp(cased, case).
 1801tv_pp(cashiered, cashier).
 1802tv_pp(charged, charge).
 1803tv_pp(chased, chase).
 1804tv_pp(checked, check).
 1805tv_pp(circled, circle).
 1806tv_pp(cleaned, clean).
 1807tv_pp(coded, code).
 1808tv_pp(collapsed, collapse).
 1809tv_pp(considered, consider).
 1810tv_pp(contained, contain).
 1811tv_pp(contented, content).
 1812tv_pp(contracted, contract).
 1813tv_pp(corrected, correct).
 1814tv_pp(counted, count).
 1815tv_pp(covered, cover).
 1816tv_pp(cowed, cow).
 1817tv_pp(danced, dance).
 1818tv_pp(dated, date).
 1819tv_pp(delivered, deliver).
 1820tv_pp(dirtied, dirty).
 1821tv_pp(displayed, display).
 1822tv_pp(doctored, doctor).
 1823tv_pp(dogged, dog).
 1824tv_pp(downloaded, download).
 1825tv_pp(driven, drive).
 1826tv_pp(dropped, drop).
 1827tv_pp(drunk, drink).
 1828tv_pp(eased, ease).
 1829tv_pp(eaten, eat).
 1830tv_pp(emptied, empty).
 1831tv_pp(entered, enter).
 1832tv_pp(expired, expire).
 1833tv_pp(eyed, eye).
 1834tv_pp(fasted, fast).
 1835tv_pp(fathered, father).
 1836tv_pp(feared, fear).
 1837tv_pp(fed, feed).
 1838tv_pp(feed, feed).
 1839tv_pp(flowered, flower).
 1840tv_pp(flown, fly).
 1841tv_pp(formed, form).
 1842tv_pp(foxed, fox).
 1843tv_pp(given, give).
 1844tv_pp(gone, go).
 1845tv_pp(got, get).
 1846tv_pp(gotten, get).
 1847tv_pp(grassed, grass).
 1848tv_pp(grated, grate).
 1849tv_pp(grouped, group).
 1850tv_pp(had, have).
 1851tv_pp(handed, hand).
 1852tv_pp(hated, hate).
 1853tv_pp(heard, hear).
 1854tv_pp(held, hold).
 1855tv_pp(hit, hit).
 1856tv_pp(housed, house).
 1857tv_pp(hurried, hurry).
 1858tv_pp(husbanded, husband).
 1859tv_pp(implied, imply).
 1860tv_pp(inserted, insert).
 1861tv_pp(interested, interest).
 1862tv_pp(invited, invite).
 1863tv_pp(kept, keep).
 1864tv_pp(known, know).
 1865tv_pp(lifted, lift).
 1866tv_pp(liked, like).
 1867tv_pp(listed, list).
 1868tv_pp(lived, live).
 1869tv_pp(lost, lose).
 1870tv_pp(loved, love).
 1871tv_pp(machined, machine).
 1872tv_pp(mailed, mail).
 1873tv_pp(manned, man).
 1874tv_pp(mastered, master).
 1875tv_pp(mated, mate).
 1876tv_pp(matted, mat).
 1877tv_pp(met, meet).
 1878tv_pp(milked, milk).
 1879tv_pp(mothered, mother).
 1880tv_pp(moved, move).
 1881tv_pp(named, name).
 1882tv_pp(needed, need).
 1883tv_pp(numbed, numb).
 1884tv_pp(numbered, number).
 1885tv_pp(offered, offer).
 1886tv_pp(opened, open).
 1887tv_pp(owned, own).
 1888tv_pp(paid, pay).
 1889tv_pp(papered, paper).
 1890tv_pp(parked, park).
 1891tv_pp(permitted, permit).
 1892tv_pp(petted, pet).
 1893tv_pp(placed, place).
 1894tv_pp(played, play).
 1895tv_pp(pointed, point).
 1896tv_pp(priced, price).
 1897tv_pp(processed, process).
 1898tv_pp(programmed, program).
 1899tv_pp(propositioned, proposition).
 1900tv_pp(proved, prove).
 1901tv_pp(proven, prove).
 1902tv_pp(queened, queen).
 1903tv_pp(ratted, rat).
 1904tv_pp(read, read).
 1905tv_pp(refereed, referee).
 1906tv_pp(rejected, reject).
 1907tv_pp(replaced, replace).
 1908tv_pp(rooked, rook).
 1909tv_pp(roomed, room).
 1910tv_pp(rotted, rot).
 1911tv_pp(run, run).
 1912tv_pp(said, say).
 1913tv_pp(sanded, sand).
 1914tv_pp(sat, sit).
 1915tv_pp(schooled, school).
 1916tv_pp(scored, score).
 1917tv_pp(screened, screen).
 1918tv_pp(seen, see).
 1919tv_pp(sent, send).
 1920tv_pp(sentenced, sentence).
 1921tv_pp(served, serve).
 1922tv_pp(serviced, service).
 1923tv_pp(set, set).
 1924tv_pp(signed, sign).
 1925tv_pp(sized, size).
 1926tv_pp(slept, sleep).
 1927tv_pp(slotted, slot).
 1928tv_pp(smarted, smart).
 1929tv_pp(smelled, smell).
 1930tv_pp(smelt, smell).
 1931tv_pp(softened, soften).
 1932tv_pp(sold, sell).
 1933tv_pp(spaced, space).
 1934tv_pp(sped, speed).
 1935tv_pp(speeded, speed).
 1936tv_pp(stolen, steal).
 1937tv_pp(succeeded, succeed).
 1938tv_pp(sugared, sugar).
 1939tv_pp(sunk, sink).
 1940tv_pp(sunken, sink).
 1941tv_pp(surfaced, surface).
 1942tv_pp(tabled, table).
 1943tv_pp(tailed, tail).
 1944tv_pp(taken, take).
 1945tv_pp(talked, talk).
 1946tv_pp(tested, test).
 1947tv_pp(tired, tire).
 1948tv_pp(told, tell).
 1949tv_pp(trained, train).
 1950tv_pp(transmitted, transmit).
 1951tv_pp(tried, try).
 1952tv_pp(typed, type).
 1953tv_pp(understood, understand).
 1954tv_pp(used, use).
 1955tv_pp(valued, value).
 1956tv_pp(varied, vary).
 1957tv_pp(visited, visit).
 1958tv_pp(waited, wait).
 1959tv_pp(walked, walk).
 1960tv_pp(wanted, want).
 1961tv_pp(warmed, warm).
 1962tv_pp(washed, wash).
 1963tv_pp(watched, watch).
 1964tv_pp(watered, water).
 1965tv_pp(wet, wet).
 1966tv_pp(wetted, wet).
 1967tv_pp(wolfed, wolf).
 1968tv_pp(won, win).
 1969tv_pp(worked, work).
 1970tv_pp(written, write).
 1971tv_pp(wrought, work).
 1972tv_pp(zipped, zip).
 1973prep(from, from).
 1974prep(as, as).
 1975prep(about, about).
 1976prep(by, by).
 1977prep(for, for).
 1978prep(among, among).
 1979prep(amongst, amongst).
 1980prep(like, like).
 1981prep(without, without).
 1982prep(despite, despite).
 1983prep(amid, amid).
 1984prep(aboard, aboard).
 1985prep(in, in).
 1986prep(at, at).
 1987prep(on, on).
 1988prep(over, over).
 1989prep(around, around).
 1990prep(between, between).
 1991prep(inside, inside).
 1992prep(behind, behind).
 1993prep(below, below).
 1994prep(beneath, beneath).
 1995prep(outside, outside).
 1996prep(upon, upon).
 1997prep(under, under).
 1998prep(above, above).
 1999prep(beside, beside).
 2000prep(near, near).
 2001prep(throughout, throughout).
 2002prep(before, before).
 2003prep(after, after).
 2004prep(within, within).
 2005prep(till, till).
 2006prep(until, until).
 2007prep(to, to).
 2008prep(into, into).
 2009prep(through, through).
 2010prep(toward, toward).
 2011prep(towards, towards).
 2012prep(onto, onto).
 2013prep(across, across).
 2014prep(off, off).
 2015prep(down, down).
 2016prep(up, up).
 2017prep(along, along).
 2018prep(past, past).
 2019prep(beyond, beyond).
 2020prep(out, out).
 2021prep(against, against).
 2022prep(alongside, alongside).
 2023prep(via, via).
 2024prep(with, with).
 2025prep(during, during)