2:- ensure_loaded(wn30_iface).    3
    4word_overlap(W1,W2):- atom_contains(W1,W2);atom_contains(W2,W1).
    5longer(W1,W2):- atom_length(W1,L1),atom_length(W2,L2),(L1==L2->W1@>W2;L1<L2).
    6slonger(W1,W2,(=)):-W1==W2,!.
    7slonger(W1,W2,(>)):-longer(W1,W2),!.
    8slonger(_W1,_W2,(<)).
    9maybe_stem(W1,W2):- word_overlap(W1,W2),!. 
   10maybe_stem(W1,W2):- first_half(W1,L1),first_half(W2,L2), word_overlap(L1,L2).
   11first_half(S,S2):- atom_length(S,L),L2 is div(L,2), L2>3, sub_atom(S,L2,_,_,S2),!.
   12first_half(S,S).
   13% imports der/4 and s/6 from wordnet db
   14candidate_creation(W1,W2):- der(ID1,SN1,ID2,SN2),s(ID1,SN1,W1,_POS1,_X1,_Y1),s(ID2,SN2,W2,_POS2,_X2,_Y2).
   15der_stem(O1,O2):- candidate_creation(W1,W2),maybe_stem(W1,W2),W1\==W2,
   16  (longer(W1,W2)->(O1:O2=W1:W2);(O2:O1=W1:W2)).
   17tellstems:- tell(tellstems),forall(no_repeats(der_stem(O1,O2)),format('~N~q.~n',[my_stems(O1,O2)])),told.
   18
   19
   20/*
   21
   22my_stems('civil liberty','civil-libertarian').
   23my_stems('co-occurrent','co-occurrence').
   24my_stems('hair style',hairstylist).
   25my_stems('left-handed','left-handedness').
   26my_stems('Modern',modernness).
   27my_stems('right-handed','right-handedness').
   28my_stems('three-dimensional','three-dimensionality').
   29my_stems('two-dimensional','two-dimensionality').
   30my_stems('up-to-date','up-to-dateness').
   31my_stems(abound,abundance).
   32my_stems(abrupt,abruptness).
   33my_stems(abstemious,abstemiousness).
   34my_stems(abundant,abundance).
   35my_stems(accelerate,acceleration).
   36my_stems(adjacent,adjacency).
   37my_stems(admit,admittance).
   38my_stems(adnexa,adnexal).
   39my_stems(advantage,advantageous).
   40my_stems(advantageous,advantageousness).
   41my_stems(advantageous,profitableness).
   42my_stems(advisable,advisability).
   43my_stems(affirmative,affirmativeness).
   44my_stems(aimless,aimlessness).
   45my_stems(airy,airiness).
   46my_stems(align,alignment).
   47my_stems(altitude,altitudinal).
   48my_stems(altitude,altitudinous).
   49my_stems(ambidextrous,ambidexterity).
   50my_stems(ambidextrous,ambidextrousness).
   51my_stems(ample,ampleness).
   52my_stems(ampulla,ampullar).
   53my_stems(ampulla,ampullary).
   54my_stems(analytic,analyticity).
   55my_stems(anastomotic,anastomosis).
   56my_stems(anatomy,anatomic).
   57my_stems(anatomy,anatomical).
   58my_stems(anatomy,anatomist).
   59my_stems(angular,angularity).
   60my_stems(antecede,antecedence).
   61my_stems(antecede,antecedency).
   62my_stems(antecedent,antecedence).
   63my_stems(antecedent,antecedency).
   64my_stems(anterior,anteriority).
   65my_stems(area,areal).
   66my_stems(arrange,arrangement).
   67my_stems(arthromere,arthromeric).
   68my_stems(assailable,assailability).
   69my_stems(assertive,assertiveness).
   70my_stems(assess,assessment).
   71my_stems(astringent,astringency).
   72my_stems(asymmetry,asymmetric).
   73my_stems(asymmetry,asymmetrical).
   74my_stems(attenuate,attenuation).
   75my_stems(attitude,attitudinise).
   76my_stems(auspicious,auspiciousness).
   77my_stems(authorise,authorisation).
   78my_stems(authorize,authorization).
   79my_stems(awkward,awkwardness).
   80my_stems(bad,badness).
   81my_stems(barren,barrenness).
   82my_stems(beam,beamy).
   83my_stems(benefit,beneficial).
   84my_stems(big,bigness).
   85my_stems(bilateral,bilaterality).
   86my_stems(boring,boringness).
   87my_stems(bottomless,bottomlessness).
   88my_stems(bounded,boundedness).
   89my_stems(boundless,boundlessness).
   90my_stems(bountiful,bountifulness).
   91my_stems(brachycephaly,brachycephalic).
   92my_stems(breakable,breakability).
   93my_stems(bregma,bregmatic).
   94my_stems(brief,briefness).
   95my_stems(broad,broadness).
   96my_stems(bulb,bulbous).
   97my_stems(bulgy,bulginess).
   98my_stems(bulk,bulky).
   99my_stems(bulky,bulkiness).
  100my_stems(bumptious,bumptiousness).
  101my_stems(cadaver,cadaveric).
  102my_stems(cadaver,cadaverous).
  103my_stems(caliber,calibrate).
  104my_stems(canal,canalize).
  105my_stems(canaliculus,canalicular).
  106my_stems(capable,capability).
  107my_stems(capable,capableness).
  108my_stems(capacious,capaciousness).
  109my_stems(capacity,capacitate).
  110my_stems(catch,catchy).
  111my_stems(cauda,caudal).
  112my_stems(ceaseless,ceaselessness).
  113my_stems(central,centrality).
  114my_stems(changeless,changelessness).
  115my_stems(channel,channelize).
  116my_stems(cheap,cheapness).
  117my_stems(chiasm,chiasmal).
  118my_stems(chiasm,chiasmatic).
  119my_stems(chiasm,chiasmic).
  120my_stems(circular,circularity).
  121my_stems(clear,clearance).
  122my_stems(close,closeness).
  123my_stems(cocky,cockiness).
  124my_stems(coif,coiffure).
  125my_stems(coincide,coincidence).
  126my_stems(coincident,coincidence).
  127my_stems(comical,comicality).
  128my_stems(commodious,commodiousness).
  129my_stems(competent,competence).
  130my_stems(competent,competency).
  131my_stems(complement,complemental).
  132my_stems(complement,complementary).
  133my_stems(concave,concaveness).
  134my_stems(concave,concavity).
  135my_stems(concentrate,concentration).
  136my_stems(concentric,concentricity).
  137my_stems(concomitant,concomitance).
  138my_stems(concur,concurrence).
  139my_stems(concurrent,concurrence).
  140my_stems(consequence,consequential).
  141my_stems(constructive,constructiveness).
  142my_stems(contemporaneous,contemporaneity).
  143my_stems(contemporaneous,contemporaneousness).
  144my_stems(contiguous,contiguity).
  145my_stems(contiguous,contiguousness).
  146my_stems(continue,continuation).
  147my_stems(continuous,continuity).
  148my_stems(continuous,continuousness).
  149my_stems(contractile,contractility).
  150my_stems(contrast,contrasty).
  151my_stems(convex,convexity).
  152my_stems(convex,convexness).
  153my_stems(copious,copiousness).
  154my_stems(cost,costly).
  155my_stems(costly,costliness).
  156my_stems(countless,countlessness).
  157my_stems(cover,coverage).
  158my_stems(crooked,crookedness).
  159my_stems(cubic,cubicity).
  160my_stems(curl,curly).
  161my_stems(curly,curliness).
  162my_stems(current,currency).
  163my_stems(current,currentness).
  164my_stems(curtail,curtailment).
  165my_stems(curve,curvature).
  166my_stems(curve,curvey).
  167my_stems(cutis,cutaneal).
  168my_stems(cylindrical,cylindricality).
  169my_stems(cylindrical,cylindricalness).
  170my_stems(dead,deadness).
  171my_stems(dear,dearness).
  172my_stems(decelerate,deceleration).
  173my_stems(decussate,decussation).
  174my_stems(deep,deepness).
  175my_stems(defenceless,defencelessness).
  176my_stems(defenseless,defenselessness).
  177my_stems(defensible,defensibility).
  178my_stems(deficient,deficiency).
  179my_stems(deliberate,deliberateness).
  180my_stems(dense,denseness).
  181my_stems(desirable,desirability).
  182my_stems(desirable,desirableness).
  183my_stems(destructible,destructibility).
  184my_stems(destructive,destructiveness).
  185my_stems(deterge,detergence).
  186my_stems(deterge,detergency).
  187my_stems(detergent,detergence).
  188my_stems(detergent,detergency).
  189my_stems(dextral,dextrality).
  190my_stems(diameter,diametral).
  191my_stems(diameter,diametric).
  192my_stems(diameter,diametrical).
  193my_stems(diffuse,diffuseness).
  194my_stems(dimensional,dimensionality).
  195my_stems(diminutive,diminutiveness).
  196my_stems(directional,directionality).
  197my_stems(directive,directiveness).
  198my_stems(directive,directivity).
  199my_stems(disadvantage,disadvantageous).
  200my_stems(discretion,discretionary).
  201my_stems(dispensable,dispensability).
  202my_stems(dispensable,dispensableness).
  203my_stems(disseminate,dissemination).
  204my_stems(distant,distance).
  205my_stems(domestic,domesticity).
  206my_stems(dominate,dominance).
  207my_stems(down,downy).
  208my_stems(dreary,dreariness).
  209my_stems(dull,dullness).
  210my_stems(durable,durability).
  211my_stems(dwarfish,dwarfishness).
  212my_stems(early,earliness).
  213my_stems(eccentric,eccentricity).
  214my_stems(effective,effectiveness).
  215my_stems(effective,effectivity).
  216my_stems(effectual,effectuality).
  217my_stems(effectual,effectualness).
  218my_stems(efficacious,efficaciousness).
  219my_stems(efficacy,efficacious).
  220my_stems(elevate,elevation).
  221my_stems(elliptic,ellipticity).
  222my_stems(elongate,elongation).
  223my_stems(empty,emptiness).
  224my_stems(endless,endlessness).
  225my_stems(endothelium,endothelial).
  226my_stems(enduring,enduringness).
  227my_stems(enervate,enervation).
  228my_stems(enfranchise,enfranchisement).
  229my_stems(enjoy,enjoyment).
  230my_stems(enormous,enormity).
  231my_stems(enormous,enormousness).
  232my_stems(entitle,entitlement).
  233my_stems(ephemeral,ephemerality).
  234my_stems(ephemeral,ephemeralness).
  235my_stems(epidermis,epidermal).
  236my_stems(epidermis,epidermic).
  237my_stems(epithelium,epithelial).
  238my_stems(erect,erectness).
  239my_stems(essential,essentiality).
  240my_stems(essential,essentialness).
  241my_stems(everlasting,everlastingness).
  242my_stems(evert,eversion).
  243my_stems(exceed,exceedance).
  244my_stems(excessive,excessiveness).
  245my_stems(executable,executability).
  246my_stems(exiguous,exiguity).
  247my_stems(exorbitant,exorbitance).
  248my_stems(expedient,expedience).
  249my_stems(expedient,expediency).
  250my_stems(expedition,expeditious).
  251my_stems(expeditious,expeditiousness).
  252my_stems(expensive,expensiveness).
  253my_stems(expose,exposure).
  254my_stems(extensive,extensiveness).
  255my_stems(external,externality).
  256my_stems(extravagant,extravagance).
  257my_stems(far,farawayness).
  258my_stems(far,farness).
  259my_stems(fast,fastness).
  260my_stems(favorable,favorableness).
  261my_stems(favourable,favourableness).
  262my_stems(feasible,feasibility).
  263my_stems(feasible,feasibleness).
  264my_stems(feckless,fecklessness).
  265my_stems(fertile,fertility).
  266my_stems(few,fewness).
  267my_stems(fine,fineness).
  268my_stems(finite,finiteness).
  269my_stems(fit,fitness).
  270my_stems(flat,flatness).
  271my_stems(fleet,fleetness).
  272my_stems(fleeting,fleetingness).
  273my_stems(flimsy,flimsiness).
  274my_stems(forward,forwardness).
  275my_stems(fragile,fragility).
  276my_stems(frangible,frangibility).
  277my_stems(frangible,frangibleness).
  278my_stems(frigid,frigidity).
  279my_stems(frigid,frigidness).
  280my_stems(fruitful,fruitfulness).
  281my_stems(fruitless,fruitlessness).
  282my_stems(fugacious,fugaciousness).
  283my_stems(fugacity,fugacious).
  284my_stems(full,fullness).
  285my_stems(functional,functionality).
  286my_stems(futile,futility).
  287my_stems(future,futurity).
  288my_stems(fuzz,fuzzy).
  289my_stems(gentle,gentleness).
  290my_stems(germ,germinate).
  291my_stems(glabella,glabellar).
  292my_stems(glib,glibness).
  293my_stems(globose,globosity).
  294my_stems(globular,globularness).
  295my_stems(glomerulus,glomerular).
  296my_stems(good,goodness).
  297my_stems(gradual,graduality).
  298my_stems(gradual,gradualness).
  299my_stems(grand,grandness).
  300my_stems(great,greatness).
  301my_stems(hair,hairy).
  302my_stems(handed,handedness).
  303my_stems(harmful,harmfulness).
  304my_stems(hasty,hastiness).
  305my_stems(heavy,heaviness).
  306my_stems(helpful,helpfulness).
  307my_stems(helpless,helplessness).
  308my_stems(high,highness).
  309my_stems(historical,historicalness).
  310my_stems(horizontal,horizontality).
  311my_stems(humor,humorist).
  312my_stems(humor,humorous).
  313my_stems(humour,humourist).
  314my_stems(humour,humourous).
  315my_stems(hurried,hurriedness).
  316my_stems(hydrophobic,hydrophobicity).
  317my_stems(idealist,idealism).
  318my_stems(idle,idleness).
  319my_stems(illustrious,illustriousness).
  320my_stems(immediate,immediateness).
  321my_stems(immense,immenseness).
  322my_stems(immense,immensity).
  323my_stems(immoderate,immoderateness).
  324my_stems(immortal,immortality).
  325my_stems(imperishable,imperishability).
  326my_stems(impermanent,impermanence).
  327my_stems(impermanent,impermanency).
  328my_stems(important,importance).
  329my_stems(impotent,impotence).
  330my_stems(impotent,impotency).
  331my_stems(impracticable,impracticability).
  332my_stems(impracticable,impracticableness).
  333my_stems(impractical,impracticality).
  334my_stems(impuissant,impuissance).
  335my_stems(inadvisable,inadvisability).
  336my_stems(inauspicious,inauspiciousness).
  337my_stems(incapable,incapability).
  338my_stems(incessant,incessancy).
  339my_stems(incessant,incessantness).
  340my_stems(incisive,incisiveness).
  341my_stems(incline,inclination).
  342my_stems(incompetent,incompetence).
  343my_stems(incompetent,incompetency).
  344my_stems(inconsequent,inconsequence).
  345my_stems(increment,incremental).
  346my_stems(indestructible,indestructibility).
  347my_stems(indispensable,indispensability).
  348my_stems(indispensable,indispensableness).
  349my_stems(ineffective,ineffectiveness).
  350my_stems(ineffectual,ineffectuality).
  351my_stems(ineffectual,ineffectualness).
  352my_stems(inefficacious,inefficaciousness).
  353my_stems(inessential,inessentiality).
  354my_stems(inexpedient,inexpedience).
  355my_stems(inexpedient,inexpediency).
  356my_stems(inexpensive,inexpensiveness).
  357my_stems(infeasible,infeasibility).
  358my_stems(infinite,infiniteness).
  359my_stems(influence,influential).
  360my_stems(infrequent,infrequency).
  361my_stems(injurious,injuriousness).
  362my_stems(innervate,innervation).
  363my_stems(innumerable,innumerableness).
  364my_stems(inordinate,inordinateness).
  365my_stems(inosculate,inosculation).
  366my_stems(insidious,insidiousness).
  367my_stems(insignificant,insignificance).
  368my_stems(insipid,insipidness).
  369my_stems(insoluble,insolubility).
  370my_stems(instant,instancy).
  371my_stems(instantaneous,instantaneousness).
  372my_stems(instrumental,instrumentality).
  373my_stems(insubstantial,insubstantiality).
  374my_stems(insufficient,insufficiency).
  375my_stems(integument,integumental).
  376my_stems(integument,integumentary).
  377my_stems(interesting,interestingness).
  378my_stems(international,internationality).
  379my_stems(internationalism,internationalistic).
  380my_stems(interoperable,interoperability).
  381my_stems(interstice,interstitial).
  382my_stems(inutile,inutility).
  383my_stems(invaluable,invaluableness).
  384my_stems(inward,inwardness).
  385my_stems(irregular,irregularity).
  386my_stems(irresistible,irresistibility).
  387my_stems(irresistible,irresistibleness).
  388my_stems(isometry,isometric).
  389my_stems(jejune,jejuneness).
  390my_stems(jejune,jejunity).
  391my_stems(large,extensiveness).
  392my_stems(large,largeness).
  393my_stems(lasting,lastingness).
  394my_stems(late,lateness).
  395my_stems(latitude,latitudinarian).
  396my_stems(lavish,lavishness).
  397my_stems(lean,leanness).
  398my_stems(leisurely,leisureliness).
  399my_stems(length,lengthy).
  400my_stems(lengthy,lengthiness).
  401my_stems(lentigo,lentiginous).
  402my_stems(liable,liability).
  403my_stems(limit,limitation).
  404my_stems(limitless,limitlessness).
  405my_stems(linear,linearity).
  406my_stems(little,littleness).
  407my_stems(lobular,lobularity).
  408my_stems(lofty,loftiness).
  409my_stems(long,longness).
  410my_stems(lopsided,lopsidedness).
  411my_stems(lord,lordship).
  412my_stems(low,lowness).
  413my_stems(lush,lushness).
  414my_stems(luxuriant,luxuriance).
  415my_stems(luxury,luxuriate).
  416my_stems(luxury,luxurious).
  417my_stems(macula,maculate).
  418my_stems(magnify,magnitude).
  419my_stems(major,majority).
  420my_stems(marginal,marginality).
  421my_stems(massive,massiveness).
  422my_stems(maximum,maximise).
  423my_stems(maximum,maximize).
  424my_stems(meager,meagerness).
  425my_stems(meagre,meagreness).
  426my_stems(meaningful,meaningfulness).
  427my_stems(measurable,measurability).
  428my_stems(mindless,mindlessness).
  429my_stems(minor,minority).
  430my_stems(minute,minuteness).
  431my_stems(misalign,misalignment).
  432my_stems(misplace,misplacement).
  433my_stems(moderate,moderateness).
  434my_stems(moderate,moderation).
  435my_stems(modern,modernity).
  436my_stems(modern,modernness).
  437my_stems(modernism,modernistic).
  438my_stems(modest,modestness).
  439my_stems(moment,momentous).
  440my_stems(momentous,momentousness).
  441my_stems(mortal,mortality).
  442my_stems(much,muchness).
  443my_stems(multiple,multiplicity).
  444my_stems(multitudinous,multitudinousness).
  445my_stems(narrow,narrowing).
  446my_stems(narrow,narrowness).
  447my_stems(near,nearness).
  448my_stems(negative,negativeness).
  449my_stems(negative,negativity).
  450my_stems(negativist,negativism).
  451my_stems(newsworthy,newsworthiness).
  452my_stems(northern,northernness).
  453my_stems(numerous,numerosity).
  454my_stems(numerous,numerousness).
  455my_stems(oblate,oblateness).
  456my_stems(oblique,obliqueness).
  457my_stems(oblong,oblongness).
  458my_stems(open,opening).
  459my_stems(open,openness).
  460my_stems(optimism,optimistic).
  461my_stems(optimist,optimism).
  462my_stems(optimum,optimise).
  463my_stems(optimum,optimize).
  464my_stems(orientalist,orientalism).
  465my_stems(orthogonal,orthogonality).
  466my_stems(outrageous,outrageousness).
  467my_stems(overabundant,overabundance).
  468my_stems(overmuch,overmuchness).
  469my_stems(paltry,paltriness).
  470my_stems(past,pastness).
  471my_stems(pelt,pelting).
  472my_stems(penetrate,penetration).
  473my_stems(perdurable,perdurability).
  474my_stems(permanent,permanence).
  475my_stems(permanent,permanency).
  476my_stems(perpendicular,perpendicularity).
  477my_stems(perpetual,perpetuity).
  478my_stems(persistent,persistence).
  479my_stems(person,personify).
  480my_stems(persuasive,persuasiveness).
  481my_stems(pessimism,pessimistic).
  482my_stems(pessimist,pessimism).
  483my_stems(petite,petiteness).
  484my_stems(petty,pettiness).
  485my_stems(place,placement).
  486my_stems(plane,planeness).
  487my_stems(plenteous,plenteousness).
  488my_stems(plentiful,plentifulness).
  489my_stems(plenty,plenteous).
  490my_stems(plethora,plethoric).
  491my_stems(poignant,poignancy).
  492my_stems(pointed,pointedness).
  493my_stems(pointless,pointlessness).
  494my_stems(poison,poisonous).
  495my_stems(ponderous,ponderousness).
  496my_stems(poor,poorness).
  497my_stems(pore,poriferous).
  498my_stems(positive,positiveness).
  499my_stems(positive,positivity).
  500my_stems(posterior,posteriority).
  501my_stems(posture,postural).
  502my_stems(powerful,powerfulness).
  503my_stems(powerless,powerlessness).
  504my_stems(practicable,practicability).
  505my_stems(practicable,practicableness).
  506my_stems(practical,practicality).
  507my_stems(pragmatic,pragmatism).
  508my_stems(pragmatism,pragmatical).
  509my_stems(pragmatist,pragmatism).
  510my_stems(precede,precedence).
  511my_stems(precede,precedency).
  512my_stems(precedent,precedence).
  513my_stems(precious,preciousness).
  514my_stems(precipitant,precipitance).
  515my_stems(precipitant,precipitancy).
  516my_stems(precipitate,precipitateness).
  517my_stems(precipitate,precipitation).
  518my_stems(precipitous,precipitousness).
  519my_stems(preempt,preemption).
  520my_stems(preponderant,preponderance).
  521my_stems(preponderate,preponderance).
  522my_stems(present,presentness).
  523my_stems(press,pressure).
  524my_stems(prevail,prevalence).
  525my_stems(price,pricey).
  526my_stems(priceless,pricelessness).
  527my_stems(prior,priority).
  528my_stems(priority,prioritize).
  529my_stems(probability,probabilistic).
  530my_stems(probable,probability).
  531my_stems(procrastinate,procrastination).
  532my_stems(productive,productiveness).
  533my_stems(productive,productivity).
  534my_stems(proficient,proficiency).
  535my_stems(profitable,profitability).
  536my_stems(profitable,profitableness).
  537my_stems(profound,profoundness).
  538my_stems(profound,profundity).
  539my_stems(profuse,profuseness).
  540my_stems(prolong,prolongation).
  541my_stems(prominent,prominence).
  542my_stems(prompt,promptness).
  543my_stems(propitious,propitiousness).
  544my_stems(protract,protraction).
  545my_stems(proximal,proximity).
  546my_stems(puissant,puissance).
  547my_stems(punctual,punctuality).
  548my_stems(puny,puniness).
  549my_stems(purposeful,purposefulness).
  550my_stems(purposeless,aimlessness).
  551my_stems(purposeless,purposelessness).
  552my_stems(pushy,pushiness).
  553my_stems(quantifiable,quantifiability).
  554my_stems(quick,quickness).
  555my_stems(ramify,ramification).
  556my_stems(rank,rankness).
  557my_stems(rapid,rapidity).
  558my_stems(rapid,rapidness).
  559my_stems(rare,rareness).
  560my_stems(reasonable,reasonableness).
  561my_stems(recent,recentness).
  562my_stems(rectangular,rectangularity).
  563my_stems(redundant,redundance).
  564my_stems(redundant,redundancy).
  565my_stems(regular,regularity).
  566my_stems(relative,relativity).
  567my_stems(relativity,relativistic).
  568my_stems(remote,remoteness).
  569my_stems(resistant,resistance).
  570my_stems(resourceful,resourcefulness).
  571my_stems(responsive,responsiveness).
  572my_stems(retard,retardation).
  573my_stems(rich,richness).
  574my_stems(romantic,romanticism).
  575my_stems(romanticist,romanticism).
  576my_stems(roomy,roominess).
  577my_stems(rotate,rotation).
  578my_stems(rotund,rotundity).
  579my_stems(rotund,rotundness).
  580my_stems(round,roundness).
  581my_stems(rounded,roundedness).
  582my_stems(runty,runtiness).
  583my_stems(scalable,scalability).
  584my_stems(scant,scantness).
  585my_stems(scanty,scantiness).
  586my_stems(scarce,scarceness).
  587my_stems(scarce,scarcity).
  588my_stems(sciolism,sciolistic).
  589my_stems(sciolist,sciolism).
  590my_stems(seasonable,seasonableness).
  591my_stems(selective,selectivity).
  592my_stems(senseless,senselessness).
  593my_stems(sensible,sensibleness).
  594my_stems(sequence,sequential).
  595my_stems(serviceable,serviceability).
  596my_stems(serviceable,serviceableness).
  597my_stems(shallow,shallowness).
  598my_stems(shit,shitty).
  599my_stems(shoddy,shoddiness).
  600my_stems(short,shortness).
  601my_stems(shrill,shrillness).
  602my_stems(significant,significance).
  603my_stems(simultaneous,simultaneity).
  604my_stems(simultaneous,simultaneousness).
  605my_stems(sinistral,sinistrality).
  606my_stems(sizeable,sizeableness).
  607my_stems(skew,skewness).
  608my_stems(skin,skinny).
  609my_stems(slender,slenderness).
  610my_stems(slick,slickness).
  611my_stems(slight,slightness).
  612my_stems(slim,slimness).
  613my_stems(slow,slowing).
  614my_stems(slow,slowness).
  615my_stems(sluggish,sluggishness).
  616my_stems(small,smallness).
  617my_stems(solarise,solarisation).
  618my_stems(solarize,solarization).
  619my_stems(soluble,solubility).
  620my_stems(solvable,solvability).
  621my_stems(sorry,sorriness).
  622my_stems(sound,sounding).
  623my_stems(sound,soundness).
  624my_stems(southern,southernness).
  625my_stems(spacious,spaciousness).
  626my_stems(spare,spareness).
  627my_stems(sparse,sparseness).
  628my_stems(sparse,sparsity).
  629my_stems(spatial,spatiality).
  630my_stems(special,speciality).
  631my_stems(spectrum,spectral).
  632my_stems(speed,speedy).
  633my_stems(speedy,speediness).
  634my_stems(spheric,sphericity).
  635my_stems(spherical,sphericalness).
  636my_stems(sprawl,sprawling).
  637my_stems(sprawl,sprawly).
  638my_stems(square,squareness).
  639my_stems(squat,squatness).
  640my_stems(stark,starkness).
  641my_stems(steep,steepness).
  642my_stems(stoma,stomatal).
  643my_stems(stoma,stomatous).
  644my_stems(straight,straightness).
  645my_stems(stubby,stubbiness).
  646my_stems(stuffy,stuffiness).
  647my_stems(stunted,stuntedness).
  648my_stems(subsequent,subsequence).
  649my_stems(subsequent,subsequentness).
  650my_stems(succeed,succession).
  651my_stems(successive,successiveness).
  652my_stems(sudden,suddenness).
  653my_stems(suffice,sufficiency).
  654my_stems(sufficient,sufficiency).
  655my_stems(suffrage,suffragette).
  656my_stems(suffrage,suffragist).
  657my_stems(sumptuous,sumptuosity).
  658my_stems(sumptuous,sumptuousness).
  659my_stems(superabundant,superabundance).
  660my_stems(superficial,superficiality).
  661my_stems(superfluous,superfluity).
  662my_stems(superior,superiority).
  663my_stems(supplement,supplemental).
  664my_stems(supplement,supplementary).
  665my_stems(supplement,supplementation).
  666my_stems(swift,swiftness).
  667my_stems(symmetrical,symmetricalness).
  668my_stems(symmetry,symmetric).
  669my_stems(symmetry,symmetrise).
  670my_stems(symmetry,symmetrize).
  671my_stems(tall,tallness).
  672my_stems(tame,tameness).
  673my_stems(tardy,tardiness).
  674my_stems(tedious,tediousness).
  675my_stems(teeming,teemingness).
  676my_stems(temporary,temporariness).
  677my_stems(tentacle,tentacular).
  678my_stems(thick,thickness).
  679my_stems(thin,thinness).
  680my_stems(tight,tightness).
  681my_stems(timely,timeliness).
  682my_stems(tiny,tininess).
  683my_stems(tiresome,tiresomeness).
  684my_stems(title,titulary).
  685my_stems(topography,topographic).
  686my_stems(topography,topographical).
  687my_stems(totipotent,totipotence).
  688my_stems(totipotent,totipotency).
  689my_stems(transient,transience).
  690my_stems(transient,transiency).
  691my_stems(transitory,transitoriness).
  692my_stems(trashy,trashiness).
  693my_stems(trenchant,trenchancy).
  694my_stems(triangular,triangularity).
  695my_stems(trivial,triviality).
  696my_stems(turnover,'turn over').
  697my_stems(unbounded,unboundedness).
  698my_stems(undesirable,undesirability).
  699my_stems(unfavorable,unfavorableness).
  700my_stems(unfavourable,unfavourableness).
  701my_stems(unfeasible,unfeasibility).
  702my_stems(unfit,unfitness).
  703my_stems(unhurried,unhurriedness).
  704my_stems(unimportant,unimportance).
  705my_stems(uninteresting,uninterestingness).
  706my_stems(unpersuasive,unpersuasiveness).
  707my_stems(unpointed,unpointedness).
  708my_stems(unproductive,unproductiveness).
  709my_stems(unprofitable,unprofitability).
  710my_stems(unprofitable,unprofitableness).
  711my_stems(unpropitious,unpropitiousness).
  712my_stems(unprotected,unprotectedness).
  713my_stems(unresponsive,unresponsiveness).
  714my_stems(unseasonable,unseasonableness).
  715my_stems(unsound,unsoundness).
  716my_stems(untimely,untimeliness).
  717my_stems(upright,uprightness).
  718my_stems(usable,usableness).
  719my_stems(useable,useableness).
  720my_stems(useableness,serviceable).
  721my_stems(useful,usefulness).
  722my_stems(useless,uselessness).
  723my_stems(usufruct,usufructuary).
  724my_stems(utility,utilitarian).
  725my_stems(valuable,valuableness).
  726my_stems(value,evaluate).
  727my_stems(valueless,valuelessness).
  728my_stems(vapid,vapidity).
  729my_stems(vapid,vapidness).
  730my_stems(vascular,vascularity).
  731my_stems(vast,vastness).
  732my_stems(verdant,verdancy).
  733my_stems(vertical,verticality).
  734my_stems(vertical,verticalness).
  735my_stems(viable,viability).
  736my_stems(virulent,virulence).
  737my_stems(virulent,virulency).
  738my_stems(vital,vitalness).
  739my_stems(vitalness,indispensable).
  740my_stems(vivid,vividness).
  741my_stems(voiceless,voicelessness).
  742my_stems(volume,voluminous).
  743my_stems(voluminous,voluminosity).
  744my_stems(voluminous,voluminousness).
  745my_stems(voluptuous,voluptuousness).
  746my_stems(vulnerable,vulnerability).
  747my_stems(watery,wateriness).
  748my_stems(wavy,waviness).
  749my_stems(waxy,waxiness).
  750my_stems(weak,weakness).
  751my_stems(wee,weeness).
  752my_stems(weight,weighty).
  753my_stems(weighty,weightiness).
  754my_stems(wide,wideness).
  755my_stems(wise,wiseness).
  756my_stems(woodsy,woodsiness).
  757my_stems(woody,woodiness).
  758my_stems(worth,worthy).
  759my_stems(worthless,worthlessness).
  760my_stems(worthwhile,worthwhileness).
  761*/
  762
  763s_id(ID1,SN,W1,POS1):- s(ID1,SN,W1,POS1,_X1,_Y1).
  764s_id(ID1,W1,POS1):- s(ID1,1,W1,POS1,_X1,_Y1).
  765
  766wdl1(W1,POS1,W2,POS2,ant):- ant(ID1,SN1,ID2,SN2),s_id(ID1,SN1,W1,POS1),s_id(ID2,SN2,W2,POS2).
  767
  768wdl2(W1,POS1,W2,POS2,How):- wdl1(W1,POS1,W2,POS2,How).
  769wdl2(W1,POS1,W2,POS2,hyp):- hyp(ID2,ID1),s_id(ID1,W1,POS1),s_id(ID2,W2,POS2).
  770wdl2(W1,POS1,W2,POS2,Hypr):- (hypr==Hypr;nonvar(W2)),hyp(ID1,ID2),s_id(ID1,W1,POS1),s_id(ID2,W2,POS2).
  771wdl2(W1,POS1,W2,POS2,der):- der(ID1,SN1,ID2,SN2),s_id(ID1,SN1,W1,POS1),s_id(ID2,SN2,W2,POS2).
  772
  773t1(W1,W2,POS,HOW):- no_repeats(W2,wdl(W1:v,W2:POS,[ant|HOW])),(atom_contains(W1,W2);atom_contains(W2,W1)).
  774
  775
  776t2(W1,W2,POS):- (var(W1),nonvar(W2)),!,t2(W2,W1,POS).
  777t2(W1,W2,POS1:POS2):- (var(W1),var(W2)),!,no_repeats(W2,wdl(W1:POS1,W2:POS2,[ant])),longer(W1,W2).
  778t2(W1,W2,POS):- t3(W1,W2,POS)*->true;(t4(W1,W3,POS),W3=W2).
  779
  780t3(W1,W2,POS):- (nonvar(W1),nonvar(W2)),!,t2(W2,WM,_),t2(W1,WM,POS).
  781t3(W1,W2,POS1:POS2):- no_repeats(W2,wdl(W1:POS1,W2:POS2,[ant])),nop(word_overlap(W1,W2)).
  782
  783t4(W1,W2,POS):- (nonvar(W1),nonvar(W2)),!,t2(W2,WM,_),t3(W1,WM,POS).
  784% t4(W1,W2,POS):- nonvar(W1),!,t3(W22,WM,_),t3(W1,WM,POS),W2=W22.
  785t4(W1,W2,POS1:POS2):- no_repeats(W2,wdl(W1:POS1,W2:POS2,_)),nop(word_overlap(W1,W2)).
  786
  787
  788wdl(W1:POS1,W2:POS2,[HOW1,HOW2]):- 
  789  dif(W1,W2),wdl2(W1,POS1,WM,POSM,HOW1),
  790  (HOW1==der->HOW2=ant;((HOW1==ant->dif(HOW2,ant);(HOW1==hyp->dif(HOW2,hyp);true)))),
  791  wdl2(WM,POSM,W2,POS2,HOW2).
  792wdl(W1:POS1,W2:POS2,[HOW]):- wdl2(W1,POS1,W2,POS2,HOW).
  793%wdl(W1:POS1,W2:POS2,[HOW1,HOW2]):- wdl1(W1,POS1,WM,POSM,HOW1),wdl1(WM,POSM,W2,POS2,HOW2).
  794%wdl(W1,POS1,W2,POS2,[HOW1,HOW2]):- wdl2(W1,POS1,WM,POSM,HOW),wdl1(WM,POSM,W2,POS2,HOW).
  795/*
  796ant,ant
  797der,ant
  798ant,hyp
  799*/
  800wn_face(vgp/4).
  801wn_face(syntax/3).
  802wn_face(sk/3).
  803wn_face(sim/2).
  804wn_face(sa/4).
  805wn_face(s/6).
  806wn_face(ppl/4).
  807wn_face(per/4).
  808wn_face(ms/2).
  809wn_face(mp/2).
  810wn_face(mm/2).
  811wn_face(ins/2).
  812wn_face(hyp/2).
  813wn_face(g/2).
  814wn_face(fr/3).
  815wn_face(ent/2).
  816wn_face(der/4).
  817wn_face(cs/2).
  818wn_face(cls/5).
  819wn_face(at/2).
  820wn_face(ant/4).
  821
  822xl(ID1):- xlisting(ID1),forall(s_id(ID1,SN,W1,POS1),dmsg(s_id(ID1,SN,W1,POS1))),forall(g(ID1,Info),dmsg(g(ID1,Info))).
  823
  824
  825opposite(n,artifact,'natural object',_80064).
  826opposite(n,overachievement,underachievement,_80064).
  827opposite(n,appearance,disappearance,_80064).
  828opposite(n,retreat,advance,_80064).
  829opposite(n,embarkation,disembarkation,_80064).
  830opposite(n,passing,failing,_80064).
  831opposite(n,'put option','call option',_80064).
  832opposite(n,best,worst,_80064).
  833opposite(n,'foul ball','fair ball',_80064).
  834opposite(n,loosening,tightening,_80064).
  835opposite(n,monetization,demonetization,_80064).
  836opposite(n,'split ticket','straight ticket',_80064).
  837opposite(n,'earned run','unearned run',_80064).
  838opposite(n,demotion,promotion,_80064).
  839opposite(n,stillbirth,'live birth',_80064).
  840opposite(n,start,finish,_80064).
  841opposite(n,activation,deactivation,_80064).
  842opposite(n,contamination,decontamination,_80064).
  843opposite(n,'rising trot','sitting trot',_80064).
  844opposite(n,'domestic flight','international flight',_80064).
  845opposite(n,deceleration,acceleration,_80064).
  846opposite(n,opening,closing,_80064).
  847opposite(n,pronation,supination,_80064).
  848opposite(n,minimization,maximization,_80064).
  849opposite(n,compression,decompression,_80064).
  850opposite(n,weakening,strengthening,_80064).
  851opposite(n,dilution,concentration,_80064).
  852opposite(n,increase,decrease,_80064).
  853opposite(n,addition,subtraction,_80064).
  854opposite(n,depreciation,appreciation,_80064).
  855opposite(n,expansion,contraction,_80064).
  856opposite(n,inflation,deflation,_80064).
  857opposite(n,union,disunion,_80064).
  858opposite(n,tribalization,detribalization,_80064).
  859opposite(n,tribalisation,detribalisation,_80064).
  860opposite(n,flexion,extension,_80064).
  861opposite(n,widening,narrowing,_80064).
  862opposite(n,activity,inactivity,_80064).
  863opposite(n,'day game','night game',_80064).
  864opposite(n,'home game','away game',_80064).
  865opposite(n,softball,hardball,_80064).
  866opposite(n,volley,'ground stroke',_80064).
  867opposite(n,'minor surgery','major surgery',_80064).
  868opposite(n,allopathy,homeopathy,_80064).
  869opposite(n,loading,unloading,_80064).
  870opposite(n,'actual sin','original sin',_80064).
  871opposite(n,'venial sin','mortal sin',_80064).
  872opposite(n,'petit larceny','grand larceny',_80064).
  873opposite(n,hypopnea,hyperpnea,_80064).
  874opposite(n,'assortative mating','disassortative mating',_80064).
  875opposite(n,assembly,disassembly,_80064).
  876opposite(n,continuance,discontinuance,_80064).
  877opposite(n,continuation,discontinuation,_80064).
  878opposite(n,uptick,downtick,_80064).
  879opposite(n,retail,wholesale,_80064).
  880opposite(n,payment,nonpayment,_80064).
  881opposite(n,criminalization,decriminalization,_80064).
  882opposite(n,criminalisation,decriminalisation,_80064).
  883opposite(n,enfranchisement,disenfranchisement,_20).
  884opposite(n,classification,declassification,_20).
  885opposite(n,nationalization,denationalization,_20).
  886opposite(n,mobilization,demobilization,_20).
  887opposite(n,arming,disarming,_20).
  888opposite(n,armament,disarmament,_20).
  889opposite(n,stabilization,destabilization,_20).
  890opposite(n,stabilisation,destabilisation,_20).
  891opposite(n,obedience,disobedience,_20).
  892opposite(n,reversal,affirmation,_20).
  893opposite(n,'judgment in rem','judgment in personam',_20).
  894opposite(n,'special verdict','general verdict',_20).
  895opposite(n,acquittal,conviction,_20).
  896opposite(n,defense,prosecution,_20).
  897opposite(n,segregation,integration,_20).
  898opposite(n,cooperation,competition,_20).
  899opposite(n,conformity,nonconformity,_20).
  900opposite(n,compliance,noncompliance,_20).
  901opposite(n,observance,nonobservance,_20).
  902opposite(n,service,disservice,_20).
  903opposite(n,approval,disapproval,_20).
  904opposite(n,attendance,nonattendance,_20).
  905opposite(n,absence,presence,_20).
  906opposite(n,centralization,decentralization,_20).
  907opposite(n,engagement,'non-engagement',_20).
  908opposite(n,participation,nonparticipation,_20).
  909opposite(n,involvement,'non-involvement',_20).
  910opposite(n,male,female,_20).
  911opposite(n,host,parasite,_20).
  912opposite(n,eukaryote,prokaryote,_20).
  913opposite(n,'soft-finned fish','spiny-finned fish',_20).
  914opposite(n,ratite,carinate,_20).
  915opposite(n,diapsid,anapsid,_20).
  916opposite(n,'diving duck','dabbling duck',_20).
  917opposite(n,'zygodactyl foot','heterodactyl foot',_20).
  918opposite(n,'odd-toed ungulate','even-toed ungulate',_20).
  919opposite(n,'homocercal fin','heterocercal fin',_20).
  920opposite(n,'plantigrade mammal','digitigrade mammal',_20).
  921opposite(n,anode,cathode,_20).
  922opposite(n,infield,outfield,_20).
  923opposite(n,'low relief','high relief',_20).
  924opposite(n,'dedicated file server','non-dedicated file server',_20).
  925opposite(n,'dumb bomb','smart bomb',_20).
  926opposite(n,'fast reactor','thermal reactor',_20).
  927opposite(n,'generic drug','brand-name drug',_20).
  928opposite(n,'hand mower','power mower',_20).
  929opposite(n,import,export,_20).
  930opposite(n,'in-basket','out-basket',_20).
  931opposite(n,larboard,starboard,_20).
  932opposite(n,local,express,_20).
  933opposite(n,mobile,stabile,_20).
  934opposite(n,'open circuit','closed circuit',_20).
  935opposite(n,overgarment,undergarment,_20).
  936opposite(n,'prescription drug','over-the-counter drug',_20).
  937opposite(n,'prescription medicine','over-the-counter medicine',_20).
  938opposite(n,'ready-made','custom-made',_20).
  939opposite(n,rear,front,_20).
  940opposite(n,reverse,obverse,_20).
  941opposite(n,rotor,stator,_20).
  942opposite(n,'slow lane','fast lane',_20).
  943opposite(n,'soft drug','hard drug',_20).
  944opposite(n,studio,location,_20).
  945opposite(n,submersible,'surface ship',_20).
  946opposite(n,synergist,antagonist,_20).
  947opposite(n,tail,head,_20).
  948opposite(n,'taper file','blunt file',_20).
  949opposite(n,'volatile storage','non-volatile storage',_20).
  950opposite(n,'volatile storage','nonvolatile storage',_20).
  951opposite(n,'voltaic cell','electrolytic cell',_20).
  952opposite(n,'wet-bulb thermometer','dry-bulb thermometer',_20).
  953opposite(n,'wet fly','dry fly',_20).
  954opposite(n,white,black,_20).
  955opposite(n,inwardness,outwardness,_20).
  956opposite(n,worldliness,otherworldliness,_20).
  957opposite(n,introversion,extraversion,_20).
  958opposite(n,emotionality,unemotionality,_20).
  959opposite(n,cheerfulness,uncheerfulness,_20).
  960opposite(n,activeness,inactiveness,_20).
  961opposite(n,permissiveness,unpermissiveness,_20).
  962opposite(n,patience,impatience,_20).
  963opposite(n,agreeableness,disagreeableness,_20).
  964opposite(n,'ill nature','good nature',_20).
  965opposite(n,willingness,unwillingness,_20).
  966opposite(n,frivolity,seriousness,_20).
  967opposite(n,communicativeness,uncommunicativeness,_20).
  968opposite(n,sociability,unsociability,_20).
  969opposite(n,openness,closeness,_20).
  970opposite(n,friendliness,unfriendliness,_20).
  971opposite(n,approachability,unapproachability,_20).
  972opposite(n,congeniality,uncongeniality,_20).
  973opposite(n,neighborliness,unneighborliness,_20).
  974opposite(n,hospitableness,inhospitableness,_20).
  975opposite(n,adaptability,unadaptability,_20).
  976opposite(n,flexibility,inflexibility,_20).
  977opposite(n,thoughtfulness,unthoughtfulness,_20).
  978opposite(n,attentiveness,inattentiveness,_20).
  979opposite(n,carefulness,carelessness,_20).
  980opposite(n,mindfulness,unmindfulness,_20).
  981opposite(n,heedfulness,heedlessness,_20).
  982opposite(n,caution,incaution,_20).
  983opposite(n,wariness,unwariness,_20).
  984opposite(n,femininity,masculinity,_20).
  985opposite(n,trustworthiness,untrustworthiness,_20).
  986opposite(n,trustiness,untrustiness,_20).
  987opposite(n,responsibility,irresponsibility,_20).
  988opposite(n,responsibleness,irresponsibleness,_20).
  989opposite(n,dependability,undependability,_20).
  990opposite(n,dependableness,undependableness,_20).
  991opposite(n,reliability,unreliability,_20).
  992opposite(n,reliableness,unreliableness,_20).
  993opposite(n,conscientiousness,unconscientiousness,_20).
  994opposite(n,hairiness,hairlessness,_20).
  995opposite(n,beauty,ugliness,_20).
  996opposite(n,pleasingness,unpleasingness,_20).
  997opposite(n,attractiveness,unattractiveness,_20).
  998opposite(n,distinctness,indistinctness,_20).
  999opposite(n,opacity,clarity,_20).
 1000opposite(n,softness,sharpness,_20).
 1001opposite(n,acuteness,obtuseness,_20).
 1002opposite(n,conspicuousness,inconspicuousness,_20).
 1003opposite(n,obtrusiveness,unobtrusiveness,_20).
 1004opposite(n,ease,difficulty,_20).
 1005opposite(n,effortfulness,effortlessness,_20).
 1006opposite(n,compatibility,incompatibility,_20).
 1007opposite(n,congruity,incongruity,_20).
 1008opposite(n,congruousness,incongruousness,_20).
 1009opposite(n,suitability,unsuitability,_20).
 1010opposite(n,suitableness,unsuitableness,_20).
 1011opposite(n,appropriateness,inappropriateness,_20).
 1012opposite(n,felicity,infelicity,_20).
 1013opposite(n,aptness,inaptness,_20).
 1014opposite(n,appositeness,inappositeness,_20).
 1015opposite(n,fitness,unfitness,_20).
 1016opposite(n,eligibility,ineligibility,_20).
 1017opposite(n,insurability,uninsurability,_20).
 1018opposite(n,convenience,inconvenience,_20).
 1019opposite(n,opportuneness,inopportuneness,_20).
 1020opposite(n,accessibility,inaccessibility,_20).
 1021opposite(n,availability,unavailability,_20).
 1022opposite(n,superiority,inferiority,_20).
 1023opposite(n,'low quality','high quality',_20).
 1024opposite(n,reversibility,irreversibility,_20).
 1025opposite(n,variability,invariability,_20).
 1026opposite(n,variableness,invariableness,_20).
 1027opposite(n,variedness,unvariedness,_20).
 1028opposite(n,exchangeability,unexchangeability,_20).
 1029opposite(n,convertibility,inconvertibility,_20).
 1030opposite(n,changelessness,changeableness,_20).
 1031opposite(n,constancy,inconstancy,_20).
 1032opposite(n,mutability,immutability,_20).
 1033opposite(n,mutableness,immutableness,_20).
 1034opposite(n,alterability,unalterability,_20).
 1035opposite(n,sameness,difference,_20).
 1036opposite(n,similarity,dissimilarity,_20).
 1037opposite(n,likeness,unlikeness,_20).
 1038opposite(n,similitude,dissimilitude,_20).
 1039opposite(n,uniformity,nonuniformity,_20).
 1040opposite(n,homogeneity,heterogeneity,_20).
 1041opposite(n,consistency,inconsistency,_20).
 1042opposite(n,equality,inequality,_20).
 1043opposite(n,equivalence,nonequivalence,_20).
 1044opposite(n,evenness,unevenness,_20).
 1045opposite(n,certainty,uncertainty,_20).
 1046opposite(n,conclusiveness,inconclusiveness,_20).
 1047opposite(n,predictability,unpredictability,_20).
 1048opposite(n,probability,improbability,_20).
 1049opposite(n,likelihood,unlikelihood,_20).
 1050opposite(n,likeliness,unlikeliness,_20).
 1051opposite(n,factuality,counterfactuality,_20).
 1052opposite(n,concreteness,abstractness,_20).
 1053opposite(n,tangibility,intangibility,_20).
 1054opposite(n,palpability,impalpability,_20).
 1055opposite(n,materiality,immateriality,_20).
 1056opposite(n,corporeality,incorporeality,_20).
 1057opposite(n,substantiality,insubstantiality,_20).
 1058opposite(n,reality,unreality,_20).
 1059opposite(n,generality,particularity,_20).
 1060opposite(n,commonality,individuality,_20).
 1061opposite(n,simplicity,complexity,_20).
 1062opposite(n,regularity,irregularity,_20).
 1063opposite(n,steadiness,unsteadiness,_20).
 1064opposite(n,mobility,immobility,_20).
 1065opposite(n,motility,immotility,_20).
 1066opposite(n,movability,immovability,_20).
 1067opposite(n,movableness,immovableness,_20).
 1068opposite(n,tightness,looseness,_20).
 1069opposite(n,looseness,fixedness,_20).
 1070opposite(n,stability,instability,_20).
 1071opposite(n,stableness,unstableness,_20).
 1072opposite(n,pleasantness,unpleasantness,_20).
 1073opposite(n,niceness,nastiness,_20).
 1074opposite(n,credibility,incredibility,_20).
 1075opposite(n,plausibility,implausibility,_20).
 1076opposite(n,logicality,illogicality,_20).
 1077opposite(n,logicalness,illogicalness,_20).
 1078opposite(n,naturalness,unnaturalness,_20).
 1079opposite(n,affectedness,unaffectedness,_20).
 1080opposite(n,pretentiousness,unpretentiousness,_20).
 1081opposite(n,wholesomeness,unwholesomeness,_20).
 1082opposite(n,healthfulness,unhealthfulness,_20).
 1083opposite(n,salubrity,insalubrity,_20).
 1084opposite(n,salubriousness,insalubriousness,_20).
 1085opposite(n,satisfactoriness,unsatisfactoriness,_20).
 1086opposite(n,adequacy,inadequacy,_20).
 1087opposite(n,acceptability,unacceptability,_20).
 1088opposite(n,admissibility,inadmissibility,_20).
 1089opposite(n,permissibility,impermissibility,_20).
 1090opposite(n,ordinariness,extraordinariness,_20).
 1091opposite(n,expectedness,unexpectedness,_20).
 1092opposite(n,commonness,uncommonness,_20).
 1093opposite(n,usualness,unusualness,_20).
 1094opposite(n,familiarity,unfamiliarity,_20).
 1095opposite(n,nativeness,foreignness,_20).
 1096opposite(n,originality,unoriginality,_20).
 1097opposite(n,orthodoxy,unorthodoxy,_20).
 1098opposite(n,conventionality,unconventionality,_20).
 1099opposite(n,correctness,incorrectness,_20).
 1100opposite(n,wrongness,rightness,_20).
 1101opposite(n,accuracy,inaccuracy,_20).
 1102opposite(n,exactness,inexactness,_20).
 1103opposite(n,preciseness,impreciseness,_20).
 1104opposite(n,precision,imprecision,_20).
 1105opposite(n,errancy,inerrancy,_20).
 1106opposite(n,fallibility,infallibility,_20).
 1107opposite(n,worthiness,unworthiness,_20).
 1108opposite(n,popularity,unpopularity,_20).
 1109opposite(n,legality,illegality,_20).
 1110opposite(n,lawfulness,unlawfulness,_20).
 1111opposite(n,legitimacy,illegitimacy,_20).
 1112opposite(n,licitness,illicitness,_20).
 1113opposite(n,elegance,inelegance,_20).
 1114opposite(n,tastefulness,tastelessness,_20).
 1115opposite(n,urbanity,rusticity,_20).
 1116opposite(n,comprehensibility,incomprehensibility,_20).
 1117opposite(n,legibility,illegibility,_20).
 1118opposite(n,intelligibility,unintelligibility,_20).
 1119opposite(n,clarity,obscurity,_20).
 1120opposite(n,clearness,unclearness,_20).
 1121opposite(n,explicitness,inexplicitness,_20).
 1122opposite(n,ambiguity,unambiguity,_20).
 1123opposite(n,equivocalness,unequivocalness,_20).
 1124opposite(n,polysemy,monosemy,_20).
 1125opposite(n,righteousness,unrighteousness,_20).
 1126opposite(n,piety,impiety,_20).
 1127opposite(n,godliness,ungodliness,_20).
 1128opposite(n,humaneness,inhumaneness,_20).
 1129opposite(n,mercifulness,mercilessness,_20).
 1130opposite(n,liberality,illiberality,_20).
 1131opposite(n,stinginess,generosity,_20).
 1132opposite(n,selfishness,unselfishness,_20).
 1133opposite(n,egoism,altruism,_20).
 1134opposite(n,fairness,unfairness,_20).
 1135opposite(n,equity,inequity,_20).
 1136opposite(n,kindness,unkindness,_20).
 1137opposite(n,consideration,inconsideration,_20).
 1138opposite(n,thoughtfulness,thoughtlessness,_20).
 1139opposite(n,tactfulness,tactlessness,_20).
 1140opposite(n,malignity,benignity,_20).
 1141opposite(n,malignancy,benignancy,_20).
 1142opposite(n,sensitivity,insensitivity,_20).
 1143opposite(n,sensitiveness,insensitiveness,_20).
 1144opposite(n,perceptiveness,unperceptiveness,_20).
 1145opposite(n,maleficence,beneficence,_20).
 1146opposite(n,morality,immorality,_20).
 1147opposite(n,good,evil,_20).
 1148opposite(n,goodness,evilness,_20).
 1149opposite(n,justice,injustice,_20).
 1150opposite(n,corruptibility,incorruptibility,_20).
 1151opposite(n,corruptness,incorruptness,_20).
 1152opposite(n,wrong,right,_20).
 1153opposite(n,wrongfulness,rightfulness,_20).
 1154opposite(n,holiness,unholiness,_20).
 1155opposite(n,safeness,dangerousness,_20).
 1156opposite(n,curability,incurability,_20).
 1157opposite(n,curableness,incurableness,_20).
 1158opposite(n,courage,cowardice,_20).
 1159opposite(n,stoutheartedness,faintheartedness,_20).
 1160opposite(n,gutsiness,gutlessness,_20).
 1161opposite(n,fearfulness,fearlessness,_20).
 1162opposite(n,timidity,boldness,_20).
 1163opposite(n,resoluteness,irresoluteness,_20).
 1164opposite(n,decisiveness,indecisiveness,_20).
 1165opposite(n,decision,indecision,_20).
 1166opposite(n,sincerity,insincerity,_20).
 1167opposite(n,honorableness,dishonorableness,_20).
 1168opposite(n,honor,dishonor,_20).
 1169opposite(n,scrupulousness,unscrupulousness,_20).
 1170opposite(n,respectability,unrespectability,_20).
 1171opposite(n,reputability,disreputability,_20).
 1172opposite(n,honesty,dishonesty,_20).
 1173opposite(n,truthfulness,untruthfulness,_20).
 1174opposite(n,veracity,mendacity,_20).
 1175opposite(n,ingenuousness,disingenuousness,_20).
 1176opposite(n,artfulness,artlessness,_20).
 1177opposite(n,fidelity,infidelity,_20).
 1178opposite(n,faithfulness,unfaithfulness,_20).
 1179opposite(n,loyalty,disloyalty,_20).
 1180opposite(n,naivete,sophistication,_20).
 1181opposite(n,discipline,indiscipline,_20).
 1182opposite(n,restraint,unrestraint,_20).
 1183opposite(n,temperance,intemperance,_20).
 1184opposite(n,conceit,humility,_20).
 1185opposite(n,folly,wisdom,_20).
 1186opposite(n,prudence,imprudence,_20).
 1187opposite(n,providence,improvidence,_20).
 1188opposite(n,trust,distrust,_20).
 1189opposite(n,cleanliness,uncleanliness,_20).
 1190opposite(n,tidiness,untidiness,_20).
 1191opposite(n,propriety,impropriety,_20).
 1192opposite(n,properness,improperness,_20).
 1193opposite(n,decorum,indecorum,_20).
 1194opposite(n,decorousness,indecorousness,_20).
 1195opposite(n,'political correctness','political incorrectness',_20).
 1196opposite(n,seemliness,unseemliness,_20).
 1197opposite(n,becomingness,unbecomingness,_20).
 1198opposite(n,decency,indecency,_20).
 1199opposite(n,modesty,immodesty,_20).
 1200opposite(n,composure,discomposure,_20).
 1201opposite(n,tractability,intractability,_20).
 1202opposite(n,subordination,insubordination,_20).
 1203opposite(n,wildness,tameness,_20).
 1204opposite(n,formality,informality,_20).
 1205opposite(n,ceremoniousness,unceremoniousness,_20).
 1206opposite(n,courtesy,discourtesy,_20).
 1207opposite(n,politeness,impoliteness,_20).
 1208opposite(n,graciousness,ungraciousness,_20).
 1209opposite(n,civility,incivility,_20).
 1210opposite(n,isotropy,anisotropy,_20).
 1211opposite(n,directness,indirectness,_20).
 1212opposite(n,mediacy,immediacy,_20).
 1213opposite(n,oldness,newness,_20).
 1214opposite(n,oldness,youngness,_20).
 1215opposite(n,staleness,freshness,_20).
 1216opposite(n,'reduced instruction set computing','complex instruction set computing',_20).
 1217opposite(n,'reduced instruction set computer','complex instruction set computer',_20).
 1218opposite(n,'RISC','CISC',_20).
 1219opposite(n,thinness,thickness,_20).
 1220opposite(n,softness,hardness,_20).
 1221opposite(n,compressibility,incompressibility,_20).
 1222opposite(n,breakableness,unbreakableness,_20).
 1223opposite(n,permeability,impermeability,_20).
 1224opposite(n,penetrability,impenetrability,_20).
 1225opposite(n,perviousness,imperviousness,_20).
 1226opposite(n,absorbency,nonabsorbency,_20).
 1227opposite(n,solidity,porosity,_20).
 1228opposite(n,roughness,smoothness,_20).
 1229opposite(n,dullness,brightness,_20).
 1230opposite(n,color,colorlessness,_20).
 1231opposite(n,'chromatic color','achromatic color',_20).
 1232opposite(n,pigmentation,depigmentation,_20).
 1233opposite(n,darkness,lightness,_20).
 1234opposite(n,sound,silence,_20).
 1235opposite(n,harmony,dissonance,_20).
 1236opposite(n,'low pitch','high pitch',_20).
 1237opposite(n,softness,loudness,_20).
 1238opposite(n,palatability,unpalatability,_20).
 1239opposite(n,appetizingness,unappetizingness,_20).
 1240opposite(n,digestibility,indigestibility,_20).
 1241opposite(n,fatness,leanness,_20).
 1242opposite(n,tallness,shortness,_20).
 1243opposite(n,awkwardness,gracefulness,_20).
 1244opposite(n,animateness,inanimateness,_20).
 1245opposite(n,sentience,insentience,_20).
 1246opposite(n,maleness,femaleness,_20).
 1247opposite(n,hotness,coldness,_20).
 1248opposite(n,perceptibility,imperceptibility,_20).
 1249opposite(n,visibility,invisibility,_20).
 1250opposite(n,audibility,inaudibility,_20).
 1251opposite(n,elasticity,inelasticity,_20).
 1252opposite(n,malleability,unmalleability,_20).
 1253opposite(n,lightness,heaviness,_20).
 1254opposite(n,soundness,unsoundness,_20).
 1255opposite(n,acidity,alkalinity,_20).
 1256opposite(n,weakness,strength,_20).
 1257opposite(n,'weak part','good part',_20).
 1258opposite(n,vulnerability,invulnerability,_20).
 1259opposite(n,destructibility,indestructibility,_20).
 1260opposite(n,lateness,earliness,_20).
 1261opposite(n,priority,posteriority,_20).
 1262opposite(n,tardiness,punctuality,_20).
 1263opposite(n,seasonableness,unseasonableness,_20).
 1264opposite(n,timeliness,untimeliness,_20).
 1265opposite(n,pastness,presentness,_20).
 1266opposite(n,pastness,futurity,_20).
 1267opposite(n,permanence,impermanence,_20).
 1268opposite(n,mortality,immortality,_20).
 1269opposite(n,symmetry,asymmetry,_20).
 1270opposite(n,'radial symmetry','radial asymmetry',_20).
 1271opposite(n,abruptness,gradualness,_20).
 1272opposite(n,pointedness,unpointedness,_20).
 1273opposite(n,roundness,angularity,_20).
 1274opposite(n,eccentricity,concentricity,_20).
 1275opposite(n,crookedness,straightness,_20).
 1276opposite(n,centrality,marginality,_20).
 1277opposite(n,southernness,northernness,_20).
 1278opposite(n,farness,nearness,_20).
 1279opposite(n,profundity,superficiality,_20).
 1280opposite(n,low,high,_20).
 1281opposite(n,bigness,littleness,_20).
 1282opposite(n,smallness,largeness,_20).
 1283opposite(n,positivity,negativity,_20).
 1284opposite(n,positiveness,negativeness,_20).
 1285opposite(n,sufficiency,insufficiency,_20).
 1286opposite(n,scarcity,abundance,_20).
 1287opposite(n,moderation,immoderation,_20).
 1288opposite(n,minority,majority,_20).
 1289opposite(n,deepness,shallowness,_20).
 1290opposite(n,wideness,narrowness,_20).
 1291opposite(n,lowness,highness,_20).
 1292opposite(n,worth,worthlessness,_20).
 1293opposite(n,merit,demerit,_20).
 1294opposite(n,desirability,undesirability,_20).
 1295opposite(n,reward,penalty,_20).
 1296opposite(n,expensiveness,inexpensiveness,_20).
 1297opposite(n,fruitfulness,fruitlessness,_20).
 1298opposite(n,productiveness,unproductiveness,_20).
 1299opposite(n,utility,inutility,_20).
 1300opposite(n,usefulness,uselessness,_20).
 1301opposite(n,practicality,impracticality,_20).
 1302opposite(n,practicability,impracticability,_20).
 1303opposite(n,practicableness,impracticableness,_20).
 1304opposite(n,feasibility,infeasibility,_20).
 1305opposite(n,competence,incompetence,_20).
 1306opposite(n,asset,liability,_20).
 1307opposite(n,advantage,disadvantage,_20).
 1308opposite(n,profitableness,unprofitableness,_20).
 1309opposite(n,profitability,unprofitability,_20).
 1310opposite(n,expedience,inexpedience,_20).
 1311opposite(n,expediency,inexpediency,_20).
 1312opposite(n,'weak point','strong point',_20).
 1313opposite(n,advisability,inadvisability,_20).
 1314opposite(n,favorableness,unfavorableness,_20).
 1315opposite(n,auspiciousness,inauspiciousness,_20).
 1316opposite(n,propitiousness,unpropitiousness,_20).
 1317opposite(n,destructiveness,constructiveness,_20).
 1318opposite(n,importance,unimportance,_20).
 1319opposite(n,significance,insignificance,_20).
 1320opposite(n,meaningfulness,meaninglessness,_20).
 1321opposite(n,purposefulness,purposelessness,_20).
 1322opposite(n,consequence,inconsequence,_20).
 1323opposite(n,essentiality,inessentiality,_20).
 1324opposite(n,dispensability,indispensability,_20).
 1325opposite(n,dispensableness,indispensableness,_20).
 1326opposite(n,power,powerlessness,_20).
 1327opposite(n,persuasiveness,unpersuasiveness,_20).
 1328opposite(n,interestingness,uninterestingness,_20).
 1329opposite(n,effectiveness,ineffectiveness,_20).
 1330opposite(n,efficacy,inefficacy,_20).
 1331opposite(n,ability,inability,_20).
 1332opposite(n,capability,incapability,_20).
 1333opposite(n,capableness,incapableness,_20).
 1334opposite(n,capacity,incapacity,_20).
 1335opposite(n,finiteness,infiniteness,_20).
 1336opposite(n,solubility,insolubility,_20).
 1337opposite(n,optimism,pessimism,_20).
 1338opposite(n,responsiveness,unresponsiveness,_20).
 1339opposite(n,solvability,unsolvability,_20).
 1340opposite(n,flexor,extensor,_20).
 1341opposite(n,receptor,effector,_20).
 1342opposite(n,cortex,medulla,_20).
 1343opposite(n,judiciousness,injudiciousness,_20).
 1344opposite(n,aptitude,inaptitude,_20).
 1345opposite(n,perfectibility,imperfectibility,_20).
 1346opposite(n,creativeness,uncreativeness,_20).
 1347opposite(n,'Hell','Heaven',_20).
 1348opposite(n,literacy,illiteracy,_20).
 1349opposite(n,skillfulness,unskillfulness,_20).
 1350opposite(n,coordination,incoordination,_20).
 1351opposite(n,fluency,disfluency,_20).
 1352opposite(n,efficiency,inefficiency,_20).
 1353opposite(n,stupidity,intelligence,_20).
 1354opposite(n,kinesthesia,kinanesthesia,_20).
 1355opposite(n,'merit system','spoils system',_20).
 1356opposite(n,consciousness,unconsciousness,_20).
 1357opposite(n,cognizance,incognizance,_20).
 1358opposite(n,'self-consciousness',unselfconsciousness,_20).
 1359opposite(n,sensibility,insensibility,_20).
 1360opposite(n,waking,sleeping,_20).
 1361opposite(n,attention,inattention,_20).
 1362opposite(n,experience,inexperience,_20).
 1363opposite(n,analysis,synthesis,_20).
 1364opposite(n,'divergent thinking','convergent thinking',_20).
 1365opposite(n,comprehension,incomprehension,_20).
 1366opposite(n,general,particular,_20).
 1367opposite(n,general,specific,_20).
 1368opposite(n,conception,misconception,_20).
 1369opposite(n,type,antitype,_20).
 1370opposite(n,divergence,convergence,_20).
 1371opposite(n,divergency,convergency,_20).
 1372opposite(n,middle,beginning,_20).
 1373opposite(n,'reality principle','pleasure principle',_20).
 1374opposite(n,yin,yang,_20).
 1375opposite(n,ground,figure,_20).
 1376opposite(n,belief,unbelief,_20).
 1377opposite(n,apophatism,cataphatism,_20).
 1378opposite(n,apophatism,'doctrine of analogy',_20).
 1379opposite(n,imitation,formalism,_20).
 1380opposite(n,monism,pluralism,_20).
 1381opposite(n,nationalism,multiculturalism,_20).
 1382opposite(n,nationalism,internationalism,_20).
 1383opposite(n,hereditarianism,environmentalism,_20).
 1384opposite(n,enlightenment,unenlightenment,_20).
 1385opposite(n,'open interval','closed interval',_20).
 1386opposite(n,eugenics,dysgenics,_20).
 1387opposite(n,holism,atomism,_20).
 1388opposite(n,'wave theory','corpuscular theory',_20).
 1389opposite(n,'wave theory of light','corpuscular theory of light',_20).
 1390opposite(n,classicism,'Romanticism',_20).
 1391opposite(n,'descriptive linguistics','prescriptive linguistics',_20).
 1392opposite(n,'Arianism','Athanasianism',_20).
 1393opposite(n,partiality,impartiality,_20).
 1394opposite(n,tolerance,intolerance,_20).
 1395opposite(n,'broad-mindedness','narrow-mindedness',_20).
 1396opposite(n,respect,disrespect,_20).
 1397opposite(n,reverence,irreverence,_20).
 1398opposite(n,conformism,nonconformism,_20).
 1399opposite(n,dovishness,hawkishness,_20).
 1400opposite(n,theism,atheism,_20).
 1401opposite(n,polytheism,monotheism,_20).
 1402opposite(n,verso,recto,_20).
 1403opposite(n,'snail mail','electronic mail',_20).
 1404opposite(n,plural,singular,_20).
 1405opposite(n,synonym,antonym,_20).
 1406opposite(n,oblique,nominative,_20).
 1407opposite(n,construction,misconstruction,_20).
 1408opposite(n,'proper noun','common noun',_20).
 1409opposite(n,flashback,'flash-forward',_20).
 1410opposite(n,'text edition','trade edition',_20).
 1411opposite(n,software,hardware,_20).
 1412opposite(n,'source program','object program',_20).
 1413opposite(n,euphemism,dysphemism,_20).
 1414opposite(n,'air mail','surface mail',_20).
 1415opposite(n,hospitality,inhospitality,_20).
 1416opposite(n,pro,con,_20).
 1417opposite(n,intervention,nonintervention,_20).
 1418opposite(n,interference,noninterference,_20).
 1419opposite(n,approbation,disapprobation,_20).
 1420opposite(n,encouragement,discouragement,_20).
 1421opposite(n,truth,falsehood,_20).
 1422opposite(n,'direct evidence','circumstantial evidence',_20).
 1423opposite(n,'universal proposition','particular proposition',_20).
 1424opposite(n,categorem,syncategorem,_20).
 1425opposite(n,categoreme,syncategoreme,_20).
 1426opposite(n,overstatement,understatement,_20).
 1427opposite(n,indication,contraindication,_20).
 1428opposite(n,'Roman numeral','Arabic numeral',_20).
 1429opposite(n,subscript,superscript,_20).
 1430opposite(n,uppercase,lowercase,_20).
 1431opposite(n,'fixed-width font','proportional font',_20).
 1432opposite(n,modern,'old style',_20).
 1433opposite(n,tonality,atonality,_20).
 1434opposite(n,'one-dimensional language','multidimensional language',_20).
 1435opposite(n,'stratified language','unstratified language',_20).
 1436opposite(n,'natural language','artificial language',_20).
 1437opposite(n,comedy,tragedy,_20).
 1438opposite(n,polyphony,monophony,_20).
 1439opposite(n,'polyphonic music','monophonic music',_20).
 1440opposite(n,resolution,preparation,_20).
 1441opposite(n,diminution,augmentation,_20).
 1442opposite(n,terseness,verboseness,_20).
 1443opposite(n,vowel,consonant,_20).
 1444opposite(n,'stop consonant','continuant consonant',_20).
 1445opposite(n,'direct discourse','indirect discourse',_20).
 1446opposite(n,agreement,disagreement,_20).
 1447opposite(n,answer,question,_20).
 1448opposite(n,yea,nay,_20).
 1449opposite(n,negative,affirmative,_20).
 1450opposite(n,no,yes,_20).
 1451opposite(n,persuasion,dissuasion,_20).
 1452opposite(n,embarrassment,disembarrassment,_20).
 1453opposite(n,success,failure,_20).
 1454opposite(n,egress,ingress,_20).
 1455opposite(n,emersion,immersion,_20).
 1456opposite(n,rise,fall,_20).
 1457opposite(n,death,birth,_20).
 1458opposite(n,levitation,gravitation,_20).
 1459opposite(n,'low tide','high tide',_20).
 1460opposite(n,ebbtide,'flood tide',_20).
 1461opposite(n,'neap tide',springtide,_20).
 1462opposite(n,waxing,waning,_20).
 1463opposite(n,'self-fertilization','cross-fertilization',_20).
 1464opposite(n,autogamy,allogamy,_20).
 1465opposite(n,'self-pollination','cross-pollination',_20).
 1466opposite(n,levorotation,dextrorotation,_20).
 1467opposite(n,defeat,victory,_20).
 1468opposite(n,aphrodisia,anaphrodisia,_20).
 1469opposite(n,pain,pleasure,_20).
 1470opposite(n,liking,dislike,_20).
 1471opposite(n,inclination,disinclination,_20).
 1472opposite(n,'Anglophobia','Anglophilia',_20).
 1473opposite(n,gratitude,ingratitude,_20).
 1474opposite(n,concern,unconcern,_20).
 1475opposite(n,levity,gravity,_20).
 1476opposite(n,calmness,agitation,_20).
 1477opposite(n,diffidence,confidence,_20).
 1478opposite(n,joy,sorrow,_20).
 1479opposite(n,euphoria,dysphoria,_20).
 1480opposite(n,cheerfulness,cheerlessness,_20).
 1481opposite(n,contentment,discontentment,_20).
 1482opposite(n,satisfaction,dissatisfaction,_20).
 1483opposite(n,sadness,happiness,_20).
 1484opposite(n,hope,despair,_20).
 1485opposite(n,hopefulness,hopelessness,_20).
 1486opposite(n,love,hate,_20).
 1487opposite(n,misogyny,philogyny,_20).
 1488opposite(n,malevolence,benevolence,_20).
 1489opposite(n,'ill humor','good humor',_20).
 1490opposite(n,'eating apple','cooking apple',_20).
 1491opposite(n,'skim milk','whole milk',_20).
 1492opposite(n,generic,varietal,_20).
 1493opposite(n,'generic wine','varietal wine',_20).
 1494opposite(n,aged,young,_20).
 1495opposite(n,timid,brave,_20).
 1496opposite(n,dead,living,_20).
 1497opposite(n,initiate,uninitiate,_20).
 1498opposite(n,offence,defence,_20).
 1499opposite(n,laity,clergy,_20).
 1500opposite(n,'rich people','poor people',_20).
 1501opposite(n,rich,poor,_20).
 1502opposite(n,'singular matrix','nonsingular matrix',_20).
 1503opposite(n,alignment,nonalignment,_20).
 1504opposite(n,'market economy','non-market economy',_20).
 1505opposite(n,socialism,capitalism,_20).
 1506opposite(n,hostile,friendly,_20).
 1507opposite(n,'day school','boarding school',_20).
 1508opposite(n,'day school','night school',_20).
 1509opposite(n,flora,fauna,_20).
 1510opposite(n,'civil law','international law',_20).
 1511opposite(n,here,there,_20).
 1512opposite(n,apex,antapex,_20).
 1513opposite(n,apogee,perigee,_20).
 1514opposite(n,apoapsis,periapsis,_20).
 1515opposite(n,'point of apoapsis','point of periapsis',_20).
 1516opposite(n,aphelion,perihelion,_20).
 1517opposite(n,apojove,perijove,_20).
 1518opposite(n,aposelene,periselene,_20).
 1519opposite(n,apolune,perilune,_20).
 1520opposite(n,'ascending node','descending node',_20).
 1521opposite(n,node,antinode,_20).
 1522opposite(n,inside,outside,_20).
 1523opposite(n,leeward,windward,_20).
 1524opposite(n,minimum,maximum,_20).
 1525opposite(n,nadir,zenith,_20).
 1526opposite(n,head,foot,_20).
 1527opposite(n,'urban area','rural area',_20).
 1528opposite(n,'free state','slave state',_20).
 1529opposite(n,incentive,disincentive,_20).
 1530opposite(n,adience,abience,_20).
 1531opposite(n,ascent,descent,_20).
 1532opposite(n,tributary,distributary,_20).
 1533opposite(n,'high sea','territorial waters',_20).
 1534opposite(n,lowland,highland,_20).
 1535opposite(n,'natural elevation','natural depression',_20).
 1536opposite(n,essential,inessential,_20).
 1537opposite(n,'open chain','closed chain',_20).
 1538opposite(n,'territorial waters','international waters',_20).
 1539opposite(n,eudemon,cacodemon,_20).
 1540opposite(n,adult,juvenile,_20).
 1541opposite(n,captor,liberator,_20).
 1542opposite(n,leader,follower,_20).
 1543opposite(n,'religious person','nonreligious person',_20).
 1544opposite(n,worker,nonworker,_20).
 1545opposite(n,amateur,professional,_20).
 1546opposite(n,ancestor,descendant,_20).
 1547opposite(n,aunt,uncle,_20).
 1548opposite(n,'bad egg','good egg',_20).
 1549opposite(n,'bad guy','good guy',_20).
 1550opposite(n,'bad person','good person',_20).
 1551opposite(n,bull,bear,_20).
 1552opposite(n,child,parent,_20).
 1553opposite(n,citizen,noncitizen,_20).
 1554opposite(n,civilian,serviceman,_20).
 1555opposite(n,classicist,romanticist,_20).
 1556opposite(n,conformist,nonconformist,_20).
 1557opposite(n,'Anglican','Nonconformist',_20).
 1558opposite(n,debtor,creditor,_20).
 1559opposite(n,draftee,volunteer,_20).
 1560opposite(n,drinker,nondrinker,_20).
 1561opposite(n,driver,nondriver,_20).
 1562opposite(n,elitist,egalitarian,_20).
 1563opposite(n,'emotional person','unemotional person',_20).
 1564opposite(n,employer,employee,_20).
 1565opposite(n,'male parent','female parent',_20).
 1566opposite(n,'fat person','thin person',_20).
 1567opposite(n,foe,friend,_20).
 1568opposite(n,granter,withholder,_20).
 1569opposite(n,hawk,dove,_20).
 1570opposite(n,'heir apparent','heir presumptive',_20).
 1571opposite(n,inpatient,outpatient,_20).
 1572opposite(n,introvert,extrovert,_20).
 1573opposite(n,king,queen,_20).
 1574opposite(n,'male monarch','female monarch',_20).
 1575opposite(n,layman,clergyman,_20).
 1576opposite(n,'lay witness','expert witness',_20).
 1577opposite(n,lender,borrower,_20).
 1578opposite(n,liar,'square shooter',_20).
 1579opposite(n,liberal,conservative,_20).
 1580opposite(n,libertarian,necessitarian,_20).
 1581opposite(n,'liveborn infant','stillborn infant',_20).
 1582opposite(n,'Lord','Lady',_20).
 1583opposite(n,nobleman,noblewoman,_20).
 1584opposite(n,loser,winner,_20).
 1585opposite(n,loser,achiever,_20).
 1586opposite(n,lumper,splitter,_20).
 1587opposite(n,'male aristocrat','female aristocrat',_20).
 1588opposite(n,'male child','female child',_20).
 1589opposite(n,boy,girl,_20).
 1590opposite(n,'male offspring','female offspring',_20).
 1591opposite(n,'male sibling','female sibling',_20).
 1592opposite(n,man,woman,_20).
 1593opposite(n,member,nonmember,_20).
 1594opposite(n,mother,father,_20).
 1595opposite(n,niece,nephew,_20).
 1596opposite(n,optimist,pessimist,_20).
 1597opposite(n,partisan,nonpartisan,_20).
 1598opposite(n,plaintiff,defendant,_20).
 1599opposite(n,eremite,cenobite,_20).
 1600opposite(n,resident,nonresident,_20).
 1601opposite(n,sadist,masochist,_20).
 1602opposite(n,sister,brother,_20).
 1603opposite(n,sitter,stander,_20).
 1604opposite(n,smoker,nonsmoker,_20).
 1605opposite(n,son,daughter,_20).
 1606opposite(n,'special agent','general agent',_20).
 1607opposite(n,specialist,generalist,_20).
 1608opposite(n,stranger,acquaintance,_20).
 1609opposite(n,superior,inferior,_20).
 1610opposite(n,technophobe,technophile,_20).
 1611opposite(n,wife,husband,_20).
 1612opposite(n,repulsion,attraction,_20).
 1613opposite(n,'centripetal force','centrifugal force',_20).
 1614opposite(n,'positive charge','negative charge',_20).
 1615opposite(n,'direct current','alternating current',_20).
 1616opposite(n,opacity,transparency,_20).
 1617opposite(n,acrocarp,pleurocarp,_20).
 1618opposite(n,'Cryptogamia','Phanerogamae',_20).
 1619opposite(n,mushroom,toadstool,_20).
 1620opposite(n,weed,'cultivated plant',_20).
 1621opposite(n,'evergreen plant','deciduous plant',_20).
 1622opposite(n,'easy money','tight money',_20).
 1623opposite(n,'paper loss','paper profit',_20).
 1624opposite(n,outgo,income,_20).
 1625opposite(n,loss,gain,_20).
 1626opposite(n,losings,winnings,_20).
 1627opposite(n,'secured bond','unsecured bond',_20).
 1628opposite(n,'cash account','margin account',_20).
 1629opposite(n,'active trust','passive trust',_20).
 1630opposite(n,cash,credit,_20).
 1631opposite(n,'cash basis','accrual basis',_20).
 1632opposite(n,'listed security','unlisted security',_20).
 1633opposite(n,activation,inactivation,_20).
 1634opposite(n,anabolism,catabolism,_20).
 1635opposite(n,anamorphism,katamorphism,_20).
 1636opposite(n,anastalsis,peristalsis,_20).
 1637opposite(n,cenogenesis,palingenesis,_20).
 1638opposite(n,deflation,disinflation,_20).
 1639opposite(n,evolution,devolution,_20).
 1640opposite(n,development,nondevelopment,_20).
 1641opposite(n,increment,decrement,_20).
 1642opposite(n,'inflationary spiral','deflationary spiral',_20).
 1643opposite(n,inflow,outflow,_20).
 1644opposite(n,influx,efflux,_20).
 1645opposite(n,ovulation,anovulation,_20).
 1646opposite(n,proliferation,nonproliferation,_20).
 1647opposite(n,proliferation,'non-proliferation',_20).
 1648opposite(n,'reversible process','irreversible process',_20).
 1649opposite(n,'serial operation','parallel operation',_20).
 1650opposite(n,sink,source,_20).
 1651opposite(n,supply,demand,_20).
 1652opposite(n,'synchronous operation','asynchronous operation',_20).
 1653opposite(n,lead,deficit,_20).
 1654opposite(n,aliquot,aliquant,_20).
 1655opposite(n,connectedness,unconnectedness,_20).
 1656opposite(n,relevance,irrelevance,_20).
 1657opposite(n,applicability,inapplicability,_20).
 1658opposite(n,relatedness,unrelatedness,_20).
 1659opposite(n,transitivity,intransitivity,_20).
 1660opposite(n,'active voice','passive voice',_20).
 1661opposite(n,affinity,consanguinity,_20).
 1662opposite(n,synchronism,asynchronism,_20).
 1663opposite(n,synchronization,desynchronization,_20).
 1664opposite(n,synchronizing,desynchronizing,_20).
 1665opposite(n,latter,former,_20).
 1666opposite(n,'convex polygon','concave polygon',_20).
 1667opposite(n,curve,'straight line',_20).
 1668opposite(n,'right triangle','oblique triangle',_20).
 1669opposite(n,trapezium,parallelogram,_20).
 1670opposite(n,'salient angle','reentrant angle',_20).
 1671opposite(n,'right angle','oblique angle',_20).
 1672opposite(n,proportion,disproportion,_20).
 1673opposite(n,utopia,dystopia,_20).
 1674opposite(n,equilibrium,disequilibrium,_20).
 1675opposite(n,inclusion,exclusion,_20).
 1676opposite(n,rejection,acceptance,_20).
 1677opposite(n,stigmatism,astigmatism,_20).
 1678opposite(n,'back burner','front burner',_20).
 1679opposite(n,'low status','high status',_20).
 1680opposite(n,being,nonbeing,_20).
 1681opposite(n,existence,nonexistence,_20).
 1682opposite(n,genuineness,spuriousness,_20).
 1683opposite(n,truth,falsity,_20).
 1684opposite(n,hereness,thereness,_20).
 1685opposite(n,sympatry,allopatry,_20).
 1686opposite(n,exogamy,endogamy,_20).
 1687opposite(n,employment,unemployment,_20).
 1688opposite(n,order,disorder,_20).
 1689opposite(n,immunodeficiency,immunocompetence,_20).
 1690opposite(n,war,peace,_20).
 1691opposite(n,'hot war','cold war',_20).
 1692opposite(n,dark,light,_20).
 1693opposite(n,happiness,unhappiness,_20).
 1694opposite(n,guilt,innocence,_20).
 1695opposite(n,balance,imbalance,_20).
 1696opposite(n,motion,motionlessness,_20).
 1697opposite(n,action,inaction,_20).
 1698opposite(n,soberness,drunkenness,_20).
 1699opposite(n,insomnia,hypersomnia,_20).
 1700opposite(n,sleepiness,wakefulness,_20).
 1701opposite(n,estrus,anestrus,_20).
 1702opposite(n,hypocapnia,hypercapnia,_20).
 1703opposite(n,hypothermia,hyperthermia,_20).
 1704opposite(n,fertility,infertility,_20).
 1705opposite(n,potency,impotency,_20).
 1706opposite(n,potence,impotence,_20).
 1707opposite(n,'ill health','good health',_20).
 1708opposite(n,'organic disorder','functional disorder',_20).
 1709opposite(n,illness,wellness,_20).
 1710opposite(n,hypoparathyroidism,hyperparathyroidism,_20).
 1711opposite(n,hypotension,hypertension,_20).
 1712opposite(n,hypothyroidism,hyperthyroidism,_20).
 1713opposite(n,hypovolemia,hypervolemia,_20).
 1714opposite(n,hypocalcemia,hypercalcemia,_20).
 1715opposite(n,hypokalemia,hyperkalemia,_20).
 1716opposite(n,hyponatremia,hypernatremia,_20).
 1717opposite(n,hypopigmentation,hyperpigmentation,_20).
 1718opposite(n,hypoglycemia,hyperglycemia,_20).
 1719opposite(n,'mental health','mental illness',_20).
 1720opposite(n,sanity,insanity,_20).
 1721opposite(n,'neurotic depression','psychotic depression',_20).
 1722opposite(n,elation,depression,_20).
 1723opposite(n,high,'low spirits',_20).
 1724opposite(n,union,separation,_20).
 1725opposite(n,connectedness,disconnectedness,_20).
 1726opposite(n,coherence,incoherence,_20).
 1727opposite(n,association,disassociation,_20).
 1728opposite(n,continuity,discontinuity,_20).
 1729opposite(n,decline,improvement,_20).
 1730opposite(n,maturity,immaturity,_20).
 1731opposite(n,ripeness,greenness,_20).
 1732opposite(n,obscurity,prominence,_20).
 1733opposite(n,fame,infamy,_20).
 1734opposite(n,esteem,disesteem,_20).
 1735opposite(n,repute,disrepute,_20).
 1736opposite(n,comfort,discomfort,_20).
 1737opposite(n,wellness,unwellness,_20).
 1738opposite(n,'ill-being','well-being',_20).
 1739opposite(n,fullness,emptiness,_20).
 1740opposite(n,solidity,hollowness,_20).
 1741opposite(n,perfection,imperfection,_20).
 1742opposite(n,completeness,incompleteness,_20).
 1743opposite(n,varus,valgus,_20).
 1744opposite(n,misfortune,'good fortune',_20).
 1745opposite(n,'bad luck','good luck',_20).
 1746opposite(n,solvency,insolvency,_20).
 1747opposite(n,possibility,impossibility,_20).
 1748opposite(n,purity,impurity,_20).
 1749opposite(n,wealth,poverty,_20).
 1750opposite(n,sanitariness,unsanitariness,_20).
 1751opposite(n,orderliness,disorderliness,_20).
 1752opposite(n,dirtiness,cleanness,_20).
 1753opposite(n,normality,abnormality,_20).
 1754opposite(n,typicality,atypicality,_20).
 1755opposite(n,'biodegradable pollution','nonbiodegradable pollution',_20).
 1756opposite(n,cyclone,anticyclone,_20).
 1757opposite(n,'bad weather','good weather',_20).
 1758opposite(n,susceptibility,unsusceptibility,_20).
 1759opposite(n,wetness,dryness,_20).
 1760opposite(n,safety,danger,_20).
 1761opposite(n,security,insecurity,_20).
 1762opposite(n,secureness,insecureness,_20).
 1763opposite(n,tonicity,atonicity,_20).
 1764opposite(n,myopia,hyperopia,_20).
 1765opposite(n,homozygosity,heterozygosity,_20).
 1766opposite(n,hypotonia,hypertonia,_20).
 1767opposite(n,hypotonus,hypertonus,_20).
 1768opposite(n,hypotonicity,hypertonicity,_20).
 1769opposite(n,'leaded gasoline','unleaded gasoline',_20).
 1770opposite(n,catalyst,anticatalyst,_20).
 1771opposite(n,inhibitor,activator,_20).
 1772opposite(n,insulator,conductor,_20).
 1773opposite(n,exon,intron,_20).
 1774opposite(n,'low explosive','high explosive',_20).
 1775opposite(n,saltwater,'fresh water',_20).
 1776opposite(n,exotoxin,endotoxin,_20).
 1777opposite(n,'soft water','hard water',_20).
 1778opposite(n,uptime,downtime,_20).
 1779opposite(n,'time off','work time',_20).
 1780opposite(n,past,future,_20).
 1781opposite(n,workday,'rest day',_20).
 1782opposite(n,day,night,_20).
 1783opposite(n,sunset,sunrise,_20).
 1784opposite(n,'winter solstice','summer solstice',_20).
 1785opposite(n,'vernal equinox','autumnal equinox',_20).
 1786opposite(n,overtime,'regulation time',_20).
 1787opposite(n,'off-season','high season',_20).
 1788opposite(n,'dry season','rainy season',_20).
 1789opposite(n,top,bottom,_20).
 1790opposite(v,inhale,exhale,_20).
 1791opposite(v,rest,'be active',_20).
 1792opposite(v,hibernate,aestivate,_20).
 1793opposite(v,estivate,hibernate,_20).
 1794opposite(v,'turn in','turn out',_20).
 1795opposite(v,'get up','go to bed',_20).
 1796opposite(v,'wake up','fall asleep',_20).
 1797opposite(v,awaken,'cause to sleep',_20).
 1798opposite(v,wake,sleep,_20).
 1799opposite(v,'bring to',anesthetize,_20).
 1800opposite(v,sedate,stimulate,_20).
 1801opposite(v,energize,'de-energize',_20).
 1802opposite(v,energise,'de-energise',_20).
 1803opposite(v,tense,relax,_20).
 1804opposite(v,strain,unstrain,_20).
 1805opposite(v,overdress,underdress,_20).
 1806opposite(v,'dress up','dress down',_20).
 1807opposite(v,gain,reduce,_20).
 1808opposite(v,dress,undress,_20).
 1809opposite(v,'slip on','slip off',_20).
 1810opposite(v,miscarry,'carry to term',_20).
 1811opposite(v,soothe,irritate,_20).
 1812opposite(v,suffer,'be well',_20).
 1813opposite(v,cry,laugh,_20).
 1814opposite(v,tire,refresh,_20).
 1815opposite(v,vomit,'keep down',_20).
 1816opposite(v,infect,disinfect,_20).
 1817opposite(v,recuperate,deteriorate,_20).
 1818opposite(v,stay,change,_20).
 1819opposite(v,differentiate,dedifferentiate,_20).
 1820opposite(v,mythologize,demythologize,_20).
 1821opposite(v,assimilate,dissimilate,_20).
 1822opposite(v,vitalize,devitalize,_20).
 1823opposite(v,enrich,deprive,_20).
 1824opposite(v,clutter,unclutter,_20).
 1825opposite(v,add,'take away',_20).
 1826opposite(v,activate,inactivate,_20).
 1827opposite(v,deaden,enliven,_20).
 1828opposite(v,falsify,correct,_20).
 1829opposite(v,worsen,better,_20).
 1830opposite(v,hydrate,dehydrate,_20).
 1831opposite(v,wet,dry,_20).
 1832opposite(v,humidify,dehumidify,_20).
 1833opposite(v,lock,unlock,_20).
 1834opposite(v,engage,disengage,_20).
 1835opposite(v,weaken,strengthen,_20).
 1836opposite(v,oxidize,deoxidize,_20).
 1837opposite(v,oxidise,deoxidise,_20).
 1838opposite(v,reduce,'blow up',_20).
 1839opposite(v,shrink,stretch,_20).
 1840opposite(v,regress,progress,_20).
 1841opposite(v,age,rejuvenate,_20).
 1842opposite(v,soften,harden,_20).
 1843opposite(v,inflate,deflate,_20).
 1844opposite(v,acidify,alkalize,_20).
 1845opposite(v,'get well','get worse',_20).
 1846opposite(v,freeze,unfreeze,_20).
 1847opposite(v,block,unblock,_20).
 1848opposite(v,stabilize,destabilize,_20).
 1849opposite(v,stabilise,destabilise,_20).
 1850opposite(v,sensitize,desensitize,_20).
 1851opposite(v,predate,postdate,_20).
 1852opposite(v,whiten,blacken,_20).
 1853opposite(v,color,discolor,_20).
 1854opposite(v,escalate,'de-escalate',_20).
 1855opposite(v,uglify,beautify,_20).
 1856opposite(v,tune,untune,_20).
 1857opposite(v,qualify,disqualify,_20).
 1858opposite(v,widen,narrow,_20).
 1859opposite(v,'take in','let out',_20).
 1860opposite(v,implode,explode,_20).
 1861opposite(v,hydrogenate,dehydrogenate,_20).
 1862opposite(v,blur,focus,_20).
 1863opposite(v,darken,brighten,_20).
 1864opposite(v,darken,lighten,_20).
 1865opposite(v,depreciate,appreciate,_20).
 1866opposite(v,shorten,lengthen,_20).
 1867opposite(v,materialize,dematerialize,_20).
 1868opposite(v,materialise,dematerialise,_20).
 1869opposite(v,end,begin,_20).
 1870opposite(v,die,'be born',_20).
 1871opposite(v,unify,disunify,_20).
 1872opposite(v,heat,cool,_20).
 1873opposite(v,personalize,depersonalize,_20).
 1874opposite(v,personalise,depersonalise,_20).
 1875opposite(v,sharpen,flatten,_20).
 1876opposite(v,synchronize,desynchronize,_20).
 1877opposite(v,synchronise,desynchronise,_20).
 1878opposite(v,magnetize,demagnetize,_20).
 1879opposite(v,magnetise,demagnetise,_20).
 1880opposite(v,simplify,complicate,_20).
 1881opposite(v,pressurize,depressurize,_20).
 1882opposite(v,pressurise,depressurise,_20).
 1883opposite(v,centralize,decentralize,_20).
 1884opposite(v,centralise,decentralise,_20).
 1885opposite(v,concentrate,deconcentrate,_20).
 1886opposite(v,winterize,summerize,_20).
 1887opposite(v,nationalize,denationalize,_20).
 1888opposite(v,nationalise,denationalise,_20).
 1889opposite(v,naturalize,denaturalize,_20).
 1890opposite(v,emigrate,immigrate,_20).
 1891opposite(v,loosen,stiffen,_20).
 1892opposite(v,transitivize,detransitivize,_20).
 1893opposite(v,appear,disappear,_20).
 1894opposite(v,minimize,maximize,_20).
 1895opposite(v,minimise,maximise,_20).
 1896opposite(v,'scale up','scale down',_20).
 1897opposite(v,thin,thicken,_20).
 1898opposite(v,wax,wane,_20).
 1899opposite(v,unfurl,'roll up',_20).
 1900opposite(v,diversify,specialize,_20).
 1901opposite(v,diversify,specialise,_20).
 1902opposite(v,decelerate,accelerate,_20).
 1903opposite(v,validate,invalidate,_20).
 1904opposite(v,fill,empty,_20).
 1905opposite(v,curdle,homogenize,_20).
 1906opposite(v,curdle,homogenise,_20).
 1907opposite(v,rush,delay,_20).
 1908opposite(v,louden,quieten,_20).
 1909opposite(v,skew,align,_20).
 1910opposite(v,integrate,disintegrate,_20).
 1911opposite(v,contaminate,decontaminate,_20).
 1912opposite(v,calcify,decalcify,_20).
 1913opposite(v,emulsify,demulsify,_20).
 1914opposite(v,nazify,denazify,_20).
 1915opposite(v,nitrify,denitrify,_20).
 1916opposite(v,enable,disable,_20).
 1917opposite(v,foreground,background,_20).
 1918opposite(v,'play up','play down',_20).
 1919opposite(v,mystify,demystify,_20).
 1920opposite(v,iodinate,'de-iodinate',_20).
 1921opposite(v,ionate,'de-ionate',_20).
 1922opposite(v,orientalize,occidentalize,_20).
 1923opposite(v,orientalise,occidentalise,_20).
 1924opposite(v,salinate,desalinate,_20).
 1925opposite(v,scramble,unscramble,_20).
 1926opposite(v,crescendo,decrescendo,_20).
 1927opposite(v,stalinize,destalinize,_20).
 1928opposite(v,know,ignore,_20).
 1929opposite(v,'lose track','keep track',_20).
 1930opposite(v,forget,remember,_20).
 1931opposite(v,neglect,'attend to',_20).
 1932opposite(v,literalize,spiritualize,_20).
 1933opposite(v,add,subtract,_20).
 1934opposite(v,divide,multiply,_20).
 1935opposite(v,analyze,synthesize,_20).
 1936opposite(v,upgrade,downgrade,_20).
 1937opposite(v,prove,disprove,_20).
 1938opposite(v,negate,affirm,_20).
 1939opposite(v,overestimate,underestimate,_20).
 1940opposite(v,approve,disapprove,_20).
 1941opposite(v,dispose,indispose,_20).
 1942opposite(v,believe,disbelieve,_20).
 1943opposite(v,include,exclude,_20).
 1944opposite(v,reject,accept,_20).
 1945opposite(v,reprobate,approbate,_20).
 1946opposite(v,trust,mistrust,_20).
 1947opposite(v,overvalue,undervalue,_20).
 1948opposite(v,associate,dissociate,_20).
 1949opposite(v,claim,disclaim,_20).
 1950opposite(v,persuade,dissuade,_20).
 1951opposite(v,'talk into','talk out of',_20).
 1952opposite(v,'contract in','contract out',_20).
 1953opposite(v,permit,forbid,_20).
 1954opposite(v,allow,disallow,_20).
 1955opposite(v,assent,dissent,_20).
 1956opposite(v,agree,disagree,_20).
 1957opposite(v,avoid,confront,_20).
 1958opposite(v,deny,admit,_20).
 1959opposite(v,avow,disavow,_20).
 1960opposite(v,overstate,understate,_20).
 1961opposite(v,blame,absolve,_20).
 1962opposite(v,deceive,undeceive,_20).
 1963opposite(v,praise,criticize,_20).
 1964opposite(v,cheer,complain,_20).
 1965opposite(v,boo,applaud,_20).
 1966opposite(v,curse,bless,_20).
 1967opposite(v,desecrate,consecrate,_20).
 1968opposite(v,flatter,disparage,_20).
 1969opposite(v,oblige,disoblige,_20).
 1970opposite(v,welcome,'say farewell',_20).
 1971opposite(v,acquit,convict,_20).
 1972opposite(v,shout,whisper,_20).
 1973opposite(v,indicate,contraindicate,_20).
 1974opposite(v,talk,'keep quiet',_20).
 1975opposite(v,clarify,obfuscate,_20).
 1976opposite(v,voice,devoice,_20).
 1977opposite(v,expand,contract,_20).
 1978opposite(v,'check in','check out',_20).
 1979opposite(v,'clock in','clock out',_20).
 1980opposite(v,'punch in','punch out',_20).
 1981opposite(v,encode,decode,_20).
 1982opposite(v,erase,record,_20).
 1983opposite(v,specify,generalize,_20).
 1984opposite(v,communicate,excommunicate,_20).
 1985opposite(v,'open up','close up',_20).
 1986opposite(v,spell,unspell,_20).
 1987opposite(v,enter,'drop out',_20).
 1988opposite(v,arm,disarm,_20).
 1989opposite(v,mobilize,demobilize,_20).
 1990opposite(v,mobilise,demobilise,_20).
 1991opposite(v,war,'make peace',_20).
 1992opposite(v,enlist,discharge,_20).
 1993opposite(v,militarize,demilitarize,_20).
 1994opposite(v,militarise,demilitarise,_20).
 1995opposite(v,win,lose,_20).
 1996opposite(v,gain,'fall back',_20).
 1997opposite(v,resist,surrender,_20).
 1998opposite(v,defend,attack,_20).
 1999opposite(v,overshoot,undershoot,_20).
 2000opposite(v,fuse,defuse,_20).
 2001opposite(v,consume,abstain,_20).
 2002opposite(v,'eat in','eat out',_20).
 2003opposite(v,'live in','live out',_20).
 2004opposite(v,feed,starve,_20).
 2005opposite(v,breastfeed,bottlefeed,_20).
 2006opposite(v,starve,'be full',_20).
 2007opposite(v,clasp,unclasp,_20).
 2008opposite(v,hold,'let go of',_20).
 2009opposite(v,twist,untwist,_20).
 2010opposite(v,hit,miss,_20).
 2011opposite(v,smooth,roughen,_20).
 2012opposite(v,fold,unfold,_20).
 2013opposite(v,bend,unbend,_20).
 2014opposite(v,wrap,unwrap,_20).
 2015opposite(v,tie,untie,_20).
 2016opposite(v,chain,unchain,_20).
 2017opposite(v,strap,unstrap,_20).
 2018opposite(v,join,disjoin,_20).
 2019opposite(v,couple,uncouple,_20).
 2020opposite(v,suffix,prefix,_20).
 2021opposite(v,detach,attach,_20).
 2022opposite(v,bridle,unbridle,_20).
 2023opposite(v,bind,unbind,_20).
 2024opposite(v,lash,unlash,_20).
 2025opposite(v,dock,undock,_20).
 2026opposite(v,degrade,aggrade,_20).
 2027opposite(v,hitch,unhitch,_20).
 2028opposite(v,cover,uncover,_20).
 2029opposite(v,fasten,unfasten,_20).
 2030opposite(v,unzip,'zip up',_20).
 2031opposite(v,bar,unbar,_20).
 2032opposite(v,open,close,_20).
 2033opposite(v,bolt,unbolt,_20).
 2034opposite(v,screw,unscrew,_20).
 2035opposite(v,seal,unseal,_20).
 2036opposite(v,connect,disconnect,_20).
 2037opposite(v,mask,unmask,_20).
 2038opposite(v,string,unstring,_20).
 2039opposite(v,hook,unhook,_20).
 2040opposite(v,belt,unbelt,_20).
 2041opposite(v,staple,unstaple,_20).
 2042opposite(v,clip,unclip,_20).
 2043opposite(v,button,unbutton,_20).
 2044opposite(v,pin,unpin,_20).
 2045opposite(v,break,repair,_20).
 2046opposite(v,spread,gather,_20).
 2047opposite(v,compress,decompress,_20).
 2048opposite(v,unplug,'plug in',_20).
 2049opposite(v,cork,uncork,_20).
 2050opposite(v,adduct,abduct,_20).
 2051opposite(v,entangle,disentangle,_20).
 2052opposite(v,snarl,unsnarl,_20).
 2053opposite(v,arrange,disarrange,_20).
 2054opposite(v,free,obstruct,_20).
 2055opposite(v,clog,unclog,_20).
 2056opposite(v,stuff,unstuff,_20).
 2057opposite(v,pack,unpack,_20).
 2058opposite(v,veil,unveil,_20).
 2059opposite(v,box,unbox,_20).
 2060opposite(v,crate,uncrate,_20).
 2061opposite(v,burden,unburden,_20).
 2062opposite(v,yoke,unyoke,_20).
 2063opposite(v,inspan,outspan,_20).
 2064opposite(v,harness,unharness,_20).
 2065opposite(v,saddle,unsaddle,_20).
 2066opposite(v,repel,attract,_20).
 2067opposite(v,'switch on','switch off',_20).
 2068opposite(v,twine,untwine,_20).
 2069opposite(v,weave,unweave,_20).
 2070opposite(v,braid,unbraid,_20).
 2071opposite(v,ravel,unravel,_20).
 2072opposite(v,knot,unknot,_20).
 2073opposite(v,wind,unwind,_20).
 2074opposite(v,coil,uncoil,_20).
 2075opposite(v,function,malfunction,_20).
 2076opposite(v,run,idle,_20).
 2077opposite(v,'go on','go off',_20).
 2078opposite(v,lodge,dislodge,_20).
 2079opposite(v,dirty,clean,_20).
 2080opposite(v,handwash,'machine wash',_20).
 2081opposite(v,sit,stand,_20).
 2082opposite(v,sit,lie,_20).
 2083opposite(v,buckle,unbuckle,_20).
 2084opposite(v,sheathe,unsheathe,_20).
 2085opposite(v,wire,unwire,_20).
 2086opposite(v,make,unmake,_20).
 2087opposite(v,'phase in','phase out',_20).
 2088opposite(v,incarnate,disincarnate,_20).
 2089opposite(v,assemble,disassemble,_20).
 2090opposite(v,raise,level,_20).
 2091opposite(v,'cast on','cast off',_20).
 2092opposite(v,overact,underact,_20).
 2093opposite(v,calm,agitate,_20).
 2094opposite(v,worry,reassure,_20).
 2095opposite(v,humanize,dehumanize,_20).
 2096opposite(v,elate,depress,_20).
 2097opposite(v,sadden,gladden,_20).
 2098opposite(v,lighten,'weigh down',_20).
 2099opposite(v,please,displease,_20).
 2100opposite(v,satisfy,dissatisfy,_20).
 2101opposite(v,content,discontent,_20).
 2102opposite(v,enchant,disenchant,_20).
 2103opposite(v,hearten,dishearten,_20).
 2104opposite(v,encourage,discourage,_20).
 2105opposite(v,bore,interest,_20).
 2106opposite(v,wish,begrudge,_20).
 2107opposite(v,admire,'look down on',_20).
 2108opposite(v,move,'stand still',_20).
 2109opposite(v,travel,'stay in place',_20).
 2110opposite(v,go,come,_20).
 2111opposite(v,'move in','move out',_20).
 2112opposite(v,push,pull,_20).
 2113opposite(v,ebb,tide,_20).
 2114opposite(v,walk,ride,_20).
 2115opposite(v,cross,uncross,_20).
 2116opposite(v,'file in','file out',_20).
 2117opposite(v,'pop in','pop out',_20).
 2118opposite(v,'hop on','hop out',_20).
 2119opposite(v,ascend,descend,_20).
 2120opposite(v,raise,lower,_20).
 2121opposite(v,embark,disembark,_20).
 2122opposite(v,arise,'sit down',_20).
 2123opposite(v,arise,'lie down',_20).
 2124opposite(v,glycerolize,deglycerolize,_20).
 2125opposite(v,sink,float,_20).
 2126opposite(v,follow,precede,_20).
 2127opposite(v,'top out','bottom out',_20).
 2128opposite(v,stay,depart,_20).
 2129opposite(v,leave,arrive,_20).
 2130opposite(v,'pull in','pull out',_20).
 2131opposite(v,'get on','get off',_20).
 2132opposite(v,diverge,converge,_20).
 2133opposite(v,bend,straighten,_20).
 2134opposite(v,rush,linger,_20).
 2135opposite(v,overexpose,underexpose,_20).
 2136opposite(v,sensitise,desensitise,_20).
 2137opposite(v,odorize,deodorize,_20).
 2138opposite(v,odourise,deodourise,_20).
 2139opposite(v,show,hide,_20).
 2140opposite(v,orient,disorient,_20).
 2141opposite(v,sour,sweeten,_20).
 2142opposite(v,take,give,_20).
 2143opposite(v,buy,sell,_20).
 2144opposite(v,bequeath,disinherit,_20).
 2145opposite(v,upload,download,_20).
 2146opposite(v,'log in','log out',_20).
 2147opposite(v,overpay,underpay,_20).
 2148opposite(v,'pay up',default,_20).
 2149opposite(v,overspend,underspend,_20).
 2150opposite(v,waste,conserve,_20).
 2151opposite(v,invest,divest,_20).
 2152opposite(v,claim,forfeit,_20).
 2153opposite(v,requisition,derequisition,_20).
 2154opposite(v,profit,'break even',_20).
 2155opposite(v,lose,find,_20).
 2156opposite(v,lose,keep,_20).
 2157opposite(v,clear,bounce,_20).
 2158opposite(v,overbid,underbid,_20).
 2159opposite(v,deposit,withdraw,_20).
 2160opposite(v,charge,'pay cash',_20).
 2161opposite(v,enrich,impoverish,_20).
 2162opposite(v,overcharge,undercharge,_20).
 2163opposite(v,'mark up','mark down',_20).
 2164opposite(v,overstock,understock,_20).
 2165opposite(v,lend,borrow,_20).
 2166opposite(v,muzzle,unmuzzle,_20).
 2167opposite(v,act,refrain,_20).
 2168opposite(v,'take office','leave office',_20).
 2169opposite(v,enthrone,dethrone,_20).
 2170opposite(v,demote,promote,_20).
 2171opposite(v,hire,fire,_20).
 2172opposite(v,free,confine,_20).
 2173opposite(v,let,prevent,_20).
 2174opposite(v,abolish,establish,_20).
 2175opposite(v,organize,disorganize,_20).
 2176opposite(v,organise,disorganise,_20).
 2177opposite(v,certify,decertify,_20).
 2178opposite(v,boycott,patronize,_20).
 2179opposite(v,boycott,patronise,_20).
 2180opposite(v,enfranchise,disenfranchise,_20).
 2181opposite(v,issue,recall,_20).
 2182opposite(v,outlaw,legalize,_20).
 2183opposite(v,criminalize,decriminalize,_20).
 2184opposite(v,criminalise,decriminalise,_20).
 2185opposite(v,segregate,desegregate,_20).
 2186opposite(v,repatriate,expatriate,_20).
 2187opposite(v,classify,declassify,_20).
 2188opposite(v,restrict,derestrict,_20).
 2189opposite(v,regulate,deregulate,_20).
 2190opposite(v,behave,misbehave,_20).
 2191opposite(v,obey,disobey,_20).
 2192opposite(v,exempt,enforce,_20).
 2193opposite(v,purge,rehabilitate,_20).
 2194opposite(v,defend,prosecute,_20).
 2195opposite(v,colonize,decolonize,_20).
 2196opposite(v,colonise,decolonise,_20).
 2197opposite(v,fail,manage,_20).
 2198opposite(v,miss,attend,_20).
 2199opposite(v,survive,succumb,_20).
 2200opposite(v,obviate,necessitate,_20).
 2201opposite(v,miss,have,_20).
 2202opposite(v,deviate,conform,_20).
 2203opposite(v,equal,differ,_20).
 2204opposite(v,'go out','come in',_20).
 2205opposite(v,violate,'conform to',_20).
 2206opposite(v,satisfy,'fall short of',_20).
 2207opposite(v,balance,unbalance,_20).
 2208opposite(v,continue,discontinue,_20).
 2209opposite(v,defy,'lend oneself',_20).
 2210opposite(v,ignite,extinguish,_20).
 2211opposite(v,emit,absorb,_20).
 2212opposite(v,overcast,'clear up',_20).
 2213opposite(a,able,unable,_20).
 2214opposite(a,adaxial,abaxial,_20).
 2215opposite(a,basiscopic,acroscopic,_20).
 2216opposite(a,adducent,abducent,_20).
 2217opposite(a,dying,nascent,_20).
 2218opposite(a,abridged,unabridged,_20).
 2219opposite(a,relative,absolute,_20).
 2220opposite(a,absorbent,nonabsorbent,_20).
 2221opposite(a,adsorbent,nonadsorbent,_20).
 2222opposite(a,adsorbable,absorbable,_20).
 2223opposite(a,gluttonous,abstemious,_20).
 2224opposite(a,concrete,abstract,_20).
 2225opposite(a,scarce,abundant,_20).
 2226opposite(a,abused,unabused,_20).
 2227opposite(a,acceptable,unacceptable,_20).
 2228opposite(a,accessible,inaccessible,_20).
 2229opposite(a,accommodating,unaccommodating,_20).
 2230opposite(a,accurate,inaccurate,_20).
 2231opposite(a,accustomed,unaccustomed,_20).
 2232opposite(a,acidic,alkaline,_20).
 2233opposite(a,acidic,amphoteric,_20).
 2234opposite(a,'acid-loving','alkaline-loving',_20).
 2235opposite(a,acknowledged,unacknowledged,_20).
 2236opposite(a,acquisitive,unacquisitive,_20).
 2237opposite(a,basipetal,acropetal,_20).
 2238opposite(a,active,inactive,_20).
 2239opposite(a,active,passive,_20).
 2240opposite(a,active,dormant,_20).
 2241opposite(a,active,extinct,_20).
 2242opposite(a,active,stative,_20).
 2243opposite(a,actual,potential,_20).
 2244opposite(a,acute,chronic,_20).
 2245opposite(a,virulent,avirulent,_20).
 2246opposite(a,adaptive,maladaptive,_20).
 2247opposite(a,addicted,unaddicted,_20).
 2248opposite(a,addictive,nonaddictive,_20).
 2249opposite(a,additive,subtractive,_20).
 2250opposite(a,addressed,unaddressed,_20).
 2251opposite(a,adequate,inadequate,_20).
 2252opposite(a,adhesive,nonadhesive,_20).
 2253opposite(a,adjective,substantive,_20).
 2254opposite(a,adoptable,unadoptable,_20).
 2255opposite(a,adorned,unadorned,_20).
 2256opposite(a,cholinergic,anticholinergic,_20).
 2257opposite(a,adroit,maladroit,_20).
 2258opposite(a,advantageous,disadvantageous,_20).
 2259opposite(a,adventurous,unadventurous,_20).
 2260opposite(a,advisable,inadvisable,_20).
 2261opposite(a,'ill-advised','well-advised',_20).
 2262opposite(a,aerobic,anaerobic,_20).
 2263opposite(a,aesthetic,inaesthetic,_20).
 2264opposite(a,affected,unaffected,_20).
 2265opposite(a,rejective,acceptive,_20).
 2266opposite(a,afloat,aground,_20).
 2267opposite(a,afraid,unafraid,_20).
 2268opposite(a,aggressive,unaggressive,_20).
 2269opposite(a,agitated,unagitated,_20).
 2270opposite(a,agreeable,disagreeable,_20).
 2271opposite(a,'air-to-air','air-to-surface',_20).
 2272opposite(a,alert,unalert,_20).
 2273opposite(a,heuristic,algorithmic,_20).
 2274opposite(a,alienable,inalienable,_20).
 2275opposite(a,dead,alive,_20).
 2276opposite(a,eccrine,apocrine,_20).
 2277opposite(a,artesian,subartesian,_20).
 2278opposite(a,alphabetic,analphabetic,_20).
 2279opposite(a,precocial,altricial,_20).
 2280opposite(a,egoistic,altruistic,_20).
 2281opposite(a,ambiguous,unambiguous,_20).
 2282opposite(a,ambitious,unambitious,_20).
 2283opposite(a,ametropic,emmetropic,_20).
 2284opposite(a,ample,meager,_20).
 2285opposite(a,anabolic,catabolic,_20).
 2286opposite(a,anaclinal,cataclinal,_20).
 2287opposite(a,astigmatic,anastigmatic,_20).
 2288opposite(a,synclinal,anticlinal,_20).
 2289opposite(a,anadromous,catadromous,_20).
 2290opposite(a,anabatic,katabatic,_20).
 2291opposite(a,oral,anal,_20).
 2292opposite(a,digital,analogue,_20).
 2293opposite(a,analytic,synthetic,_20).
 2294opposite(a,inflectional,derivational,_20).
 2295opposite(a,syncarpous,apocarpous,_20).
 2296opposite(a,angry,unangry,_20).
 2297opposite(a,resentful,unresentful,_20).
 2298opposite(a,sentient,insentient,_20).
 2299opposite(a,animate,inanimate,_20).
 2300opposite(a,animated,unanimated,_20).
 2301opposite(a,enlivened,unenlivened,_20).
 2302opposite(a,onymous,anonymous,_20).
 2303opposite(a,postmortem,antemortem,_20).
 2304opposite(a,subsequent,antecedent,_20).
 2305opposite(a,retrorse,antrorse,_20).
 2306opposite(a,aquatic,terrestrial,_20).
 2307opposite(a,aquatic,amphibious,_20).
 2308opposite(a,preceding,succeeding,_20).
 2309opposite(a,precedented,unprecedented,_20).
 2310opposite(a,prehensile,nonprehensile,_20).
 2311opposite(a,prenatal,perinatal,_20).
 2312opposite(a,prenatal,postnatal,_20).
 2313opposite(a,preprandial,postprandial,_20).
 2314opposite(a,prewar,postwar,_20).
 2315opposite(a,retrograde,anterograde,_20).
 2316opposite(a,postmeridian,antemeridian,_20).
 2317opposite(a,anterior,posterior,_20).
 2318opposite(a,dorsal,ventral,_20).
 2319opposite(a,appealable,unappealable,_20).
 2320opposite(a,appendaged,unappendaged,_20).
 2321opposite(a,appetizing,unappetizing,_20).
 2322opposite(a,approachable,unapproachable,_20).
 2323opposite(a,appropriate,inappropriate,_20).
 2324opposite(a,due,undue,_20).
 2325opposite(a,apropos,malapropos,_20).
 2326opposite(a,'a priori','a posteriori',_20).
 2327opposite(a,apteral,peripteral,_20).
 2328opposite(a,arbitrable,nonarbitrable,_20).
 2329opposite(a,columned,noncolumned,_20).
 2330opposite(a,arboreal,nonarboreal,_20).
 2331opposite(a,arenaceous,argillaceous,_20).
 2332opposite(a,armed,unarmed,_20).
 2333opposite(a,armored,unarmored,_20).
 2334opposite(a,armed,armless,_20).
 2335opposite(a,artful,artless,_20).
 2336opposite(a,articulate,inarticulate,_20).
 2337opposite(a,speaking,nonspeaking,_20).
 2338opposite(a,articulated,unarticulated,_20).
 2339opposite(a,ashamed,unashamed,_20).
 2340opposite(a,assertive,unassertive,_20).
 2341opposite(a,associative,nonassociative,_20).
 2342opposite(a,attached,unattached,_20).
 2343opposite(a,affixed,unaffixed,_20).
 2344opposite(a,sessile,pedunculate,_20).
 2345opposite(a,stuck,unstuck,_20).
 2346opposite(a,detachable,attachable,_20).
 2347opposite(a,wary,unwary,_20).
 2348opposite(a,attentive,inattentive,_20).
 2349opposite(a,attractive,unattractive,_20).
 2350opposite(a,appealing,unappealing,_20).
 2351opposite(a,attributable,unattributable,_20).
 2352opposite(a,predicative,attributive,_20).
 2353opposite(a,pregnant,nonpregnant,_20).
 2354opposite(a,audible,inaudible,_20).
 2355opposite(a,sonic,subsonic,_20).
 2356opposite(a,sonic,supersonic,_20).
 2357opposite(a,auspicious,inauspicious,_20).
 2358opposite(a,propitious,unpropitious,_20).
 2359opposite(a,authorized,unauthorized,_20).
 2360opposite(a,constitutional,unconstitutional,_20).
 2361opposite(a,autochthonous,allochthonous,_20).
 2362opposite(a,autoecious,heteroecious,_20).
 2363opposite(a,autogenous,heterogenous,_20).
 2364opposite(a,manual,automatic,_20).
 2365opposite(a,available,unavailable,_20).
 2366opposite(a,awake,asleep,_20).
 2367opposite(a,astringent,nonastringent,_20).
 2368opposite(a,aware,unaware,_20).
 2369opposite(a,witting,unwitting,_20).
 2370opposite(a,alarming,unalarming,_20).
 2371opposite(a,anemophilous,entomophilous,_20).
 2372opposite(a,reassuring,unreassuring,_20).
 2373opposite(a,leading,following,_20).
 2374opposite(a,backed,backless,_20).
 2375opposite(a,forward,backward,_20).
 2376opposite(a,balconied,unbalconied,_20).
 2377opposite(a,barreled,unbarreled,_20).
 2378opposite(a,beaked,beakless,_20).
 2379opposite(a,bedded,bedless,_20).
 2380opposite(a,beneficed,unbeneficed,_20).
 2381opposite(a,stratified,unstratified,_20).
 2382opposite(a,ferned,fernless,_20).
 2383opposite(a,grassy,grassless,_20).
 2384opposite(a,gusseted,ungusseted,_20).
 2385opposite(a,hairy,hairless,_20).
 2386opposite(a,awned,awnless,_20).
 2387opposite(a,bearing,nonbearing,_20).
 2388opposite(a,ugly,beautiful,_20).
 2389opposite(a,bellied,bellyless,_20).
 2390opposite(a,banded,unbanded,_20).
 2391opposite(a,belted,unbelted,_20).
 2392opposite(a,maleficent,beneficent,_20).
 2393opposite(a,malicious,unmalicious,_20).
 2394opposite(a,malign,benign,_20).
 2395opposite(a,worsening,bettering,_20).
 2396opposite(a,bicameral,unicameral,_20).
 2397opposite(a,bidirectional,unidirectional,_20).
 2398opposite(a,faced,faceless,_20).
 2399opposite(a,bibbed,bibless,_20).
 2400opposite(a,unilateral,multilateral,_20).
 2401opposite(a,bimodal,unimodal,_20).
 2402opposite(a,monaural,binaural,_20).
 2403opposite(a,binucleate,trinucleate,_20).
 2404opposite(a,binucleate,mononuclear,_20).
 2405opposite(a,bipedal,quadrupedal,_20).
 2406opposite(a,biped,quadruped,_20).
 2407opposite(a,blond,brunet,_20).
 2408opposite(a,blemished,unblemished,_20).
 2409opposite(a,bloody,bloodless,_20).
 2410opposite(a,bound,unbound,_20).
 2411opposite(a,laced,unlaced,_20).
 2412opposite(a,tied,untied,_20).
 2413opposite(a,tangled,untangled,_20).
 2414opposite(a,bordered,unbordered,_20).
 2415opposite(a,lotic,lentic,_20).
 2416opposite(a,'lower-class','middle-class',_20).
 2417opposite(a,brachycephalic,dolichocephalic,_20).
 2418opposite(a,brave,cowardly,_20).
 2419opposite(a,gutsy,gutless,_20).
 2420opposite(a,'breast-fed','bottle-fed',_20).
 2421opposite(a,breathing,breathless,_20).
 2422opposite(a,crystalline,noncrystalline,_20).
 2423opposite(a,landed,landless,_20).
 2424opposite(a,shaded,unshaded,_20).
 2425opposite(a,moonlit,moonless,_20).
 2426opposite(a,bridgeable,unbridgeable,_20).
 2427opposite(a,dull,bright,_20).
 2428opposite(a,dimmed,undimmed,_20).
 2429opposite(a,prejudiced,unprejudiced,_20).
 2430opposite(a,'broad-minded','narrow-minded',_20).
 2431opposite(a,reconstructed,unreconstructed,_20).
 2432opposite(a,broken,unbroken,_20).
 2433opposite(a,sisterly,brotherly,_20).
 2434opposite(a,exergonic,endergonic,_20).
 2435opposite(a,identical,fraternal,_20).
 2436opposite(a,buried,unburied,_20).
 2437opposite(a,idle,busy,_20).
 2438opposite(a,bony,boneless,_20).
 2439opposite(a,buttoned,unbuttoned,_20).
 2440opposite(a,socialistic,capitalistic,_20).
 2441opposite(a,euphonious,cacophonous,_20).
 2442opposite(a,calculable,incalculable,_20).
 2443opposite(a,calm,stormy,_20).
 2444opposite(a,camphorated,uncamphorated,_20).
 2445opposite(a,capable,incapable,_20).
 2446opposite(a,'cared-for','uncared-for',_20).
 2447opposite(a,careful,careless,_20).
 2448opposite(a,carnivorous,insectivorous,_20).
 2449opposite(a,herbivorous,carnivorous,_20).
 2450opposite(a,holozoic,holophytic,_20).
 2451opposite(a,carpellate,acarpelous,_20).
 2452opposite(a,carpeted,uncarpeted,_20).
 2453opposite(a,'carvel-built','clinker-built',_20).
 2454opposite(a,carved,uncarved,_20).
 2455opposite(a,acatalectic,hypercatalectic,_20).
 2456opposite(a,catalectic,acatalectic,_20).
 2457opposite(a,radical,cauline,_20).
 2458opposite(a,censored,uncensored,_20).
 2459opposite(a,caudate,acaudate,_20).
 2460opposite(a,caulescent,acaulescent,_20).
 2461opposite(a,causative,noncausative,_20).
 2462opposite(a,cautious,incautious,_20).
 2463opposite(a,cellular,noncellular,_20).
 2464opposite(a,coherent,incoherent,_20).
 2465opposite(a,compartmented,uncompartmented,_20).
 2466opposite(a,porous,nonporous,_20).
 2467opposite(a,central,peripheral,_20).
 2468opposite(a,centripetal,centrifugal,_20).
 2469opposite(a,efferent,afferent,_20).
 2470opposite(a,centralizing,decentralizing,_20).
 2471opposite(a,certain,uncertain,_20).
 2472opposite(a,sure,unsure,_20).
 2473opposite(a,convinced,unconvinced,_20).
 2474opposite(a,diffident,confident,_20).
 2475opposite(a,certified,uncertified,_20).
 2476opposite(a,evitable,inevitable,_20).
 2477opposite(a,preventable,unpreventable,_20).
 2478opposite(a,changeable,unchangeable,_20).
 2479opposite(a,commutable,incommutable,_20).
 2480opposite(a,alterable,unalterable,_20).
 2481opposite(a,modifiable,unmodifiable,_20).
 2482opposite(a,adjusted,unadjusted,_20).
 2483opposite(a,adjusted,maladjusted,_20).
 2484opposite(a,altered,unaltered,_20).
 2485opposite(a,amended,unamended,_20).
 2486opposite(a,changed,unchanged,_20).
 2487opposite(a,isotonic,isometric,_20).
 2488opposite(a,ionized,nonionized,_20).
 2489opposite(a,mutable,immutable,_20).
 2490opposite(a,characteristic,uncharacteristic,_20).
 2491opposite(a,charged,uncharged,_20).
 2492opposite(a,charitable,uncharitable,_20).
 2493opposite(a,chartered,unchartered,_20).
 2494opposite(a,owned,unowned,_20).
 2495opposite(a,chaste,unchaste,_20).
 2496opposite(a,cheerful,depressing,_20).
 2497opposite(a,chlamydeous,achlamydeous,_20).
 2498opposite(a,chondritic,achondritic,_20).
 2499opposite(a,triclinic,monoclinic,_20).
 2500opposite(a,polychromatic,monochromatic,_20).
 2501opposite(a,chromatic,achromatic,_20).
 2502opposite(a,saturated,unsaturated,_20).
 2503opposite(a,color,'black-and-white',_20).
 2504opposite(a,colored,uncolored,_20).
 2505opposite(a,stained,unstained,_20).
 2506opposite(a,colorful,colorless,_20).
 2507opposite(a,colourful,colourless,_20).
 2508opposite(a,tramontane,cismontane,_20).
 2509opposite(a,christian,unchristian,_20).
 2510opposite(a,civilized,noncivilized,_20).
 2511opposite(a,classical,nonclassical,_20).
 2512opposite(a,classified,unclassified,_20).
 2513opposite(a,analyzed,unanalyzed,_20).
 2514opposite(a,radioactive,nonradioactive,_20).
 2515opposite(a,clean,unclean,_20).
 2516opposite(a,clear,unclear,_20).
 2517opposite(a,clear,opaque,_20).
 2518opposite(a,radiopaque,radiolucent,_20).
 2519opposite(a,confused,clearheaded,_20).
 2520opposite(a,clement,inclement,_20).
 2521opposite(a,smart,stupid,_20).
 2522opposite(a,clockwise,counterclockwise,_20).
 2523opposite(a,far,near,_20).
 2524opposite(a,close,distant,_20).
 2525opposite(a,cousinly,uncousinly,_20).
 2526opposite(a,clothed,unclothed,_20).
 2527opposite(a,saddled,unsaddled,_20).
 2528opposite(a,clear,cloudy,_20).
 2529opposite(a,inland,coastal,_20).
 2530opposite(a,inshore,offshore,_20).
 2531opposite(a,collapsible,noncollapsible,_20).
 2532opposite(a,crannied,uncrannied,_20).
 2533opposite(a,collective,distributive,_20).
 2534opposite(a,suppressed,publicized,_20).
 2535opposite(a,published,unpublished,_20).
 2536opposite(a,publishable,unpublishable,_20).
 2537opposite(a,reported,unreported,_20).
 2538opposite(a,reportable,unreportable,_20).
 2539opposite(a,combinative,noncombinative,_20).
 2540opposite(a,combustible,noncombustible,_20).
 2541opposite(a,explosive,nonexplosive,_20).
 2542opposite(a,lighted,unlighted,_20).
 2543opposite(a,commodious,incommodious,_20).
 2544opposite(a,comfortable,uncomfortable,_20).
 2545opposite(a,commensurate,incommensurate,_20).
 2546opposite(a,proportionate,disproportionate,_20).
 2547opposite(a,commercial,noncommercial,_20).
 2548opposite(a,residential,nonresidential,_20).
 2549opposite(a,commissioned,noncommissioned,_20).
 2550opposite(a,common,uncommon,_20).
 2551opposite(a,usual,unusual,_20).
 2552opposite(a,hydrophobic,hydrophilic,_20).
 2553opposite(a,oleophobic,oleophilic,_20).
 2554opposite(a,common,individual,_20).
 2555opposite(a,communicative,uncommunicative,_20).
 2556opposite(a,loose,compact,_20).
 2557opposite(a,comparable,incomparable,_20).
 2558opposite(a,compassionate,uncompassionate,_20).
 2559opposite(a,compatible,incompatible,_20).
 2560opposite(a,miscible,immiscible,_20).
 2561opposite(a,competent,incompetent,_20).
 2562opposite(a,competitive,noncompetitive,_20).
 2563opposite(a,complaining,uncomplaining,_20).
 2564opposite(a,compressible,incompressible,_20).
 2565opposite(a,whole,fractional,_20).
 2566opposite(a,committed,uncommitted,_20).
 2567opposite(a,dedicated,undedicated,_20).
 2568opposite(a,complete,incomplete,_20).
 2569opposite(a,comprehensive,noncomprehensive,_20).
 2570opposite(a,composed,discomposed,_20).
 2571opposite(a,comprehensible,incomprehensible,_20).
 2572opposite(a,convex,concave,_20).
 2573opposite(a,distributed,concentrated,_20).
 2574opposite(a,eccentric,concentric,_20).
 2575opposite(a,concerned,unconcerned,_20).
 2576opposite(a,prolix,concise,_20).
 2577opposite(a,conclusive,inconclusive,_20).
 2578opposite(a,consummated,unconsummated,_20).
 2579opposite(a,coordinating,subordinating,_20).
 2580opposite(a,accordant,discordant,_20).
 2581opposite(a,expanded,contracted,_20).
 2582opposite(a,atrophied,hypertrophied,_20).
 2583opposite(a,conditional,unconditional,_20).
 2584opposite(a,enforceable,unenforceable,_20).
 2585opposite(a,enforced,unenforced,_20).
 2586opposite(a,conductive,nonconductive,_20).
 2587opposite(a,confined,unconfined,_20).
 2588opposite(a,crowded,uncrowded,_20).
 2589opposite(a,congenial,uncongenial,_20).
 2590opposite(a,congruent,incongruent,_20).
 2591opposite(a,congruous,incongruous,_20).
 2592opposite(a,disjunctive,conjunctive,_20).
 2593opposite(a,disjunct,conjunct,_20).
 2594opposite(a,connected,unconnected,_20).
 2595opposite(a,conquerable,unconquerable,_20).
 2596opposite(a,conscious,unconscious,_20).
 2597opposite(a,desecrated,consecrated,_20).
 2598opposite(a,priestly,unpriestly,_20).
 2599opposite(a,consistent,inconsistent,_20).
 2600opposite(a,conspicuous,inconspicuous,_20).
 2601opposite(a,discernible,indiscernible,_20).
 2602opposite(a,distinguishable,indistinguishable,_20).
 2603opposite(a,constant,inconstant,_20).
 2604opposite(a,destructive,constructive,_20).
 2605opposite(a,contented,discontented,_20).
 2606opposite(a,contestable,incontestable,_20).
 2607opposite(a,continent,incontinent,_20).
 2608opposite(a,sporadic,continual,_20).
 2609opposite(a,continuous,discontinuous,_20).
 2610opposite(a,continued,discontinued,_20).
 2611opposite(a,controlled,uncontrolled,_20).
 2612opposite(a,controversial,uncontroversial,_20).
 2613opposite(a,argumentative,unargumentative,_20).
 2614opposite(a,convenient,inconvenient,_20).
 2615opposite(a,conventional,unconventional,_20).
 2616opposite(a,traditional,nontraditional,_20).
 2617opposite(a,divergent,convergent,_20).
 2618opposite(a,branchy,branchless,_20).
 2619opposite(a,convincing,unconvincing,_20).
 2620opposite(a,raw,cooked,_20).
 2621opposite(a,cooperative,uncooperative,_20).
 2622opposite(a,corrupt,incorrupt,_20).
 2623opposite(a,synergistic,antagonistic,_20).
 2624opposite(a,considerable,inconsiderable,_20).
 2625opposite(a,substantial,insubstantial,_20).
 2626opposite(a,material,immaterial,_20).
 2627opposite(a,bodied,unbodied,_20).
 2628opposite(a,brainwashed,unbrainwashed,_20).
 2629opposite(a,corporeal,incorporeal,_20).
 2630opposite(a,correct,incorrect,_20).
 2631opposite(a,corrected,uncorrected,_20).
 2632opposite(a,corrigible,incorrigible,_20).
 2633opposite(a,provincial,cosmopolitan,_20).
 2634opposite(a,costive,laxative,_20).
 2635opposite(a,constipated,unconstipated,_20).
 2636opposite(a,considerate,inconsiderate,_20).
 2637opposite(a,courteous,discourteous,_20).
 2638opposite(a,polite,impolite,_20).
 2639opposite(a,civil,uncivil,_20).
 2640opposite(a,civil,sidereal,_20).
 2641opposite(a,creative,uncreative,_20).
 2642opposite(a,credible,incredible,_20).
 2643opposite(a,credulous,incredulous,_20).
 2644opposite(a,critical,uncritical,_20).
 2645opposite(a,judgmental,nonjudgmental,_20).
 2646opposite(a,critical,noncritical,_20).
 2647opposite(a,crossed,uncrossed,_20).
 2648opposite(a,walleyed,'cross-eyed',_20).
 2649opposite(a,crowned,uncrowned,_20).
 2650opposite(a,crucial,noncrucial,_20).
 2651opposite(a,crystallized,uncrystallized,_20).
 2652opposite(a,cubic,linear,_20).
 2653opposite(a,cubic,planar,_20).
 2654opposite(a,unidimensional,multidimensional,_20).
 2655opposite(a,cut,uncut,_20).
 2656opposite(a,curious,incurious,_20).
 2657opposite(a,current,noncurrent,_20).
 2658opposite(a,cursed,blessed,_20).
 2659opposite(a,endowed,unendowed,_20).
 2660opposite(a,curtained,curtainless,_20).
 2661opposite(a,handmade,'machine-made',_20).
 2662opposite(a,homemade,'factory-made',_20).
 2663opposite(a,cyclic,noncyclic,_20).
 2664opposite(a,cyclic,acyclic,_20).
 2665opposite(a,annual,biennial,_20).
 2666opposite(a,annual,perennial,_20).
 2667opposite(a,diurnal,nocturnal,_20).
 2668opposite(a,damaged,undamaged,_20).
 2669opposite(a,datable,undatable,_20).
 2670opposite(a,deaf,hearing,_20).
 2671opposite(a,decent,indecent,_20).
 2672opposite(a,decisive,indecisive,_20).
 2673opposite(a,declarative,interrogative,_20).
 2674opposite(a,declaratory,interrogatory,_20).
 2675opposite(a,declared,undeclared,_20).
 2676opposite(a,decorous,indecorous,_20).
 2677opposite(a,deductible,nondeductible,_20).
 2678opposite(a,deep,shallow,_20).
 2679opposite(a,'de jure','de facto',_20).
 2680opposite(a,defeasible,indefeasible,_20).
 2681opposite(a,defeated,undefeated,_20).
 2682opposite(a,defiant,compliant,_20).
 2683opposite(a,defined,undefined,_20).
 2684opposite(a,'ill-defined','well-defined',_20).
 2685opposite(a,derived,underived,_20).
 2686opposite(a,inflected,uninflected,_20).
 2687opposite(a,definite,indefinite,_20).
 2688opposite(a,dehiscent,indehiscent,_20).
 2689opposite(a,elated,dejected,_20).
 2690opposite(a,rugged,delicate,_20).
 2691opposite(a,breakable,unbreakable,_20).
 2692opposite(a,demanding,undemanding,_20).
 2693opposite(a,imperative,beseeching,_20).
 2694opposite(a,democratic,undemocratic,_20).
 2695opposite(a,arbitrary,nonarbitrary,_20).
 2696opposite(a,demonstrative,undemonstrative,_20).
 2697opposite(a,deniable,undeniable,_20).
 2698opposite(a,denotative,connotative,_20).
 2699opposite(a,reliable,unreliable,_20).
 2700opposite(a,dependable,undependable,_20).
 2701opposite(a,dependent,independent,_20).
 2702opposite(a,aligned,nonaligned,_20).
 2703opposite(a,descriptive,prescriptive,_20).
 2704opposite(a,descriptive,undescriptive,_20).
 2705opposite(a,desirable,undesirable,_20).
 2706opposite(a,preserved,destroyed,_20).
 2707opposite(a,destructible,indestructible,_20).
 2708opposite(a,determinable,indeterminable,_20).
 2709opposite(a,determinate,indeterminate,_20).
 2710opposite(a,developed,undeveloped,_20).
 2711opposite(a,dextral,sinistral,_20).
 2712opposite(a,diabatic,adiabatic,_20).
 2713opposite(a,differentiated,undifferentiated,_20).
 2714opposite(a,easy,difficult,_20).
 2715opposite(a,plantigrade,digitigrade,_20).
 2716opposite(a,dignified,undignified,_20).
 2717opposite(a,statesmanlike,unstatesmanlike,_20).
 2718opposite(a,presidential,unpresidential,_20).
 2719opposite(a,dicotyledonous,monocotyledonous,_20).
 2720opposite(a,diligent,negligent,_20).
 2721opposite(a,diluted,undiluted,_20).
 2722opposite(a,diplomatic,undiplomatic,_20).
 2723opposite(a,direct,indirect,_20).
 2724opposite(a,direct,alternating,_20).
 2725opposite(a,direct,inverse,_20).
 2726opposite(a,mediate,immediate,_20).
 2727opposite(a,discerning,undiscerning,_20).
 2728opposite(a,discreet,indiscreet,_20).
 2729opposite(a,discriminate,indiscriminate,_20).
 2730opposite(a,discriminating,undiscriminating,_20).
 2731opposite(a,disposable,nondisposable,_20).
 2732opposite(a,returnable,nonreturnable,_20).
 2733opposite(a,distal,proximal,_20).
 2734opposite(a,distinct,indistinct,_20).
 2735opposite(a,focused,unfocused,_20).
 2736opposite(a,diversified,undiversified,_20).
 2737opposite(a,divisible,indivisible,_20).
 2738opposite(a,documented,undocumented,_20).
 2739opposite(a,submissive,domineering,_20).
 2740opposite(a,servile,unservile,_20).
 2741opposite(a,dominant,subordinate,_20).
 2742opposite(a,dominant,recessive,_20).
 2743opposite(a,'single-barreled','double-barreled',_20).
 2744opposite(a,'single-breasted','double-breasted',_20).
 2745opposite(a,dramatic,undramatic,_20).
 2746opposite(a,actable,unactable,_20).
 2747opposite(a,theatrical,untheatrical,_20).
 2748opposite(a,drinkable,undrinkable,_20).
 2749opposite(a,sober,intoxicated,_20).
 2750opposite(a,dull,sharp,_20).
 2751opposite(a,eventful,uneventful,_20).
 2752opposite(a,dull,lively,_20).
 2753opposite(a,dynamic,undynamic,_20).
 2754opposite(a,eager,uneager,_20).
 2755opposite(a,eared,earless,_20).
 2756opposite(a,earned,unearned,_20).
 2757opposite(a,easy,uneasy,_20).
 2758opposite(a,west,east,_20).
 2759opposite(a,western,eastern,_20).
 2760opposite(a,endomorphic,ectomorphic,_20).
 2761opposite(a,edible,inedible,_20).
 2762opposite(a,educated,uneducated,_20).
 2763opposite(a,numerate,innumerate,_20).
 2764opposite(a,operative,inoperative,_20).
 2765opposite(a,effective,ineffective,_20).
 2766opposite(a,effortful,effortless,_20).
 2767opposite(a,efficacious,inefficacious,_20).
 2768opposite(a,efficient,inefficient,_20).
 2769opposite(a,forceful,forceless,_20).
 2770opposite(a,elastic,inelastic,_20).
 2771opposite(a,elective,appointive,_20).
 2772opposite(a,assigned,unassigned,_20).
 2773opposite(a,optional,obligatory,_20).
 2774opposite(a,elegant,inelegant,_20).
 2775opposite(a,eligible,ineligible,_20).
 2776opposite(a,emotional,unemotional,_20).
 2777opposite(a,empirical,theoretical,_20).
 2778opposite(a,salaried,freelance,_20).
 2779opposite(a,employed,unemployed,_20).
 2780opposite(a,employable,unemployable,_20).
 2781opposite(a,enchanted,disenchanted,_20).
 2782opposite(a,encouraging,discouraging,_20).
 2783opposite(a,encumbered,unencumbered,_20).
 2784opposite(a,burdened,unburdened,_20).
 2785opposite(a,exocentric,endocentric,_20).
 2786opposite(a,exogamous,endogamous,_20).
 2787opposite(a,endogamous,autogamous,_20).
 2788opposite(a,exoergic,endoergic,_20).
 2789opposite(a,exothermic,endothermic,_20).
 2790opposite(a,exogenous,endogenous,_20).
 2791opposite(a,exogenic,endogenic,_20).
 2792opposite(a,'run-on','end-stopped',_20).
 2793opposite(a,lethargic,energetic,_20).
 2794opposite(a,enfranchised,disenfranchised,_20).
 2795opposite(a,exportable,unexportable,_20).
 2796opposite(a,exploratory,nonexploratory,_20).
 2797opposite(a,inquiring,uninquiring,_20).
 2798opposite(a,increased,decreased,_20).
 2799opposite(a,reducible,irreducible,_20).
 2800opposite(a,enlightened,unenlightened,_20).
 2801opposite(a,enterprising,unenterprising,_20).
 2802opposite(a,enthusiastic,unenthusiastic,_20).
 2803opposite(a,desirous,undesirous,_20).
 2804opposite(a,epizoic,entozoic,_20).
 2805opposite(a,equal,unequal,_20).
 2806opposite(a,balanced,unbalanced,_20).
 2807opposite(a,isotonic,hypertonic,_20).
 2808opposite(a,isotonic,hypotonic,_20).
 2809opposite(a,equivocal,unequivocal,_20).
 2810opposite(a,eradicable,ineradicable,_20).
 2811opposite(a,exoteric,esoteric,_20).
 2812opposite(a,dispensable,indispensable,_20).
 2813opposite(a,estimable,contemptible,_20).
 2814opposite(a,ethical,unethical,_20).
 2815opposite(a,complimentary,uncomplimentary,_20).
 2816opposite(a,flattering,unflattering,_20).
 2817opposite(a,euphemistic,dysphemistic,_20).
 2818opposite(a,euphoric,dysphoric,_20).
 2819opposite(a,even,uneven,_20).
 2820opposite(a,evergreen,deciduous,_20).
 2821opposite(a,exact,inexact,_20).
 2822opposite(a,convertible,inconvertible,_20).
 2823opposite(a,exchangeable,unexchangeable,_20).
 2824opposite(a,excitable,unexcitable,_20).
 2825opposite(a,excited,unexcited,_20).
 2826opposite(a,exciting,unexciting,_20).
 2827opposite(a,inculpatory,exculpatory,_20).
 2828opposite(a,exhaustible,inexhaustible,_20).
 2829opposite(a,exhausted,unexhausted,_20).
 2830opposite(a,existent,nonexistent,_20).
 2831opposite(a,expected,unexpected,_20).
 2832opposite(a,expedient,inexpedient,_20).
 2833opposite(a,expendable,unexpendable,_20).
 2834opposite(a,cheap,expensive,_20).
 2835opposite(a,experienced,inexperienced,_20).
 2836opposite(a,expired,unexpired,_20).
 2837opposite(a,explicable,inexplicable,_20).
 2838opposite(a,implicit,explicit,_20).
 2839opposite(a,exploited,unexploited,_20).
 2840opposite(a,expressible,inexpressible,_20).
 2841opposite(a,extensile,nonextensile,_20).
 2842opposite(a,extricable,inextricable,_20).
 2843opposite(a,bowed,plucked,_20).
 2844opposite(a,fingered,fingerless,_20).
 2845opposite(a,expansive,unexpansive,_20).
 2846opposite(a,extinguishable,inextinguishable,_20).
 2847opposite(a,internal,external,_20).
 2848opposite(a,outer,inner,_20).
 2849opposite(a,inward,outward,_20).
 2850opposite(a,interior,exterior,_20).
 2851opposite(a,eyed,eyeless,_20).
 2852opposite(a,playable,unplayable,_20).
 2853opposite(a,foul,fair,_20).
 2854opposite(a,fair,unfair,_20).
 2855opposite(a,equitable,inequitable,_20).
 2856opposite(a,faithful,unfaithful,_20).
 2857opposite(a,loyal,disloyal,_20).
 2858opposite(a,fallible,infallible,_20).
 2859opposite(a,familiar,unfamiliar,_20).
 2860opposite(a,fashionable,unfashionable,_20).
 2861opposite(a,stylish,styleless,_20).
 2862opposite(a,slow,fast,_20).
 2863opposite(a,fastidious,unfastidious,_20).
 2864opposite(a,fatty,nonfat,_20).
 2865opposite(a,fatal,nonfatal,_20).
 2866opposite(a,curable,incurable,_20).
 2867opposite(a,fathomable,unfathomable,_20).
 2868opposite(a,favorable,unfavorable,_20).
 2869opposite(a,feathered,unfeathered,_20).
 2870opposite(a,felicitous,infelicitous,_20).
 2871opposite(a,sterile,fertile,_20).
 2872opposite(a,finished,unfinished,_20).
 2873opposite(a,finite,infinite,_20).
 2874opposite(a,last,first,_20).
 2875opposite(a,terminal,intermediate,_20).
 2876opposite(a,first,second,_20).
 2877opposite(a,fissile,nonfissile,_20).
 2878opposite(a,fissionable,nonfissionable,_20).
 2879opposite(a,fit,unfit,_20).
 2880opposite(a,flat,contrasty,_20).
 2881opposite(a,flexible,inflexible,_20).
 2882opposite(a,compromising,uncompromising,_20).
 2883opposite(a,rigid,nonrigid,_20).
 2884opposite(a,adaptable,unadaptable,_20).
 2885opposite(a,orthotropous,campylotropous,_20).
 2886opposite(a,anatropous,amphitropous,_20).
 2887opposite(a,curly,straight,_20).
 2888opposite(a,footed,footless,_20).
 2889opposite(a,toed,toeless,_20).
 2890opposite(a,splayfooted,'pigeon-toed',_20).
 2891opposite(a,aft,fore,_20).
 2892opposite(a,forehand,backhand,_20).
 2893opposite(a,native,adopted,_20).
 2894opposite(a,native,foreign,_20).
 2895opposite(a,native,nonnative,_20).
 2896opposite(a,foreign,domestic,_20).
 2897opposite(a,domestic,undomestic,_20).
 2898opposite(a,forgettable,unforgettable,_20).
 2899opposite(a,forgiving,unforgiving,_20).
 2900opposite(a,formal,informal,_20).
 2901opposite(a,fortunate,unfortunate,_20).
 2902opposite(a,fragrant,malodorous,_20).
 2903opposite(a,odorous,odorless,_20).
 2904opposite(a,scented,scentless,_20).
 2905opposite(a,fixed,unfixed,_20).
 2906opposite(a,free,unfree,_20).
 2907opposite(a,frequent,infrequent,_20).
 2908opposite(a,stale,fresh,_20).
 2909opposite(a,friendly,unfriendly,_20).
 2910opposite(a,frozen,unfrozen,_20).
 2911opposite(a,fruitful,unfruitful,_20).
 2912opposite(a,drained,undrained,_20).
 2913opposite(a,'part-time','full-time',_20).
 2914opposite(a,functional,nonfunctional,_20).
 2915opposite(a,functioning,malfunctioning,_20).
 2916opposite(a,rigged,unrigged,_20).
 2917opposite(a,equipped,unequipped,_20).
 2918opposite(a,fledged,unfledged,_20).
 2919opposite(a,framed,unframed,_20).
 2920opposite(a,furnished,unfurnished,_20).
 2921opposite(a,funded,unfunded,_20).
 2922opposite(a,fueled,unfueled,_20).
 2923opposite(a,specified,unspecified,_20).
 2924opposite(a,geared,ungeared,_20).
 2925opposite(a,specific,nonspecific,_20).
 2926opposite(a,local,national,_20).
 2927opposite(a,branchiate,abranchiate,_20).
 2928opposite(a,unitary,federal,_20).
 2929opposite(a,centralized,decentralized,_20).
 2930opposite(a,technical,nontechnical,_20).
 2931opposite(a,proprietary,nonproprietary,_20).
 2932opposite(a,stingy,generous,_20).
 2933opposite(a,generous,ungenerous,_20).
 2934opposite(a,genuine,counterfeit,_20).
 2935opposite(a,geocentric,heliocentric,_20).
 2936opposite(a,talented,untalented,_20).
 2937opposite(a,glazed,unglazed,_20).
 2938opposite(a,glorious,inglorious,_20).
 2939opposite(a,go,'no-go',_20).
 2940opposite(a,'ill-natured','good-natured',_20).
 2941opposite(a,awkward,graceful,_20).
 2942opposite(a,gracious,ungracious,_20).
 2943opposite(a,sudden,gradual,_20).
 2944opposite(a,grammatical,ungrammatical,_20).
 2945opposite(a,grateful,ungrateful,_20).
 2946opposite(a,haploid,diploid,_20).
 2947opposite(a,haploid,polyploid,_20).
 2948opposite(a,happy,unhappy,_20).
 2949opposite(a,regretful,unregretful,_20).
 2950opposite(a,soft,hard,_20).
 2951opposite(a,softhearted,hardhearted,_20).
 2952opposite(a,alcoholic,nonalcoholic,_20).
 2953opposite(a,harmful,harmless,_20).
 2954opposite(a,harmonious,inharmonious,_20).
 2955opposite(a,healthful,unhealthful,_20).
 2956opposite(a,medical,surgical,_20).
 2957opposite(a,operable,inoperable,_20).
 2958opposite(a,pyretic,antipyretic,_20).
 2959opposite(a,healthy,unhealthy,_20).
 2960opposite(a,dry,phlegmy,_20).
 2961opposite(a,earthly,heavenly,_20).
 2962opposite(a,digestible,indigestible,_20).
 2963opposite(a,headed,headless,_20).
 2964opposite(a,headed,unheaded,_20).
 2965opposite(a,light,heavy,_20).
 2966opposite(a,weighty,weightless,_20).
 2967opposite(a,'light-duty','heavy-duty',_20).
 2968opposite(a,'light-footed','heavy-footed',_20).
 2969opposite(a,heedful,heedless,_20).
 2970opposite(a,enabling,disabling,_20).
 2971opposite(a,helpful,unhelpful,_20).
 2972opposite(a,zygodactyl,heterodactyl,_20).
 2973opposite(a,homogeneous,heterogeneous,_20).
 2974opposite(a,homozygous,heterozygous,_20).
 2975opposite(a,homosexual,heterosexual,_20).
 2976opposite(a,hierarchical,nonhierarchical,_20).
 2977opposite(a,raised,lowered,_20).
 2978opposite(a,'low-tech','high-tech',_20).
 2979opposite(a,necked,neckless,_20).
 2980opposite(a,floored,ceilinged,_20).
 2981opposite(a,'low-sudsing','high-sudsing',_20).
 2982opposite(a,'low-interest','high-interest',_20).
 2983opposite(a,imitative,nonimitative,_20).
 2984opposite(a,echoic,nonechoic,_20).
 2985opposite(a,'low-resolution','high-resolution',_20).
 2986opposite(a,'low-rise','high-rise',_20).
 2987opposite(a,home,away,_20).
 2988opposite(a,homologous,heterologous,_20).
 2989opposite(a,homologous,autologous,_20).
 2990opposite(a,hipped,gabled,_20).
 2991opposite(a,hipped,hipless,_20).
 2992opposite(a,honest,dishonest,_20).
 2993opposite(a,truthful,untruthful,_20).
 2994opposite(a,honorable,dishonorable,_20).
 2995opposite(a,hopeful,hopeless,_20).
 2996opposite(a,institutionalized,noninstitutionalized,_20).
 2997opposite(a,institutional,noninstitutional,_20).
 2998opposite(a,iodinating,'de-iodinating',_20).
 2999opposite(a,consolable,inconsolable,_20).
 3000opposite(a,vertical,horizontal,_20).
 3001opposite(a,erect,unerect,_20).
 3002opposite(a,seated,standing,_20).
 3003opposite(a,hospitable,inhospitable,_20).
 3004opposite(a,hostile,amicable,_20).
 3005opposite(a,hot,cold,_20).
 3006opposite(a,vernal,summery,_20).
 3007opposite(a,vernal,autumnal,_20).
 3008opposite(a,human,nonhuman,_20).
 3009opposite(a,subhuman,superhuman,_20).
 3010opposite(a,humane,inhumane,_20).
 3011opposite(a,humorous,humorless,_20).
 3012opposite(a,hungry,thirsty,_20).
 3013opposite(a,hurried,unhurried,_20).
 3014opposite(a,identifiable,unidentifiable,_20).
 3015opposite(a,immanent,transeunt,_20).
 3016opposite(a,impaired,unimpaired,_20).
 3017opposite(a,important,unimportant,_20).
 3018opposite(a,impressive,unimpressive,_20).
 3019opposite(a,noticeable,unnoticeable,_20).
 3020opposite(a,improved,unimproved,_20).
 3021opposite(a,cleared,uncleared,_20).
 3022opposite(a,inaugural,exaugural,_20).
 3023opposite(a,inboard,outboard,_20).
 3024opposite(a,inbred,outbred,_20).
 3025opposite(a,inclined,disinclined,_20).
 3026opposite(a,outgoing,incoming,_20).
 3027opposite(a,inductive,deductive,_20).
 3028opposite(a,indulgent,nonindulgent,_20).
 3029opposite(a,industrial,nonindustrial,_20).
 3030opposite(a,infectious,noninfectious,_20).
 3031opposite(a,supernal,infernal,_20).
 3032opposite(a,informative,uninformative,_20).
 3033opposite(a,gnostic,agnostic,_20).
 3034opposite(a,informed,uninformed,_20).
 3035opposite(a,ingenuous,disingenuous,_20).
 3036opposite(a,inhabited,uninhabited,_20).
 3037opposite(a,inheritable,noninheritable,_20).
 3038opposite(a,inhibited,uninhibited,_20).
 3039opposite(a,injectable,uninjectable,_20).
 3040opposite(a,injured,uninjured,_20).
 3041opposite(a,guilty,innocent,_20).
 3042opposite(a,inspiring,uninspiring,_20).
 3043opposite(a,instructive,uninstructive,_20).
 3044opposite(a,edifying,unedifying,_20).
 3045opposite(a,enlightening,unenlightening,_20).
 3046opposite(a,segregated,integrated,_20).
 3047opposite(a,integrated,nonintegrated,_20).
 3048opposite(a,blended,unblended,_20).
 3049opposite(a,combined,uncombined,_20).
 3050opposite(a,integrative,disintegrative,_20).
 3051opposite(a,intellectual,nonintellectual,_20).
 3052opposite(a,intelligent,unintelligent,_20).
 3053opposite(a,intelligible,unintelligible,_20).
 3054opposite(a,intended,unintended,_20).
 3055opposite(a,designed,undesigned,_20).
 3056opposite(a,moderating,intensifying,_20).
 3057opposite(a,intraspecies,interspecies,_20).
 3058opposite(a,interested,uninterested,_20).
 3059opposite(a,interesting,uninteresting,_20).
 3060opposite(a,intramural,extramural,_20).
 3061opposite(a,'ultra vires','intra vires',_20).
 3062opposite(a,intrinsic,extrinsic,_20).
 3063opposite(a,introspective,extrospective,_20).
 3064opposite(a,introversive,extroversive,_20).
 3065opposite(a,intrusive,unintrusive,_20).
 3066opposite(a,intrusive,protrusive,_20).
 3067opposite(a,igneous,aqueous,_20).
 3068opposite(a,intrusive,extrusive,_20).
 3069opposite(a,invasive,noninvasive,_20).
 3070opposite(a,invigorating,debilitating,_20).
 3071opposite(a,inviting,uninviting,_20).
 3072opposite(a,'in vivo','in vitro',_20).
 3073opposite(a,ironed,unironed,_20).
 3074opposite(a,wrinkled,unwrinkled,_20).
 3075opposite(a,isotropic,anisotropic,_20).
 3076opposite(a,sad,glad,_20).
 3077opposite(a,joyful,sorrowful,_20).
 3078opposite(a,joyous,joyless,_20).
 3079opposite(a,juicy,juiceless,_20).
 3080opposite(a,just,unjust,_20).
 3081opposite(a,merited,unmerited,_20).
 3082opposite(a,keyed,keyless,_20).
 3083opposite(a,kind,unkind,_20).
 3084opposite(a,knowable,unknowable,_20).
 3085opposite(a,known,unknown,_20).
 3086opposite(a,understood,ununderstood,_20).
 3087opposite(a,labeled,unlabeled,_20).
 3088opposite(a,lamented,unlamented,_20).
 3089opposite(a,laureled,unlaureled,_20).
 3090opposite(a,big,little,_20).
 3091opposite(a,small,large,_20).
 3092opposite(a,lesser,greater,_20).
 3093opposite(a,lawful,unlawful,_20).
 3094opposite(a,leaded,unleaded,_20).
 3095opposite(a,tight,leaky,_20).
 3096opposite(a,caulked,uncaulked,_20).
 3097opposite(a,leavened,unleavened,_20).
 3098opposite(a,legal,illegal,_20).
 3099opposite(a,legible,illegible,_20).
 3100opposite(a,deciphered,undeciphered,_20).
 3101opposite(a,adoptive,biological,_20).
 3102opposite(a,legitimate,illegitimate,_20).
 3103opposite(a,catarrhine,leptorrhine,_20).
 3104opposite(a,eusporangiate,leptosporangiate,_20).
 3105opposite(a,like,unlike,_20).
 3106opposite(a,alike,unalike,_20).
 3107opposite(a,likely,unlikely,_20).
 3108opposite(a,probable,improbable,_20).
 3109opposite(a,limbed,limbless,_20).
 3110opposite(a,limited,unlimited,_20).
 3111opposite(a,lineal,collateral,_20).
 3112opposite(a,linear,nonlinear,_20).
 3113opposite(a,lined,unlined,_20).
 3114opposite(a,listed,unlisted,_20).
 3115opposite(a,literal,figurative,_20).
 3116opposite(a,literate,illiterate,_20).
 3117opposite(a,live,recorded,_20).
 3118opposite(a,livable,unlivable,_20).
 3119opposite(a,liveried,unliveried,_20).
 3120opposite(a,loaded,unloaded,_20).
 3121opposite(a,loamy,loamless,_20).
 3122opposite(a,ecdemic,epidemic,_20).
 3123opposite(a,gloved,gloveless,_20).
 3124opposite(a,hatted,hatless,_20).
 3125opposite(a,guided,unguided,_20).
 3126opposite(a,legged,legless,_20).
 3127opposite(a,logical,illogical,_20).
 3128opposite(a,extended,unextended,_20).
 3129opposite(a,mini,midi,_20).
 3130opposite(a,mini,maxi,_20).
 3131opposite(a,lossy,lossless,_20).
 3132opposite(a,long,short,_20).
 3133opposite(a,crosswise,lengthwise,_20).
 3134opposite(a,lidded,lidless,_20).
 3135opposite(a,constricted,unconstricted,_20).
 3136opposite(a,lost,found,_20).
 3137opposite(a,lost,saved,_20).
 3138opposite(a,soft,loud,_20).
 3139opposite(a,piano,forte,_20).
 3140opposite(a,soft,hardened,_20).
 3141opposite(a,lovable,hateful,_20).
 3142opposite(a,liked,disliked,_20).
 3143opposite(a,loved,unloved,_20).
 3144opposite(a,loving,unloving,_20).
 3145opposite(a,lucky,unlucky,_20).
 3146opposite(a,made,unmade,_20).
 3147opposite(a,magnetic,antimagnetic,_20).
 3148opposite(a,magnetic,geographic,_20).
 3149opposite(a,magnetic,nonmagnetic,_20).
 3150opposite(a,minor,major,_20).
 3151opposite(a,minuscule,majuscule,_20).
 3152opposite(a,manageable,unmanageable,_20).
 3153opposite(a,manly,unmanly,_20).
 3154opposite(a,male,androgynous,_20).
 3155opposite(a,manned,unmanned,_20).
 3156opposite(a,marked,unmarked,_20).
 3157opposite(a,branded,unbranded,_20).
 3158opposite(a,married,unmarried,_20).
 3159opposite(a,mated,unmated,_20).
 3160opposite(a,feminine,masculine,_20).
 3161opposite(a,womanly,unwomanly,_20).
 3162opposite(a,matched,mismatched,_20).
 3163opposite(a,mature,immature,_20).
 3164opposite(a,ripe,green,_20).
 3165opposite(a,seasonal,'year-round',_20).
 3166opposite(a,seasonable,unseasonable,_20).
 3167opposite(a,seasoned,unseasoned,_20).
 3168opposite(a,premature,'full-term',_20).
 3169opposite(a,minimal,maximal,_20).
 3170opposite(a,meaningful,meaningless,_20).
 3171opposite(a,measurable,immeasurable,_20).
 3172opposite(a,meaty,meatless,_20).
 3173opposite(a,mechanical,nonmechanical,_20).
 3174opposite(a,melodious,unmelodious,_20).
 3175opposite(a,tuneful,tuneless,_20).
 3176opposite(a,membered,memberless,_20).
 3177opposite(a,mined,unmined,_20).
 3178opposite(a,musical,unmusical,_20).
 3179opposite(a,melted,unmelted,_20).
 3180opposite(a,merciful,merciless,_20).
 3181opposite(a,metabolic,ametabolic,_20).
 3182opposite(a,mild,intense,_20).
 3183opposite(a,intensive,extensive,_20).
 3184opposite(a,involved,uninvolved,_20).
 3185opposite(a,military,unmilitary,_20).
 3186opposite(a,mitigated,unmitigated,_20).
 3187opposite(a,tempered,untempered,_20).
 3188opposite(a,mobile,immobile,_20).
 3189opposite(a,portable,unportable,_20).
 3190opposite(a,removable,irremovable,_20).
 3191opposite(a,metallic,nonmetallic,_20).
 3192opposite(a,metamorphic,nonmetamorphic,_20).
 3193opposite(a,moderate,immoderate,_20).
 3194opposite(a,modern,nonmodern,_20).
 3195opposite(a,modest,immodest,_20).
 3196opposite(a,modified,unmodified,_20).
 3197opposite(a,modulated,unmodulated,_20).
 3198opposite(a,molar,molecular,_20).
 3199opposite(a,diclinous,monoclinous,_20).
 3200opposite(a,dioecious,monoecious,_20).
 3201opposite(a,polyphonic,monophonic,_20).
 3202opposite(a,polygamous,monogamous,_20).
 3203opposite(a,monolingual,multilingual,_20).
 3204opposite(a,polyvalent,monovalent,_20).
 3205opposite(a,univalent,multivalent,_20).
 3206opposite(a,bivalent,univalent,_20).
 3207opposite(a,monotonic,nonmonotonic,_20).
 3208opposite(a,moral,immoral,_20).
 3209opposite(a,licit,illicit,_20).
 3210opposite(a,principled,unprincipled,_20).
 3211opposite(a,few,many,_20).
 3212opposite(a,more,less,_20).
 3213opposite(a,most,least,_20).
 3214opposite(a,more,fewer,_20).
 3215opposite(a,most,fewest,_20).
 3216opposite(a,mortal,immortal,_20).
 3217opposite(a,motivated,unmotivated,_20).
 3218opposite(a,motorized,unmotorized,_20).
 3219opposite(a,moved,unmoved,_20).
 3220opposite(a,moving,unmoving,_20).
 3221opposite(a,moving,nonmoving,_20).
 3222opposite(a,mown,unmown,_20).
 3223opposite(a,seamanlike,unseamanlike,_20).
 3224opposite(a,continental,intercontinental,_20).
 3225opposite(a,national,international,_20).
 3226opposite(a,intrastate,interstate,_20).
 3227opposite(a,natural,unnatural,_20).
 3228opposite(a,natural,artificial,_20).
 3229opposite(a,natural,supernatural,_20).
 3230opposite(a,ultimate,proximate,_20).
 3231opposite(a,necessary,unnecessary,_20).
 3232opposite(a,net,gross,_20).
 3233opposite(a,neurotic,unneurotic,_20).
 3234opposite(a,nice,nasty,_20).
 3235opposite(a,nidifugous,nidicolous,_20).
 3236opposite(a,noble,ignoble,_20).
 3237opposite(a,noble,lowborn,_20).
 3238opposite(a,normal,abnormal,_20).
 3239opposite(a,hypotensive,hypertensive,_20).
 3240opposite(a,normal,paranormal,_20).
 3241opposite(a,south,north,_20).
 3242opposite(a,southern,northern,_20).
 3243opposite(a,nosed,noseless,_20).
 3244opposite(a,noticed,unnoticed,_20).
 3245opposite(a,detected,undetected,_20).
 3246opposite(a,determined,undetermined,_20).
 3247opposite(a,noxious,innocuous,_20).
 3248opposite(a,obedient,disobedient,_20).
 3249opposite(a,obtrusive,unobtrusive,_20).
 3250opposite(a,objective,subjective,_20).
 3251opposite(a,obligated,unobligated,_20).
 3252opposite(a,obligate,facultative,_20).
 3253opposite(a,obvious,unobvious,_20).
 3254opposite(a,obstructed,unobstructed,_20).
 3255opposite(a,occupied,unoccupied,_20).
 3256opposite(a,offensive,inoffensive,_20).
 3257opposite(a,savory,unsavory,_20).
 3258opposite(a,offensive,defensive,_20).
 3259opposite(a,offending,unoffending,_20).
 3260opposite(a,apologetic,unapologetic,_20).
 3261opposite(a,official,unofficial,_20).
 3262opposite(a,confirmed,unconfirmed,_20).
 3263opposite(a,established,unestablished,_20).
 3264opposite(a,conditioned,unconditioned,_20).
 3265opposite(a,'on-site','off-site',_20).
 3266opposite(a,onstage,offstage,_20).
 3267opposite(a,'on-street','off-street',_20).
 3268opposite(a,old,new,_20).
 3269opposite(a,'one-piece','three-piece',_20).
 3270opposite(a,'two-piece','one-piece',_20).
 3271opposite(a,'on-line','off-line',_20).
 3272opposite(a,on,off,_20).
 3273opposite(a,onside,offside,_20).
 3274opposite(a,open,closed,_20).
 3275opposite(a,spaced,unspaced,_20).
 3276opposite(a,enclosed,unenclosed,_20).
 3277opposite(a,tanned,untanned,_20).
 3278opposite(a,tapped,untapped,_20).
 3279opposite(a,operational,nonoperational,_20).
 3280opposite(a,opportune,inopportune,_20).
 3281opposite(a,opposable,unopposable,_20).
 3282opposite(a,opposed,unopposed,_20).
 3283opposite(a,opposite,alternate,_20).
 3284opposite(a,optimistic,pessimistic,_20).
 3285opposite(a,oral,aboral,_20).
 3286opposite(a,actinal,abactinal,_20).
 3287opposite(a,orderly,disorderly,_20).
 3288opposite(a,ordered,disordered,_20).
 3289opposite(a,organized,disorganized,_20).
 3290opposite(a,organized,unorganized,_20).
 3291opposite(a,structured,unstructured,_20).
 3292opposite(a,ordinary,extraordinary,_20).
 3293opposite(a,organic,inorganic,_20).
 3294opposite(a,holistic,atomistic,_20).
 3295opposite(a,arranged,disarranged,_20).
 3296opposite(a,oriented,unoriented,_20).
 3297opposite(a,orienting,disorienting,_20).
 3298opposite(a,original,unoriginal,_20).
 3299opposite(a,orthodox,unorthodox,_20).
 3300opposite(a,indoor,outdoor,_20).
 3301opposite(a,bare,covered,_20).
 3302opposite(a,coated,uncoated,_20).
 3303opposite(a,roofed,roofless,_20).
 3304opposite(a,leafy,leafless,_20).
 3305opposite(a,lipped,lipless,_20).
 3306opposite(a,overt,covert,_20).
 3307opposite(a,paid,unpaid,_20).
 3308opposite(a,painful,painless,_20).
 3309opposite(a,painted,unpainted,_20).
 3310opposite(a,delineated,undelineated,_20).
 3311opposite(a,paintable,unpaintable,_20).
 3312opposite(a,palatable,unpalatable,_20).
 3313opposite(a,palpable,impalpable,_20).
 3314opposite(a,parallel,perpendicular,_20).
 3315opposite(a,oblique,parallel,_20).
 3316opposite(a,pardonable,unpardonable,_20).
 3317opposite(a,excusable,inexcusable,_20).
 3318opposite(a,filial,parental,_20).
 3319opposite(a,partial,impartial,_20).
 3320opposite(a,particulate,nonparticulate,_20).
 3321opposite(a,passable,impassable,_20).
 3322opposite(a,passionate,passionless,_20).
 3323opposite(a,past,present,_20).
 3324opposite(a,born,unborn,_20).
 3325opposite(a,parented,unparented,_20).
 3326opposite(a,paternal,maternal,_20).
 3327opposite(a,wifely,husbandly,_20).
 3328opposite(a,patient,impatient,_20).
 3329opposite(a,patriarchal,matriarchal,_20).
 3330opposite(a,patronized,unpatronized,_20).
 3331opposite(a,packaged,unpackaged,_20).
 3332opposite(a,paved,unpaved,_20).
 3333opposite(a,patriotic,unpatriotic,_20).
 3334opposite(a,peaceful,unpeaceful,_20).
 3335opposite(a,penitent,impenitent,_20).
 3336opposite(a,repentant,unrepentant,_20).
 3337opposite(a,perceptive,unperceptive,_20).
 3338opposite(a,perceptible,imperceptible,_20).
 3339opposite(a,perfect,imperfect,_20).
 3340opposite(a,perishable,imperishable,_20).
 3341opposite(a,permanent,impermanent,_20).
 3342opposite(a,caducous,persistent,_20).
 3343opposite(a,reversible,irreversible,_20).
 3344opposite(a,reversible,nonreversible,_20).
 3345opposite(a,revocable,irrevocable,_20).
 3346opposite(a,permissible,impermissible,_20).
 3347opposite(a,admissible,inadmissible,_20).
 3348opposite(a,permissive,unpermissive,_20).
 3349opposite(a,perplexed,unperplexed,_20).
 3350opposite(a,personal,impersonal,_20).
 3351opposite(a,persuasive,dissuasive,_20).
 3352opposite(a,penetrable,impenetrable,_20).
 3353opposite(a,permeable,impermeable,_20).
 3354opposite(a,pervious,impervious,_20).
 3355opposite(a,petalous,apetalous,_20).
 3356opposite(a,puncturable,punctureless,_20).
 3357opposite(a,psychoactive,nonpsychoactive,_20).
 3358opposite(a,mental,physical,_20).
 3359opposite(a,polytheistic,monotheistic,_20).
 3360opposite(a,pious,impious,_20).
 3361opposite(a,secular,religious,_20).
 3362opposite(a,religious,irreligious,_20).
 3363opposite(a,placable,implacable,_20).
 3364opposite(a,plain,patterned,_20).
 3365opposite(a,plain,fancy,_20).
 3366opposite(a,planned,unplanned,_20).
 3367opposite(a,studied,unstudied,_20).
 3368opposite(a,plausible,implausible,_20).
 3369opposite(a,pleasant,unpleasant,_20).
 3370opposite(a,pleased,displeased,_20).
 3371opposite(a,pleasing,displeasing,_20).
 3372opposite(a,pointed,pointless,_20).
 3373opposite(a,acute,obtuse,_20).
 3374opposite(a,polished,unpolished,_20).
 3375opposite(a,politic,impolitic,_20).
 3376opposite(a,political,nonpolitical,_20).
 3377opposite(a,ponderable,imponderable,_20).
 3378opposite(a,popular,unpopular,_20).
 3379opposite(a,pro,anti,_20).
 3380opposite(a,plus,minus,_20).
 3381opposite(a,possible,impossible,_20).
 3382opposite(a,potent,impotent,_20).
 3383opposite(a,powerful,powerless,_20).
 3384opposite(a,powered,unpowered,_20).
 3385opposite(a,'low-tension','high-tension',_20).
 3386opposite(a,influential,uninfluential,_20).
 3387opposite(a,placental,aplacental,_20).
 3388opposite(a,planted,unplanted,_20).
 3389opposite(a,plowed,unplowed,_20).
 3390opposite(a,cultivated,uncultivated,_20).
 3391opposite(a,potted,unpotted,_20).
 3392opposite(a,practical,impractical,_20).
 3393opposite(a,precise,imprecise,_20).
 3394opposite(a,retarded,precocious,_20).
 3395opposite(a,predictable,unpredictable,_20).
 3396opposite(a,premeditated,unpremeditated,_20).
 3397opposite(a,prepared,unprepared,_20).
 3398opposite(a,prescription,nonprescription,_20).
 3399opposite(a,ostentatious,unostentatious,_20).
 3400opposite(a,pretentious,unpretentious,_20).
 3401opposite(a,primary,secondary,_20).
 3402opposite(a,basic,incidental,_20).
 3403opposite(a,public,private,_20).
 3404opposite(a,inclusive,exclusive,_20).
 3405opposite(a,privileged,underprivileged,_20).
 3406opposite(a,productive,unproductive,_20).
 3407opposite(a,generative,consumptive,_20).
 3408opposite(a,reproducible,unreproducible,_20).
 3409opposite(a,professional,nonprofessional,_20).
 3410opposite(a,professional,unprofessional,_20).
 3411opposite(a,profitable,unprofitable,_20).
 3412opposite(a,profound,superficial,_20).
 3413opposite(a,prognathous,opisthognathous,_20).
 3414opposite(a,regressive,progressive,_20).
 3415opposite(a,pronounceable,unpronounceable,_20).
 3416opposite(a,proper,improper,_20).
 3417opposite(a,prophetic,unprophetic,_20).
 3418opposite(a,prospective,retrospective,_20).
 3419opposite(a,protected,unprotected,_20).
 3420opposite(a,protective,unprotective,_20).
 3421opposite(a,proud,humble,_20).
 3422opposite(a,proved,unproved,_20).
 3423opposite(a,provident,improvident,_20).
 3424opposite(a,provocative,unprovocative,_20).
 3425opposite(a,prudent,imprudent,_20).
 3426opposite(a,punctual,unpunctual,_20).
 3427opposite(a,punished,unpunished,_20).
 3428opposite(a,punitive,rehabilitative,_20).
 3429opposite(a,purebred,crossbred,_20).
 3430opposite(a,pure,impure,_20).
 3431opposite(a,contaminated,uncontaminated,_20).
 3432opposite(a,purposeful,purposeless,_20).
 3433opposite(a,qualified,unqualified,_20).
 3434opposite(a,trained,untrained,_20).
 3435opposite(a,qualitative,quantitative,_20).
 3436opposite(a,questionable,unquestionable,_20).
 3437opposite(a,quiet,noisy,_20).
 3438opposite(a,restful,restless,_20).
 3439opposite(a,quiet,unquiet,_20).
 3440opposite(a,random,nonrandom,_20).
 3441opposite(a,rational,irrational,_20).
 3442opposite(a,racial,nonracial,_20).
 3443opposite(a,reactive,unreactive,_20).
 3444opposite(a,ready,unready,_20).
 3445opposite(a,real,unreal,_20).
 3446opposite(a,real,nominal,_20).
 3447opposite(a,realistic,unrealistic,_20).
 3448opposite(a,reasonable,unreasonable,_20).
 3449opposite(a,reciprocal,nonreciprocal,_20).
 3450opposite(a,refined,unrefined,_20).
 3451opposite(a,processed,unprocessed,_20).
 3452opposite(a,treated,untreated,_20).
 3453opposite(a,oiled,unoiled,_20).
 3454opposite(a,recoverable,unrecoverable,_20).
 3455opposite(a,regenerate,unregenerate,_20).
 3456opposite(a,registered,unregistered,_20).
 3457opposite(a,regular,irregular,_20).
 3458opposite(a,regulated,unregulated,_20).
 3459opposite(a,remediable,irremediable,_20).
 3460opposite(a,renewable,unrenewable,_20).
 3461opposite(a,rentable,unrentable,_20).
 3462opposite(a,reparable,irreparable,_20).
 3463opposite(a,repeatable,unrepeatable,_20).
 3464opposite(a,quotable,unquotable,_20).
 3465opposite(a,repetitive,nonrepetitive,_20).
 3466opposite(a,printable,unprintable,_20).
 3467opposite(a,requested,unrequested,_20).
 3468opposite(a,rhymed,unrhymed,_20).
 3469opposite(a,uniform,multiform,_20).
 3470opposite(a,periodic,aperiodic,_20).
 3471opposite(a,related,unrelated,_20).
 3472opposite(a,relevant,irrelevant,_20).
 3473opposite(a,mindful,unmindful,_20).
 3474opposite(a,replaceable,irreplaceable,_20).
 3475opposite(a,representational,nonrepresentational,_20).
 3476opposite(a,representative,nonrepresentative,_20).
 3477opposite(a,reputable,disreputable,_20).
 3478opposite(a,receptive,unreceptive,_20).
 3479opposite(a,reconcilable,irreconcilable,_20).
 3480opposite(a,reserved,unreserved,_20).
 3481opposite(a,resistible,irresistible,_20).
 3482opposite(a,resolute,irresolute,_20).
 3483opposite(a,respectable,unrespectable,_20).
 3484opposite(a,respectful,disrespectful,_20).
 3485opposite(a,responsible,irresponsible,_20).
 3486opposite(a,responsive,unresponsive,_20).
 3487opposite(a,restrained,unrestrained,_20).
 3488opposite(a,restricted,unrestricted,_20).
 3489opposite(a,restrictive,unrestrictive,_20).
 3490opposite(a,retentive,unretentive,_20).
 3491opposite(a,reticulate,nonreticulate,_20).
 3492opposite(a,retractile,nonretractile,_20).
 3493opposite(a,reflective,nonreflective,_20).
 3494opposite(a,reflected,unreflected,_20).
 3495opposite(a,reverberant,unreverberant,_20).
 3496opposite(a,reverent,irreverent,_20).
 3497opposite(a,revived,unrevived,_20).
 3498opposite(a,awakened,unawakened,_20).
 3499opposite(a,awed,unawed,_20).
 3500opposite(a,revolutionary,counterrevolutionary,_20).
 3501opposite(a,rewarding,unrewarding,_20).
 3502opposite(a,rhetorical,unrhetorical,_20).
 3503opposite(a,rhythmical,unrhythmical,_20).
 3504opposite(a,ribbed,ribless,_20).
 3505opposite(a,moneyed,moneyless,_20).
 3506opposite(a,solvent,insolvent,_20).
 3507opposite(a,rich,lean,_20).
 3508opposite(a,rimmed,rimless,_20).
 3509opposite(a,handed,handless,_20).
 3510opposite(a,handled,handleless,_20).
 3511opposite(a,'right-handed',ambidextrous,_20).
 3512opposite(a,'left-handed','right-handed',_20).
 3513opposite(a,right,center,_20).
 3514opposite(a,horned,hornless,_20).
 3515opposite(a,righteous,unrighteous,_20).
 3516opposite(a,frail,robust,_20).
 3517opposite(a,round,square,_20).
 3518opposite(a,rounded,angular,_20).
 3519opposite(a,oblate,prolate,_20).
 3520opposite(a,urban,rural,_20).
 3521opposite(a,rusted,rustless,_20).
 3522opposite(a,holy,unholy,_20).
 3523opposite(a,sacred,profane,_20).
 3524opposite(a,sadistic,masochistic,_20).
 3525opposite(a,safe,dangerous,_20).
 3526opposite(a,salable,unsalable,_20).
 3527opposite(a,same,different,_20).
 3528opposite(a,same,other,_20).
 3529opposite(a,similar,dissimilar,_20).
 3530opposite(a,sane,insane,_20).
 3531opposite(a,satiate,insatiate,_20).
 3532opposite(a,sarcastic,unsarcastic,_20).
 3533opposite(a,satisfactory,unsatisfactory,_20).
 3534opposite(a,scalable,unscalable,_20).
 3535opposite(a,scholarly,unscholarly,_20).
 3536opposite(a,scientific,unscientific,_20).
 3537opposite(a,scrupulous,unscrupulous,_20).
 3538opposite(a,conscientious,unconscientious,_20).
 3539opposite(a,sealed,unsealed,_20).
 3540opposite(a,wrapped,unwrapped,_20).
 3541opposite(a,seaworthy,unseaworthy,_20).
 3542opposite(a,airworthy,unairworthy,_20).
 3543opposite(a,concealed,unconcealed,_20).
 3544opposite(a,revealing,concealing,_20).
 3545opposite(a,sectarian,nonsectarian,_20).
 3546opposite(a,secure,insecure,_20).
 3547opposite(a,fastened,unfastened,_20).
 3548opposite(a,insured,uninsured,_20).
 3549opposite(a,seductive,unseductive,_20).
 3550opposite(a,selfish,unselfish,_20).
 3551opposite(a,senior,junior,_20).
 3552opposite(a,sensational,unsensational,_20).
 3553opposite(a,sensible,insensible,_20).
 3554opposite(a,sensitive,insensitive,_20).
 3555opposite(a,sensitizing,desensitizing,_20).
 3556opposite(a,sensory,extrasensory,_20).
 3557opposite(a,sent,unsent,_20).
 3558opposite(a,joint,separate,_20).
 3559opposite(a,sanitary,unsanitary,_20).
 3560opposite(a,septic,antiseptic,_20).
 3561opposite(a,germy,germfree,_20).
 3562opposite(a,purifying,adulterating,_20).
 3563opposite(a,serious,frivolous,_20).
 3564opposite(a,playful,unplayful,_20).
 3565opposite(a,selected,unselected,_20).
 3566opposite(a,serviceable,unserviceable,_20).
 3567opposite(a,settled,unsettled,_20).
 3568opposite(a,migratory,nonmigratory,_20).
 3569opposite(a,sexy,unsexy,_20).
 3570opposite(a,sexual,asexual,_20).
 3571opposite(a,castrated,uncastrated,_20).
 3572opposite(a,aphrodisiac,anaphrodisiac,_20).
 3573opposite(a,estrous,anestrous,_20).
 3574opposite(a,shapely,unshapely,_20).
 3575opposite(a,breasted,breastless,_20).
 3576opposite(a,formed,unformed,_20).
 3577opposite(a,shared,unshared,_20).
 3578opposite(a,shaven,unshaven,_20).
 3579opposite(a,sheared,unsheared,_20).
 3580opposite(a,sheathed,unsheathed,_20).
 3581opposite(a,shockable,unshockable,_20).
 3582opposite(a,shod,unshod,_20).
 3583opposite(a,calced,discalced,_20).
 3584opposite(a,farsighted,nearsighted,_20).
 3585opposite(a,shrinkable,unshrinkable,_20).
 3586opposite(a,blind,sighted,_20).
 3587opposite(a,signed,unsigned,_20).
 3588opposite(a,significant,insignificant,_20).
 3589opposite(a,significant,nonsignificant,_20).
 3590opposite(a,silenced,unsilenced,_20).
 3591opposite(a,simple,compound,_20).
 3592opposite(a,simple,complex,_20).
 3593opposite(a,sincere,insincere,_20).
 3594opposite(a,ordinal,cardinal,_20).
 3595opposite(a,scripted,unscripted,_20).
 3596opposite(a,sinkable,unsinkable,_20).
 3597opposite(a,single,multiple,_20).
 3598opposite(a,single,double,_20).
 3599opposite(a,'true-false','multiple-choice',_20).
 3600opposite(a,multilane,'single-lane',_20).
 3601opposite(a,sized,unsized,_20).
 3602opposite(a,skilled,unskilled,_20).
 3603opposite(a,verbal,numerical,_20).
 3604opposite(a,fine,coarse,_20).
 3605opposite(a,smoky,smokeless,_20).
 3606opposite(a,slippery,nonslippery,_20).
 3607opposite(a,lubricated,unlubricated,_20).
 3608opposite(a,furrowed,unfurrowed,_20).
 3609opposite(a,rifled,unrifled,_20).
 3610opposite(a,social,unsocial,_20).
 3611opposite(a,accompanied,unaccompanied,_20).
 3612opposite(a,gregarious,ungregarious,_20).
 3613opposite(a,seamed,seamless,_20).
 3614opposite(a,seeded,unseeded,_20).
 3615opposite(a,seedy,seedless,_20).
 3616opposite(a,shuttered,unshuttered,_20).
 3617opposite(a,sleeved,sleeveless,_20).
 3618opposite(a,sociable,unsociable,_20).
 3619opposite(a,sold,unsold,_20).
 3620opposite(a,soled,soleless,_20).
 3621opposite(a,solid,liquid,_20).
 3622opposite(a,solid,gaseous,_20).
 3623opposite(a,solid,hollow,_20).
 3624opposite(a,soluble,insoluble,_20).
 3625opposite(a,solved,unsolved,_20).
 3626opposite(a,no,some,_20).
 3627opposite(a,naive,sophisticated,_20).
 3628opposite(a,sound,unsound,_20).
 3629opposite(a,effervescent,noneffervescent,_20).
 3630opposite(a,still,sparkling,_20).
 3631opposite(a,specialized,unspecialized,_20).
 3632opposite(a,spinous,spineless,_20).
 3633opposite(a,spirited,spiritless,_20).
 3634opposite(a,induced,spontaneous,_20).
 3635opposite(a,spoken,written,_20).
 3636opposite(a,voiced,unvoiced,_20).
 3637opposite(a,written,unwritten,_20).
 3638opposite(a,vocalic,consonantal,_20).
 3639opposite(a,stoppable,unstoppable,_20).
 3640opposite(a,syllabic,nonsyllabic,_20).
 3641opposite(a,syllabic,accentual,_20).
 3642opposite(a,stable,unstable,_20).
 3643opposite(a,legato,staccato,_20).
 3644opposite(a,staged,unstaged,_20).
 3645opposite(a,standard,nonstandard,_20).
 3646opposite(a,starchy,starchless,_20).
 3647opposite(a,starry,starless,_20).
 3648opposite(a,nourished,malnourished,_20).
 3649opposite(a,steady,unsteady,_20).
 3650opposite(a,stemmed,stemless,_20).
 3651opposite(a,stimulating,unstimulating,_20).
 3652opposite(a,depressant,stimulative,_20).
 3653opposite(a,stomatous,astomatous,_20).
 3654opposite(a,coiled,uncoiled,_20).
 3655opposite(a,stressed,unstressed,_20).
 3656opposite(a,tonic,atonic,_20).
 3657opposite(a,weak,strong,_20).
 3658opposite(a,docile,stubborn,_20).
 3659opposite(a,subordinate,insubordinate,_20).
 3660opposite(a,successful,unsuccessful,_20).
 3661opposite(a,sufficient,insufficient,_20).
 3662opposite(a,sugary,sugarless,_20).
 3663opposite(a,subjacent,superjacent,_20).
 3664opposite(a,supervised,unsupervised,_20).
 3665opposite(a,supported,unsupported,_20).
 3666opposite(a,assisted,unassisted,_20).
 3667opposite(a,supportive,unsupportive,_20).
 3668opposite(a,surmountable,insurmountable,_20).
 3669opposite(a,surprised,unsurprised,_20).
 3670opposite(a,surprising,unsurprising,_20).
 3671opposite(a,susceptible,unsusceptible,_20).
 3672opposite(a,impressionable,unimpressionable,_20).
 3673opposite(a,exempt,nonexempt,_20).
 3674opposite(a,scheduled,unscheduled,_20).
 3675opposite(a,dry,sweet,_20).
 3676opposite(a,soured,unsoured,_20).
 3677opposite(a,suspected,unsuspected,_20).
 3678opposite(a,swept,unswept,_20).
 3679opposite(a,sworn,unsworn,_20).
 3680opposite(a,symmetrical,asymmetrical,_20).
 3681opposite(a,zygomorphic,actinomorphic,_20).
 3682opposite(a,sympathetic,unsympathetic,_20).
 3683opposite(a,sympatric,allopatric,_20).
 3684opposite(a,synchronic,diachronic,_20).
 3685opposite(a,synchronous,asynchronous,_20).
 3686opposite(a,syndetic,asyndetic,_20).
 3687opposite(a,synonymous,antonymous,_20).
 3688opposite(a,systematic,unsystematic,_20).
 3689opposite(a,voluble,taciturn,_20).
 3690opposite(a,tactful,tactless,_20).
 3691opposite(a,wild,tame,_20).
 3692opposite(a,tangible,intangible,_20).
 3693opposite(a,tasteful,tasteless,_20).
 3694opposite(a,taxable,nontaxable,_20).
 3695opposite(a,temperate,intemperate,_20).
 3696opposite(a,tense,relaxed,_20).
 3697opposite(a,territorial,extraterritorial,_20).
 3698opposite(a,territorial,nonterritorial,_20).
 3699opposite(a,thermosetting,thermoplastic,_20).
 3700opposite(a,thin,thick,_20).
 3701opposite(a,thinkable,unthinkable,_20).
 3702opposite(a,thoughtful,thoughtless,_20).
 3703opposite(a,thrifty,wasteful,_20).
 3704opposite(a,tidy,untidy,_20).
 3705opposite(a,groomed,ungroomed,_20).
 3706opposite(a,combed,uncombed,_20).
 3707opposite(a,timbered,untimbered,_20).
 3708opposite(a,toned,toneless,_20).
 3709opposite(a,tongued,tongueless,_20).
 3710opposite(a,tipped,untipped,_20).
 3711opposite(a,tired,rested,_20).
 3712opposite(a,tolerable,intolerable,_20).
 3713opposite(a,tolerant,intolerant,_20).
 3714opposite(a,tonal,atonal,_20).
 3715opposite(a,toothed,toothless,_20).
 3716opposite(a,top,side,_20).
 3717opposite(a,topped,topless,_20).
 3718opposite(a,bottomed,bottomless,_20).
 3719opposite(a,'top-down','bottom-up',_20).
 3720opposite(a,polar,equatorial,_20).
 3721opposite(a,testate,intestate,_20).
 3722opposite(a,touched,untouched,_20).
 3723opposite(a,tough,tender,_20).
 3724opposite(a,toxic,nontoxic,_20).
 3725opposite(a,tractable,intractable,_20).
 3726opposite(a,'a la carte','table d\'hote',_20).
 3727opposite(a,traceable,untraceable,_20).
 3728opposite(a,tracked,trackless,_20).
 3729opposite(a,traveled,untraveled,_20).
 3730opposite(a,trimmed,untrimmed,_20).
 3731opposite(a,troubled,untroubled,_20).
 3732opposite(a,true,false,_20).
 3733opposite(a,trustful,distrustful,_20).
 3734opposite(a,trustworthy,untrustworthy,_20).
 3735opposite(a,tubed,tubeless,_20).
 3736opposite(a,tucked,untucked,_20).
 3737opposite(a,turned,unturned,_20).
 3738opposite(a,typical,atypical,_20).
 3739opposite(a,overhand,underhand,_20).
 3740opposite(a,surface,subsurface,_20).
 3741opposite(a,surface,overhead,_20).
 3742opposite(a,submersible,nonsubmersible,_20).
 3743opposite(a,tearful,tearless,_20).
 3744opposite(a,union,nonunion,_20).
 3745opposite(a,uniparous,multiparous,_20).
 3746opposite(a,bipolar,unipolar,_20).
 3747opposite(a,united,divided,_20).
 3748opposite(a,adnate,connate,_20).
 3749opposite(a,bivalve,univalve,_20).
 3750opposite(a,ascending,descending,_20).
 3751opposite(a,rising,falling,_20).
 3752opposite(a,climactic,anticlimactic,_20).
 3753opposite(a,upmarket,downmarket,_20).
 3754opposite(a,transitive,intransitive,_20).
 3755opposite(a,translatable,untranslatable,_20).
 3756opposite(a,ungulate,unguiculate,_20).
 3757opposite(a,up,down,_20).
 3758opposite(a,upstage,downstage,_20).
 3759opposite(a,upstairs,downstairs,_20).
 3760opposite(a,upstream,downstream,_20).
 3761opposite(a,uptown,downtown,_20).
 3762opposite(a,used,misused,_20).
 3763opposite(a,useful,useless,_20).
 3764opposite(a,utopian,dystopian,_20).
 3765opposite(a,valid,invalid,_20).
 3766opposite(a,valuable,worthless,_20).
 3767opposite(a,variable,invariable,_20).
 3768opposite(a,varied,unvaried,_20).
 3769opposite(a,veiled,unveiled,_20).
 3770opposite(a,ventilated,unventilated,_20).
 3771opposite(a,vertebrate,invertebrate,_20).
 3772opposite(a,violable,inviolable,_20).
 3773opposite(a,violent,nonviolent,_20).
 3774opposite(a,wicked,virtuous,_20).
 3775opposite(a,visible,invisible,_20).
 3776opposite(a,viviparous,ovoviviparous,_20).
 3777opposite(a,oviparous,viviparous,_20).
 3778opposite(a,volatile,nonvolatile,_20).
 3779opposite(a,voluntary,involuntary,_20).
 3780opposite(a,vulnerable,invulnerable,_20).
 3781opposite(a,wanted,unwanted,_20).
 3782opposite(a,'warm-blooded','cold-blooded',_20).
 3783opposite(a,warmhearted,coldhearted,_20).
 3784opposite(a,washable,nonwashable,_20).
 3785opposite(a,waxed,unwaxed,_20).
 3786opposite(a,increasing,decreasing,_20).
 3787opposite(a,inflationary,deflationary,_20).
 3788opposite(a,weaned,unweaned,_20).
 3789opposite(a,wearable,unwearable,_20).
 3790opposite(a,weedy,weedless,_20).
 3791opposite(a,welcome,unwelcome,_20).
 3792opposite(a,ill,well,_20).
 3793opposite(a,hydrous,anhydrous,_20).
 3794opposite(a,wheeled,wheelless,_20).
 3795opposite(a,'blue-collar','white-collar',_20).
 3796opposite(a,wholesome,unwholesome,_20).
 3797opposite(a,wieldy,unwieldy,_20).
 3798opposite(a,wigged,wigless,_20).
 3799opposite(a,willing,unwilling,_20).
 3800opposite(a,winged,wingless,_20).
 3801opposite(a,wired,wireless,_20).
 3802opposite(a,wise,foolish,_20).
 3803opposite(a,wooded,unwooded,_20).
 3804opposite(a,woody,nonwoody,_20).
 3805opposite(a,worldly,unworldly,_20).
 3806opposite(a,woven,unwoven,_20).
 3807opposite(a,new,worn,_20).
 3808opposite(a,worthy,unworthy,_20).
 3809opposite(a,xeric,hydric,_20).
 3810opposite(a,xeric,mesic,_20).
 3811opposite(a,zonal,azonal,_20).
 3812opposite(a,acrocarpous,pleurocarpous,_20).
 3813opposite(a,fossorial,cursorial,_20).
 3814opposite(a,homocercal,heterocercal,_20).
 3815opposite(a,webbed,unwebbed,_20).
 3816opposite(a,faceted,unfaceted,_20).
 3817opposite(a,ipsilateral,contralateral,_20).
 3818opposite(a,salient,'re-entrant',_20).
 3819opposite(a,proactive,retroactive,_20).
 3820opposite(a,'rh-positive','rh-negative',_20).
 3821opposite(a,categorematic,syncategorematic,_20).
 3822opposite(a,nomothetic,idiographic,_20).
 3823opposite(a,'pro-life','pro-choice',_20).
 3824opposite(a,baptized,unbaptized,_20).
 3825opposite(a,benign,malignant,_20).
 3826opposite(a,calcifugous,calcicolous,_20).
 3827opposite(a,invertible,'non-invertible',_20).
 3828opposite(a,immunodeficient,immunocompetent,_20).
 3829opposite(a,xenogeneic,allogeneic,_20).
 3830opposite(a,'long-spurred','short-spurred',_20).
 3831opposite(a,shelled,unshelled,_20).
 3832opposite(a,jawed,jawless,_20).
 3833opposite(a,skinned,skinless,_20).
 3834opposite(a,flowering,flowerless,_20).
 3835opposite(a,adient,abient,_20).
 3836opposite(a,anodic,cathodic,_20).
 3837opposite(a,autotrophic,heterotrophic,_20).
 3838opposite(a,bracteate,ebracteate,_20).
 3839opposite(a,intracellular,extracellular,_20).
 3840opposite(a,eremitic,cenobitic,_20).
 3841opposite(a,cenogenetic,palingenetic,_20).
 3842opposite(a,chromatinic,achromatinic,_20).
 3843opposite(a,directional,omnidirectional,_20).
 3844opposite(a,eugenic,dysgenic,_20).
 3845opposite(a,febrile,afebrile,_20).
 3846opposite(a,fictional,nonfictional,_20).
 3847opposite(a,fretted,unfretted,_20).
 3848opposite(a,harmonic,nonharmonic,_20).
 3849opposite(a,ionic,nonionic,_20).
 3850opposite(a,myelinated,unmyelinated,_20).
 3851opposite(a,passerine,nonpasserine,_20).
 3852opposite(a,photosynthetic,nonphotosynthetic,_20).
 3853opposite(a,ruminant,nonruminant,_20).
 3854opposite(a,spherical,nonspherical,_20).
 3855opposite(a,steroidal,nonsteroidal,_20).
 3856opposite(a,suppurative,nonsuppurative,_20).
 3857opposite(a,syntagmatic,paradigmatic,_20).
 3858opposite(a,thematic,unthematic,_20).
 3859opposite(a,thermal,nonthermal,_20).
 3860opposite(a,vocal,instrumental,_20).
 3861opposite(a,hydrostatic,hydrokinetic,_20).
 3862opposite(a,spatial,nonspatial,_20).
 3863opposite(a,linguistic,nonlinguistic,_20).
 3864opposite(a,caudal,cephalic,_20).
 3865opposite(a,financial,nonfinancial,_20).
 3866opposite(a,eukaryotic,prokaryotic,_20).
 3867opposite(a,eucaryotic,procaryotic,_20).
 3868opposite(a,vascular,avascular,_20).
 3869opposite(a,uninucleate,multinucleate,_20).
 3870opposite(a,surgical,nonsurgical,_20).
 3871opposite(a,exocrine,endocrine,_20).
 3872opposite(a,historical,ahistorical,_20).
 3873opposite(a,'pro-American','anti-American',_20).
 3874opposite(a,anionic,cationic,_20).
 3875opposite(a,accusatorial,inquisitorial,_20).
 3876opposite(a,prenuptial,postnuptial,_20).
 3877opposite(a,intradepartmental,interdepartmental,_20).
 3878opposite(a,allopathic,homeopathic,_20).
 3879opposite(a,translational,nontranslational,_20).
 3880opposite(a,avenged,unavenged,_20).
 3881opposite(a,collected,uncollected,_20).
 3882opposite(a,gathered,ungathered,_20).
 3883opposite(a,contested,uncontested,_20).
 3884opposite(a,filled,unfilled,_20).
 3885opposite(a,malted,unmalted,_20).
 3886opposite(a,posed,unposed,_20).
 3887opposite(a,saponified,unsaponified,_20).
 3888opposite(r,kindly,unkindly,_20).
 3889opposite(r,significantly,insignificantly,_20).
 3890opposite(r,wholly,partly,_20).
 3891opposite(r,perfectly,imperfectly,_20).
 3892opposite(r,well,badly,_20).
 3893opposite(r,advantageously,disadvantageously,_20).
 3894opposite(r,satisfactorily,unsatisfactorily,_20).
 3895opposite(r,ever,never,_20).
 3896opposite(r,conventionally,unconventionally,_20).
 3897opposite(r,still,'no longer',_20).
 3898opposite(r,frequently,infrequently,_20).
 3899opposite(r,often,rarely,_20).
 3900opposite(r,reasonably,unreasonably,_20).
 3901opposite(r,moderately,immoderately,_20).
 3902opposite(r,naturally,unnaturally,_20).
 3903opposite(r,generally,specifically,_20).
 3904opposite(r,fortunately,unfortunately,_20).
 3905opposite(r,luckily,unluckily,_20).
 3906opposite(r,sadly,happily,_20).
 3907opposite(r,happily,unhappily,_20).
 3908opposite(r,'by hand','by machine',_20).
 3909opposite(r,acceptably,unacceptably,_20).
 3910opposite(r,tolerably,intolerably,_20).
 3911opposite(r,adroitly,maladroitly,_20).
 3912opposite(r,'by no means','by all means',_20).
 3913opposite(r,directly,indirectly,_20).
 3914opposite(r,intentionally,unintentionally,_20).
 3915opposite(r,deliberately,accidentally,_20).
 3916opposite(r,softly,loudly,_20).
 3917opposite(r,back,ahead,_20).
 3918opposite(r,overtly,covertly,_20).
 3919opposite(r,actively,passively,_20).
 3920opposite(r,below,above,_20).
 3921opposite(r,sanely,insanely,_20).
 3922opposite(r,empirically,theoretically,_20).
 3923opposite(r,permissibly,impermissibly,_20).
 3924opposite(r,temporarily,permanently,_20).
 3925opposite(r,conclusively,inconclusively,_20).
 3926opposite(r,upwind,downwind,_20).
 3927opposite(r,upwards,downwards,_20).
 3928opposite(r,upward,downward,_20).
 3929opposite(r,upwardly,downwardly,_20).
 3930opposite(r,upriver,downriver,_20).
 3931opposite(r,'at most','at least',_20).
 3932opposite(r,'at the most','at the least',_20).
 3933opposite(r,'at best','at worst',_20).
 3934opposite(r,responsibly,irresponsibly,_20).
 3935opposite(r,remarkably,unremarkably,_20).
 3936opposite(r,indoors,outdoors,_20).
 3937opposite(r,organically,inorganically,_20).
 3938opposite(r,officially,unofficially,_20).
 3939opposite(r,centrally,peripherally,_20).
 3940opposite(r,'on the one hand','on the other hand',_20).
 3941opposite(r,successfully,unsuccessfully,_20).
 3942opposite(r,systematically,unsystematically,_20).
 3943opposite(r,consistently,inconsistently,_20).
 3944opposite(r,constitutionally,unconstitutionally,_20).
 3945opposite(r,democratically,undemocratically,_20).
 3946opposite(r,typically,atypically,_20).
 3947opposite(r,linearly,geometrically,_20).
 3948opposite(r,primarily,secondarily,_20).
 3949opposite(r,dramatically,undramatically,_20).
 3950opposite(r,appropriately,inappropriately,_20).
 3951opposite(r,suitably,unsuitably,_20).
 3952opposite(r,naturally,artificially,_20).
 3953opposite(r,acutely,chronically,_20).
 3954opposite(r,sufficiently,insufficiently,_20).
 3955opposite(r,hesitantly,unhesitatingly,_20).
 3956opposite(r,'in hand','out of hand',_20).
 3957opposite(r,mindfully,unmindfully,_20).
 3958opposite(r,advertently,inadvertently,_20).
 3959opposite(r,comfortably,uncomfortably,_20).
 3960opposite(r,slowly,quickly,_20).
 3961opposite(r,publicly,privately,_20).
 3962opposite(r,orad,aborad,_20).
 3963opposite(r,patiently,impatiently,_20).
 3964opposite(r,steadily,unsteadily,_20).
 3965opposite(r,symmetrically,asymmetrically,_20).
 3966opposite(r,lightly,heavily,_20).
 3967opposite(r,weakly,strongly,_20).
 3968opposite(r,amply,meagerly,_20).
 3969opposite(r,gracefully,gracelessly,_20).
 3970opposite(r,considerately,inconsiderately,_20).
 3971opposite(r,helpfully,unhelpfully,_20).
 3972opposite(r,rationally,irrationally,_20).
 3973opposite(r,critically,uncritically,_20).
 3974opposite(r,competently,incompetently,_20).
 3975opposite(r,emotionally,unemotionally,_20).
 3976opposite(r,formally,informally,_20).
 3977opposite(r,enthusiastically,unenthusiastically,_20).
 3978opposite(r,finely,coarsely,_20).
 3979opposite(r,sympathetically,unsympathetically,_20).
 3980opposite(r,convincingly,unconvincingly,_20).
 3981opposite(r,graciously,ungraciously,_20).
 3982opposite(r,gracefully,ungracefully,_20).
 3983opposite(r,regularly,irregularly,_20).
 3984opposite(r,properly,improperly,_20).
 3985opposite(r,conveniently,inconveniently,_20).
 3986opposite(r,concretely,abstractly,_20).
 3987opposite(r,fearfully,fearlessly,_20).
 3988opposite(r,hopefully,hopelessly,_20).
 3989opposite(r,wisely,foolishly,_20).
 3990opposite(r,intelligently,unintelligently,_20).
 3991opposite(r,intelligibly,unintelligibly,_20).
 3992opposite(r,diplomatically,undiplomatically,_20).
 3993opposite(r,correctly,incorrectly,_20).
 3994opposite(r,right,wrongly,_20).
 3995opposite(r,accurately,inaccurately,_20).
 3996opposite(r,justly,unjustly,_20).
 3997opposite(r,hurriedly,unhurriedly,_20).
 3998opposite(r,monaurally,binaurally,_20).
 3999opposite(r,imaginatively,unimaginatively,_20).
 4000opposite(r,impressively,unimpressively,_20).
 4001opposite(r,productively,unproductively,_20).
 4002opposite(r,fruitfully,fruitlessly,_20).
 4003opposite(r,profitably,unprofitably,_20).
 4004opposite(r,expertly,amateurishly,_20).
 4005opposite(r,interestingly,uninterestingly,_20).
 4006opposite(r,realistically,unrealistically,_20).
 4007opposite(r,thoughtfully,thoughtlessly,_20).
 4008opposite(r,auspiciously,inauspiciously,_20).
 4009opposite(r,propitiously,unpropitiously,_20).
 4010opposite(r,politely,impolitely,_20).
 4011opposite(r,courteously,discourteously,_20).
 4012opposite(r,pleasantly,unpleasantly,_20).
 4013opposite(r,agreeably,disagreeably,_20).
 4014opposite(r,ambiguously,unambiguously,_20).
 4015opposite(r,ceremoniously,unceremoniously,_20).
 4016opposite(r,broadly,narrowly,_20).
 4017opposite(r,faithfully,unfaithfully,_20).
 4018opposite(r,dependably,undependably,_20).
 4019opposite(r,reliably,unreliably,_20).
 4020opposite(r,violently,nonviolently,_20).
 4021opposite(r,finitely,infinitely,_20).
 4022opposite(r,warily,unwarily,_20).
 4023opposite(r,quietly,noisily,_20).
 4024opposite(r,quietly,unquietly,_20).
 4025opposite(r,inwardly,outwardly,_20).
 4026opposite(r,favorably,unfavorably,_20).
 4027opposite(r,cheerfully,cheerlessly,_20).
 4028opposite(r,voluntarily,involuntarily,_20).
 4029opposite(r,efficiently,inefficiently,_20).
 4030opposite(r,wittingly,unwittingly,_20).
 4031opposite(r,knowingly,unknowingly,_20).
 4032opposite(r,justifiably,unjustifiably,_20).
 4033opposite(r,modestly,immodestly,_20).
 4034opposite(r,resolutely,irresolutely,_20).
 4035opposite(r,attractively,unattractively,_20).
 4036opposite(r,consciously,unconsciously,_20).
 4037opposite(r,competitively,noncompetitively,_20).
 4038opposite(r,believably,unbelievably,_20).
 4039opposite(r,decently,indecently,_20).
 4040opposite(r,characteristically,uncharacteristically,_20).
 4041opposite(r,internally,externally,_20).
 4042opposite(r,lawfully,unlawfully,_20).
 4043opposite(r,unilaterally,multilaterally,_20).
 4044opposite(r,appealingly,unappealingly,_20).
 4045opposite(r,approvingly,disapprovingly,_20).
 4046opposite(r,ambitiously,unambitiously,_20).
 4047opposite(r,ashamedly,unashamedly,_20).
 4048opposite(r,assertively,unassertively,_20).
 4049opposite(r,articulately,inarticulately,_20).
 4050opposite(r,audibly,inaudibly,_20).
 4051opposite(r,bloodily,bloodlessly,_20).
 4052opposite(r,appreciatively,unappreciatively,_20).
 4053opposite(r,gratefully,ungratefully,_20).
 4054opposite(r,seasonably,unseasonably,_20).
 4055opposite(r,cautiously,incautiously,_20).
 4056opposite(r,carefully,carelessly,_20).
 4057opposite(r,chivalrously,unchivalrously,_20).
 4058opposite(r,fairly,unfairly,_20).
 4059opposite(r,coherently,incoherently,_20).
 4060opposite(r,compatibly,incompatibly,_20).
 4061opposite(r,complainingly,uncomplainingly,_20).
 4062opposite(r,comprehensively,noncomprehensively,_20).
 4063opposite(r,conditionally,unconditionally,_20).
 4064opposite(r,consequentially,inconsequentially,_20).
 4065opposite(r,credibly,incredibly,_20).
 4066opposite(r,credulously,incredulously,_20).
 4067opposite(r,believingly,unbelievingly,_20).
 4068opposite(r,decisively,indecisively,_20).
 4069opposite(r,possibly,impossibly,_20).
 4070opposite(r,deservedly,undeservedly,_20).
 4071opposite(r,controversially,uncontroversially,_20).
 4072opposite(r,decorously,indecorously,_20).
 4073opposite(r,willingly,unwillingly,_20).
 4074opposite(r,offensively,defensively,_20).
 4075opposite(r,offensively,inoffensively,_20).
 4076opposite(r,harmfully,harmlessly,_20).
 4077opposite(r,honestly,dishonestly,_20).
 4078opposite(r,honorably,dishonorably,_20).
 4079opposite(r,loyally,disloyally,_20).
 4080opposite(r,obediently,disobediently,_20).
 4081opposite(r,proportionately,disproportionately,_20).
 4082opposite(r,reputably,disreputably,_20).
 4083opposite(r,respectfully,disrespectfully,_20).
 4084opposite(r,trustfully,distrustfully,_20).
 4085opposite(r,westerly,easterly,_20).
 4086opposite(r,effectually,ineffectually,_20).
 4087opposite(r,efficaciously,inefficaciously,_20).
 4088opposite(r,effectively,ineffectively,_20).
 4089opposite(r,selfishly,unselfishly,_20).
 4090opposite(r,elegantly,inelegantly,_20).
 4091opposite(r,eloquently,ineloquently,_20).
 4092opposite(r,encouragingly,discouragingly,_20).
 4093opposite(r,equitably,inequitably,_20).
 4094opposite(r,ethically,unethically,_20).
 4095opposite(r,evenly,unevenly,_20).
 4096opposite(r,equally,unequally,_20).
 4097opposite(r,excitingly,unexcitingly,_20).
 4098opposite(r,excusably,inexcusably,_20).
 4099opposite(r,forgivably,unforgivably,_20).
 4100opposite(r,pardonably,unpardonably,_20).
 4101opposite(r,expediently,inexpediently,_20).
 4102opposite(r,cheaply,expensively,_20).
 4103opposite(r,expressively,inexpressively,_20).
 4104opposite(r,fashionably,unfashionably,_20).
 4105opposite(r,civilly,uncivilly,_20).
 4106opposite(r,feelingly,unfeelingly,_20).
 4107opposite(r,felicitously,infelicitously,_20).
 4108opposite(r,literally,figuratively,_20).
 4109opposite(r,flexibly,inflexibly,_20).
 4110opposite(r,forgivingly,unforgivingly,_20).
 4111opposite(r,pianissimo,fortissimo,_20).
 4112opposite(r,joyfully,joylessly,_20).
 4113opposite(r,grudgingly,ungrudgingly,_20).
 4114opposite(r,hospitably,inhospitably,_20).
 4115opposite(r,humanely,inhumanely,_20).
 4116opposite(r,humorously,humorlessly,_20).
 4117opposite(r,hygienically,unhygienically,_20).
 4118opposite(r,legibly,illegibly,_20).
 4119opposite(r,legitimately,illegitimately,_20).
 4120opposite(r,lawfully,lawlessly,_20).
 4121opposite(r,licitly,illicitly,_20).
 4122opposite(r,logically,illogically,_20).
 4123opposite(r,morally,immorally,_20).
 4124opposite(r,penitently,impenitently,_20).
 4125opposite(r,repentantly,unrepentantly,_20).
 4126opposite(r,perceptibly,imperceptibly,_20).
 4127opposite(r,personally,impersonally,_20).
 4128opposite(r,implicitly,explicitly,_20).
 4129opposite(r,precisely,imprecisely,_20).
 4130opposite(r,exactly,inexactly,_20).
 4131opposite(r,providently,improvidently,_20).
 4132opposite(r,prudently,imprudently,_20).
 4133opposite(r,adequately,inadequately,_20).
 4134opposite(r,comparably,incomparably,_20).
 4135opposite(r,conspicuously,inconspicuously,_20).
 4136opposite(r,discreetly,indiscreetly,_20).
 4137opposite(r,informatively,uninformatively,_20).
 4138opposite(r,instructively,uninstructively,_20).
 4139opposite(r,opportunely,inopportunely,_20).
 4140opposite(r,securely,insecurely,_20).
 4141opposite(r,sensitively,insensitively,_20).
 4142opposite(r,sincerely,insincerely,_20).
 4143opposite(r,tolerantly,intolerantly,_20).
 4144opposite(r,transitively,intransitively,_20).
 4145opposite(r,visibly,invisibly,_20).
 4146opposite(r,maturely,immaturely,_20).
 4147opposite(r,judiciously,injudiciously,_20).
 4148opposite(r,manageably,unmanageably,_20).
 4149opposite(r,manfully,unmanfully,_20).
 4150opposite(r,malevolently,benevolently,_20).
 4151opposite(r,minimally,maximally,_20).
 4152opposite(r,measurably,immeasurably,_20).
 4153opposite(r,melodiously,unmelodiously,_20).
 4154opposite(r,memorably,unmemorably,_20).
 4155opposite(r,truthfully,untruthfully,_20).
 4156opposite(r,musically,unmusically,_20).
 4157opposite(r,'broad-mindedly','narrow-mindedly',_20).
 4158opposite(r,necessarily,unnecessarily,_20).
 4159opposite(r,objectively,subjectively,_20).
 4160opposite(r,obtrusively,unobtrusively,_20).
 4161opposite(r,optimistically,pessimistically,_20).
 4162opposite(r,optionally,obligatorily,_20).
 4163opposite(r,palatably,unpalatably,_20).
 4164opposite(r,patriotically,unpatriotically,_20).
 4165opposite(r,recognizably,unrecognizably,_20).
 4166opposite(r,pretentiously,unpretentiously,_20).
 4167opposite(r,relevantly,irrelevantly,_20).
 4168opposite(r,reverently,irreverently,_20).
 4169opposite(r,righteously,unrighteously,_20).
 4170opposite(r,'self-consciously',unselfconsciously,_20).
 4171opposite(r,sentimentally,unsentimentally,_20).
 4172opposite(r,separably,inseparably,_20).
 4173opposite(r,smilingly,unsmilingly,_20).
 4174opposite(r,sociably,unsociably,_20).
 4175opposite(r,sportingly,unsportingly,_20).
 4176opposite(r,romantically,unromantically,_20).
 4177opposite(r,tactfully,tactlessly,_20).
 4178opposite(r,tastefully,tastelessly,_20).
 4179opposite(r,thinly,thickly,_20).
 4180opposite(r,grammatically,ungrammatically,_20).
 4181opposite(r,precedentedly,unprecedentedly,_20).
 4182opposite(r,usefully,uselessly,_20).
 4183opposite(r,convexly,concavely,_20).
 4184opposite(r,painfully,painlessly,_20).
 4185opposite(r,adaxially,abaxially,_20)