Skip to content

Instantly share code, notes, and snippets.

@vasilescur
Last active February 2, 2023 07:37
Show Gist options
  • Save vasilescur/a223d6e95423fe86cfd3fca097d3ee78 to your computer and use it in GitHub Desktop.
Save vasilescur/a223d6e95423fe86cfd3fca097d3ee78 to your computer and use it in GitHub Desktop.
% Prolog Wordle Solver
% Author: Radu Vasilescu
green_valid(GreenLetter, WordLetter) :-
var(GreenLetter);
atom(GreenLetter), GreenLetter = WordLetter.
black_valid(Black, WordChars) :-
forall(member(B, Black),
\+ member(B, WordChars)).
yellow_valid(YellowEntry, WordLetter) :-
forall(member(Y, YellowEntry),
Y \= WordLetter).
yellow_appears(Yellow, WordChars) :-
forall(member(YellowEntry, Yellow),
forall(member(YellowLetter, YellowEntry),
member(YellowLetter, WordChars))).
wordle_line(Green, Yellow, Black, Word) :-
w(Word),
atom_chars(Word, WordChars),
maplist(green_valid, Green, WordChars),
black_valid(Black, WordChars),
maplist(yellow_valid, Yellow, WordChars),
yellow_appears(Yellow, WordChars).
% Word bank
% Source: https://www.nytimes.com/games/wordle/index.html
w(cigar). w(rebut). w(sissy). w(humph).
w(awake). w(blush). w(focal). w(evade).
w(naval). w(serve). w(heath). w(dwarf).
w(model). w(karma). w(stink). w(grade).
w(quiet). w(bench). w(abate). w(feign).
w(major). w(death). w(fresh). w(crust).
w(stool). w(colon). w(abase). w(marry).
w(react). w(batty). w(pride). w(floss).
w(helix). w(croak). w(staff). w(paper).
w(unfed). w(whelp). w(trawl). w(outdo).
w(adobe). w(crazy). w(sower). w(repay).
w(digit). w(crate). w(cluck). w(spike).
w(mimic). w(pound). w(maxim). w(linen).
w(unmet). w(flesh). w(booby). w(forth).
w(first). w(stand). w(belly). w(ivory).
w(seedy). w(print). w(yearn). w(drain).
w(bribe). w(stout). w(panel). w(crass).
w(flume). w(offal). w(agree). w(error).
w(swirl). w(argue). w(bleed). w(delta).
w(flick). w(totem). w(wooer). w(front).
w(shrub). w(parry). w(biome). w(lapel).
w(start). w(greet). w(goner). w(golem).
w(lusty). w(loopy). w(round). w(audit).
w(lying). w(gamma). w(labor). w(islet).
w(civic). w(forge). w(corny). w(moult).
w(basic). w(salad). w(agate). w(spicy).
w(spray). w(essay). w(fjord). w(spend).
w(kebab). w(guild). w(aback). w(motor).
w(alone). w(hatch). w(hyper). w(thumb).
w(dowry). w(ought). w(belch). w(dutch).
w(pilot). w(tweed). w(comet). w(jaunt).
w(enema). w(steed). w(abyss). w(growl).
w(fling). w(dozen). w(boozy). w(erode).
w(world). w(gouge). w(click). w(briar).
w(great). w(altar). w(pulpy). w(blurt).
w(coast). w(duchy). w(groin). w(fixer).
w(group). w(rogue). w(badly). w(smart).
w(pithy). w(gaudy). w(chill). w(heron).
w(vodka). w(finer). w(surer). w(radio).
w(rouge). w(perch). w(retch). w(wrote).
w(clock). w(tilde). w(store). w(prove).
w(bring). w(solve). w(cheat). w(grime).
w(exult). w(usher). w(epoch). w(triad).
w(break). w(rhino). w(viral). w(conic).
w(masse). w(sonic). w(vital). w(trace).
w(using). w(peach). w(champ). w(baton).
w(brake). w(pluck). w(craze). w(gripe).
w(weary). w(picky). w(acute). w(ferry).
w(aside). w(tapir). w(troll). w(unify).
w(rebus). w(boost). w(truss). w(siege).
w(tiger). w(banal). w(slump). w(crank).
w(gorge). w(query). w(drink). w(favor).
w(abbey). w(tangy). w(panic). w(solar).
w(shire). w(proxy). w(point). w(robot).
w(prick). w(wince). w(crimp). w(knoll).
w(sugar). w(whack). w(mount). w(perky).
w(could). w(wrung). w(light). w(those).
w(moist). w(shard). w(pleat). w(aloft).
w(skill). w(elder). w(frame). w(humor).
w(pause). w(ulcer). w(ultra). w(robin).
w(cynic). w(aroma). w(caulk). w(shake).
w(dodge). w(swill). w(tacit). w(other).
w(thorn). w(trove). w(bloke). w(vivid).
w(spill). w(chant). w(choke). w(rupee).
w(nasty). w(mourn). w(ahead). w(brine).
w(cloth). w(hoard). w(sweet). w(month).
w(lapse). w(watch). w(today). w(focus).
w(smelt). w(tease). w(cater). w(movie).
w(saute). w(allow). w(renew). w(their).
w(slosh). w(purge). w(chest). w(depot).
w(epoxy). w(nymph). w(found). w(shall).
w(harry). w(stove). w(lowly). w(snout).
w(trope). w(fewer). w(shawl). w(natal).
w(comma). w(foray). w(scare). w(stair).
w(black). w(squad). w(royal). w(chunk).
w(mince). w(shame). w(cheek). w(ample).
w(flair). w(foyer). w(cargo). w(oxide).
w(plant). w(olive). w(inert). w(askew).
w(heist). w(shown). w(zesty). w(hasty).
w(trash). w(fella). w(larva). w(forgo).
w(story). w(hairy). w(train). w(homer).
w(badge). w(midst). w(canny). w(fetus).
w(butch). w(farce). w(slung). w(tipsy).
w(metal). w(yield). w(delve). w(being).
w(scour). w(glass). w(gamer). w(scrap).
w(money). w(hinge). w(album). w(vouch).
w(asset). w(tiara). w(crept). w(bayou).
w(atoll). w(manor). w(creak). w(showy).
w(phase). w(froth). w(depth). w(gloom).
w(flood). w(trait). w(girth). w(piety).
w(payer). w(goose). w(float). w(donor).
w(atone). w(primo). w(apron). w(blown).
w(cacao). w(loser). w(input). w(gloat).
w(awful). w(brink). w(smite). w(beady).
w(rusty). w(retro). w(droll). w(gawky).
w(hutch). w(pinto). w(gaily). w(egret).
w(lilac). w(sever). w(field). w(fluff).
w(hydro). w(flack). w(agape). w(voice).
w(stead). w(stalk). w(berth). w(madam).
w(night). w(bland). w(liver). w(wedge).
w(augur). w(roomy). w(wacky). w(flock).
w(angry). w(bobby). w(trite). w(aphid).
w(tryst). w(midge). w(power). w(elope).
w(cinch). w(motto). w(stomp). w(upset).
w(bluff). w(cramp). w(quart). w(coyly).
w(youth). w(rhyme). w(buggy). w(alien).
w(smear). w(unfit). w(patty). w(cling).
w(glean). w(label). w(hunky). w(khaki).
w(poker). w(gruel). w(twice). w(twang).
w(shrug). w(treat). w(unlit). w(waste).
w(merit). w(woven). w(octal). w(needy).
w(clown). w(widow). w(irony). w(ruder).
w(gauze). w(chief). w(onset). w(prize).
w(fungi). w(charm). w(gully). w(inter).
w(whoop). w(taunt). w(leery). w(class).
w(theme). w(lofty). w(tibia). w(booze).
w(alpha). w(thyme). w(eclat). w(doubt).
w(parer). w(chute). w(stick). w(trice).
w(alike). w(sooth). w(recap). w(saint).
w(liege). w(glory). w(grate). w(admit).
w(brisk). w(soggy). w(usurp). w(scald).
w(scorn). w(leave). w(twine). w(sting).
w(bough). w(marsh). w(sloth). w(dandy).
w(vigor). w(howdy). w(enjoy). w(valid).
w(ionic). w(equal). w(unset). w(floor).
w(catch). w(spade). w(stein). w(exist).
w(quirk). w(denim). w(grove). w(spiel).
w(mummy). w(fault). w(foggy). w(flout).
w(carry). w(sneak). w(libel). w(waltz).
w(aptly). w(piney). w(inept). w(aloud).
w(photo). w(dream). w(stale). w(vomit).
w(ombre). w(fanny). w(unite). w(snarl).
w(baker). w(there). w(glyph). w(pooch).
w(hippy). w(spell). w(folly). w(louse).
w(gulch). w(vault). w(godly). w(threw).
w(fleet). w(grave). w(inane). w(shock).
w(crave). w(spite). w(valve). w(skimp).
w(claim). w(rainy). w(musty). w(pique).
w(daddy). w(quasi). w(arise). w(aging).
w(valet). w(opium). w(avert). w(stuck).
w(recut). w(mulch). w(genre). w(plume).
w(rifle). w(count). w(incur). w(total).
w(wrest). w(mocha). w(deter). w(study).
w(lover). w(safer). w(rivet). w(funny).
w(smoke). w(mound). w(undue). w(sedan).
w(pagan). w(swine). w(guile). w(gusty).
w(equip). w(tough). w(canoe). w(chaos).
w(covet). w(human). w(udder). w(lunch).
w(blast). w(stray). w(manga). w(melee).
w(lefty). w(quick). w(paste). w(given).
w(octet). w(risen). w(groan). w(leaky).
w(grind). w(carve). w(loose). w(sadly).
w(spilt). w(apple). w(slack). w(honey).
w(final). w(sheen). w(eerie). w(minty).
w(slick). w(derby). w(wharf). w(spelt).
w(coach). w(erupt). w(singe). w(price).
w(spawn). w(fairy). w(jiffy). w(filmy).
w(stack). w(chose). w(sleep). w(ardor).
w(nanny). w(niece). w(woozy). w(handy).
w(grace). w(ditto). w(stank). w(cream).
w(usual). w(diode). w(valor). w(angle).
w(ninja). w(muddy). w(chase). w(reply).
w(prone). w(spoil). w(heart). w(shade).
w(diner). w(arson). w(onion). w(sleet).
w(dowel). w(couch). w(palsy). w(bowel).
w(smile). w(evoke). w(creek). w(lance).
w(eagle). w(idiot). w(siren). w(built).
w(embed). w(award). w(dross). w(annul).
w(goody). w(frown). w(patio). w(laden).
w(humid). w(elite). w(lymph). w(edify).
w(might). w(reset). w(visit). w(gusto).
w(purse). w(vapor). w(crock). w(write).
w(sunny). w(loath). w(chaff). w(slide).
w(queer). w(venom). w(stamp). w(sorry).
w(still). w(acorn). w(aping). w(pushy).
w(tamer). w(hater). w(mania). w(awoke).
w(brawn). w(swift). w(exile). w(birch).
w(lucky). w(freer). w(risky). w(ghost).
w(plier). w(lunar). w(winch). w(snare).
w(nurse). w(house). w(borax). w(nicer).
w(lurch). w(exalt). w(about). w(savvy).
w(toxin). w(tunic). w(pried). w(inlay).
w(chump). w(lanky). w(cress). w(eater).
w(elude). w(cycle). w(kitty). w(boule).
w(moron). w(tenet). w(place). w(lobby).
w(plush). w(vigil). w(index). w(blink).
w(clung). w(qualm). w(croup). w(clink).
w(juicy). w(stage). w(decay). w(nerve).
w(flier). w(shaft). w(crook). w(clean).
w(china). w(ridge). w(vowel). w(gnome).
w(snuck). w(icing). w(spiny). w(rigor).
w(snail). w(flown). w(rabid). w(prose).
w(thank). w(poppy). w(budge). w(fiber).
w(moldy). w(dowdy). w(kneel). w(track).
w(caddy). w(quell). w(dumpy). w(paler).
w(swore). w(rebar). w(scuba). w(splat).
w(flyer). w(horny). w(mason). w(doing).
w(ozone). w(amply). w(molar). w(ovary).
w(beset). w(queue). w(cliff). w(magic).
w(truce). w(sport). w(fritz). w(edict).
w(twirl). w(verse). w(llama). w(eaten).
w(range). w(whisk). w(hovel). w(rehab).
w(macaw). w(sigma). w(spout). w(verve).
w(sushi). w(dying). w(fetid). w(brain).
w(buddy). w(thump). w(scion). w(candy).
w(chord). w(basin). w(march). w(crowd).
w(arbor). w(gayly). w(musky). w(stain).
w(dally). w(bless). w(bravo). w(stung).
w(title). w(ruler). w(kiosk). w(blond).
w(ennui). w(layer). w(fluid). w(tatty).
w(score). w(cutie). w(zebra). w(barge).
w(matey). w(bluer). w(aider). w(shook).
w(river). w(privy). w(betel). w(frisk).
w(bongo). w(begun). w(azure). w(weave).
w(genie). w(sound). w(glove). w(braid).
w(scope). w(wryly). w(rover). w(assay).
w(ocean). w(bloom). w(irate). w(later).
w(woken). w(silky). w(wreck). w(dwelt).
w(slate). w(smack). w(solid). w(amaze).
w(hazel). w(wrist). w(jolly). w(globe).
w(flint). w(rouse). w(civil). w(vista).
w(relax). w(cover). w(alive). w(beech).
w(jetty). w(bliss). w(vocal). w(often).
w(dolly). w(eight). w(joker). w(since).
w(event). w(ensue). w(shunt). w(diver).
w(poser). w(worst). w(sweep). w(alley).
w(creed). w(anime). w(leafy). w(bosom).
w(dunce). w(stare). w(pudgy). w(waive).
w(choir). w(stood). w(spoke). w(outgo).
w(delay). w(bilge). w(ideal). w(clasp).
w(seize). w(hotly). w(laugh). w(sieve).
w(block). w(meant). w(grape). w(noose).
w(hardy). w(shied). w(drawl). w(daisy).
w(putty). w(strut). w(burnt). w(tulip).
w(crick). w(idyll). w(vixen). w(furor).
w(geeky). w(cough). w(naive). w(shoal).
w(stork). w(bathe). w(aunty). w(check).
w(prime). w(brass). w(outer). w(furry).
w(razor). w(elect). w(evict). w(imply).
w(demur). w(quota). w(haven). w(cavil).
w(swear). w(crump). w(dough). w(gavel).
w(wagon). w(salon). w(nudge). w(harem).
w(pitch). w(sworn). w(pupil). w(excel).
w(stony). w(cabin). w(unzip). w(queen).
w(trout). w(polyp). w(earth). w(storm).
w(until). w(taper). w(enter). w(child).
w(adopt). w(minor). w(fatty). w(husky).
w(brave). w(filet). w(slime). w(glint).
w(tread). w(steal). w(regal). w(guest).
w(every). w(murky). w(share). w(spore).
w(hoist). w(buxom). w(inner). w(otter).
w(dimly). w(level). w(sumac). w(donut).
w(stilt). w(arena). w(sheet). w(scrub).
w(fancy). w(slimy). w(pearl). w(silly).
w(porch). w(dingo). w(sepia). w(amble).
w(shady). w(bread). w(friar). w(reign).
w(dairy). w(quill). w(cross). w(brood).
w(tuber). w(shear). w(posit). w(blank).
w(villa). w(shank). w(piggy). w(freak).
w(which). w(among). w(fecal). w(shell).
w(would). w(algae). w(large). w(rabbi).
w(agony). w(amuse). w(bushy). w(copse).
w(swoon). w(knife). w(pouch). w(ascot).
w(plane). w(crown). w(urban). w(snide).
w(relay). w(abide). w(viola). w(rajah).
w(straw). w(dilly). w(crash). w(amass).
w(third). w(trick). w(tutor). w(woody).
w(blurb). w(grief). w(disco). w(where).
w(sassy). w(beach). w(sauna). w(comic).
w(clued). w(creep). w(caste). w(graze).
w(snuff). w(frock). w(gonad). w(drunk).
w(prong). w(lurid). w(steel). w(halve).
w(buyer). w(vinyl). w(utile). w(smell).
w(adage). w(worry). w(tasty). w(local).
w(trade). w(finch). w(ashen). w(modal).
w(gaunt). w(clove). w(enact). w(adorn).
w(roast). w(speck). w(sheik). w(missy).
w(grunt). w(snoop). w(party). w(touch).
w(mafia). w(emcee). w(array). w(south).
w(vapid). w(jelly). w(skulk). w(angst).
w(tubal). w(lower). w(crest). w(sweat).
w(cyber). w(adore). w(tardy). w(swami).
w(notch). w(groom). w(roach). w(hitch).
w(young). w(align). w(ready). w(frond).
w(strap). w(puree). w(realm). w(venue).
w(swarm). w(offer). w(seven). w(dryer).
w(diary). w(dryly). w(drank). w(acrid).
w(heady). w(theta). w(junto). w(pixie).
w(quoth). w(bonus). w(shalt). w(penne).
w(amend). w(datum). w(build). w(piano).
w(shelf). w(lodge). w(suing). w(rearm).
w(coral). w(ramen). w(worth). w(psalm).
w(infer). w(overt). w(mayor). w(ovoid).
w(glide). w(usage). w(poise). w(randy).
w(chuck). w(prank). w(fishy). w(tooth).
w(ether). w(drove). w(idler). w(swath).
w(stint). w(while). w(begat). w(apply).
w(slang). w(tarot). w(radar). w(credo).
w(aware). w(canon). w(shift). w(timer).
w(bylaw). w(serum). w(three). w(steak).
w(iliac). w(shirk). w(blunt). w(puppy).
w(penal). w(joist). w(bunny). w(shape).
w(beget). w(wheel). w(adept). w(stunt).
w(stole). w(topaz). w(chore). w(fluke).
w(afoot). w(bloat). w(bully). w(dense).
w(caper). w(sneer). w(boxer). w(jumbo).
w(lunge). w(space). w(avail). w(short).
w(slurp). w(loyal). w(flirt). w(pizza).
w(conch). w(tempo). w(droop). w(plate).
w(bible). w(plunk). w(afoul). w(savoy).
w(steep). w(agile). w(stake). w(dwell).
w(knave). w(beard). w(arose). w(motif).
w(smash). w(broil). w(glare). w(shove).
w(baggy). w(mammy). w(swamp). w(along).
w(rugby). w(wager). w(quack). w(squat).
w(snaky). w(debit). w(mange). w(skate).
w(ninth). w(joust). w(tramp). w(spurn).
w(medal). w(micro). w(rebel). w(flank).
w(learn). w(nadir). w(maple). w(comfy).
w(remit). w(gruff). w(ester). w(least).
w(mogul). w(fetch). w(cause). w(oaken).
w(aglow). w(meaty). w(gaffe). w(shyly).
w(racer). w(prowl). w(thief). w(stern).
w(poesy). w(rocky). w(tweet). w(waist).
w(spire). w(grope). w(havoc). w(patsy).
w(truly). w(forty). w(deity). w(uncle).
w(swish). w(giver). w(preen). w(bevel).
w(lemur). w(draft). w(slope). w(annoy).
w(lingo). w(bleak). w(ditty). w(curly).
w(cedar). w(dirge). w(grown). w(horde).
w(drool). w(shuck). w(crypt). w(cumin).
w(stock). w(gravy). w(locus). w(wider).
w(breed). w(quite). w(chafe). w(cache).
w(blimp). w(deign). w(fiend). w(logic).
w(cheap). w(elide). w(rigid). w(false).
w(renal). w(pence). w(rowdy). w(shoot).
w(blaze). w(envoy). w(posse). w(brief).
w(never). w(abort). w(mouse). w(mucky).
w(sulky). w(fiery). w(media). w(trunk).
w(yeast). w(clear). w(skunk). w(scalp).
w(bitty). w(cider). w(koala). w(duvet).
w(segue). w(creme). w(super). w(grill).
w(after). w(owner). w(ember). w(reach).
w(nobly). w(empty). w(speed). w(gipsy).
w(recur). w(smock). w(dread). w(merge).
w(burst). w(kappa). w(amity). w(shaky).
w(hover). w(carol). w(snort). w(synod).
w(faint). w(haunt). w(flour). w(chair).
w(detox). w(shrew). w(tense). w(plied).
w(quark). w(burly). w(novel). w(waxen).
w(stoic). w(jerky). w(blitz). w(beefy).
w(lyric). w(hussy). w(towel). w(quilt).
w(below). w(bingo). w(wispy). w(brash).
w(scone). w(toast). w(easel). w(saucy).
w(value). w(spice). w(honor). w(route).
w(sharp). w(bawdy). w(radii). w(skull).
w(phony). w(issue). w(lager). w(swell).
w(urine). w(gassy). w(trial). w(flora).
w(upper). w(latch). w(wight). w(brick).
w(retry). w(holly). w(decal). w(grass).
w(shack). w(dogma). w(mover). w(defer).
w(sober). w(optic). w(crier). w(vying).
w(nomad). w(flute). w(hippo). w(shark).
w(drier). w(obese). w(bugle). w(tawny).
w(chalk). w(feast). w(ruddy). w(pedal).
w(scarf). w(cruel). w(bleat). w(tidal).
w(slush). w(semen). w(windy). w(dusty).
w(sally). w(igloo). w(nerdy). w(jewel).
w(shone). w(whale). w(hymen). w(abuse).
w(fugue). w(elbow). w(crumb). w(pansy).
w(welsh). w(syrup). w(terse). w(suave).
w(gamut). w(swung). w(drake). w(freed).
w(afire). w(shirt). w(grout). w(oddly).
w(tithe). w(plaid). w(dummy). w(broom).
w(blind). w(torch). w(enemy). w(again).
w(tying). w(pesky). w(alter). w(gazer).
w(noble). w(ethos). w(bride). w(extol).
w(decor). w(hobby). w(beast). w(idiom).
w(utter). w(these). w(sixth). w(alarm).
w(erase). w(elegy). w(spunk). w(piper).
w(scaly). w(scold). w(hefty). w(chick).
w(sooty). w(canal). w(whiny). w(slash).
w(quake). w(joint). w(swept). w(prude).
w(heavy). w(wield). w(femme). w(lasso).
w(maize). w(shale). w(screw). w(spree).
w(smoky). w(whiff). w(scent). w(glade).
w(spent). w(prism). w(stoke). w(riper).
w(orbit). w(cocoa). w(guilt). w(humus).
w(shush). w(table). w(smirk). w(wrong).
w(noisy). w(alert). w(shiny). w(elate).
w(resin). w(whole). w(hunch). w(pixel).
w(polar). w(hotel). w(sword). w(cleat).
w(mango). w(rumba). w(puffy). w(filly).
w(billy). w(leash). w(clout). w(dance).
w(ovate). w(facet). w(chili). w(paint).
w(liner). w(curio). w(salty). w(audio).
w(snake). w(fable). w(cloak). w(navel).
w(spurt). w(pesto). w(balmy). w(flash).
w(unwed). w(early). w(churn). w(weedy).
w(stump). w(lease). w(witty). w(wimpy).
w(spoof). w(saner). w(blend). w(salsa).
w(thick). w(warty). w(manic). w(blare).
w(squib). w(spoon). w(probe). w(crepe).
w(knack). w(force). w(debut). w(order).
w(haste). w(teeth). w(agent). w(widen).
w(icily). w(slice). w(ingot). w(clash).
w(juror). w(blood). w(abode). w(throw).
w(unity). w(pivot). w(slept). w(troop).
w(spare). w(sewer). w(parse). w(morph).
w(cacti). w(tacky). w(spool). w(demon).
w(moody). w(annex). w(begin). w(fuzzy).
w(patch). w(water). w(lumpy). w(admin).
w(omega). w(limit). w(tabby). w(macho).
w(aisle). w(skiff). w(basis). w(plank).
w(verge). w(botch). w(crawl). w(lousy).
w(slain). w(cubic). w(raise). w(wrack).
w(guide). w(foist). w(cameo). w(under).
w(actor). w(revue). w(fraud). w(harpy).
w(scoop). w(climb). w(refer). w(olden).
w(clerk). w(debar). w(tally). w(ethic).
w(cairn). w(tulle). w(ghoul). w(hilly).
w(crude). w(apart). w(scale). w(older).
w(plain). w(sperm). w(briny). w(abbot).
w(rerun). w(quest). w(crisp). w(bound).
w(befit). w(drawn). w(suite). w(itchy).
w(cheer). w(bagel). w(guess). w(broad).
w(axiom). w(chard). w(caput). w(leant).
w(harsh). w(curse). w(proud). w(swing).
w(opine). w(taste). w(lupus). w(gumbo).
w(miner). w(green). w(chasm). w(lipid).
w(topic). w(armor). w(brush). w(crane).
w(mural). w(abled). w(habit). w(bossy).
w(maker). w(dusky). w(dizzy). w(lithe).
w(brook). w(jazzy). w(fifty). w(sense).
w(giant). w(surly). w(legal). w(fatal).
w(flunk). w(began). w(prune). w(small).
w(slant). w(scoff). w(torus). w(ninny).
w(covey). w(viper). w(taken). w(moral).
w(vogue). w(owing). w(token). w(entry).
w(booth). w(voter). w(chide). w(elfin).
w(ebony). w(neigh). w(minim). w(melon).
w(kneed). w(decoy). w(voila). w(ankle).
w(arrow). w(mushy). w(tribe). w(cease).
w(eager). w(birth). w(graph). w(odder).
w(terra). w(weird). w(tried). w(clack).
w(color). w(rough). w(weigh). w(uncut).
w(ladle). w(strip). w(craft). w(minus).
w(dicey). w(titan). w(lucid). w(vicar).
w(dress). w(ditch). w(gypsy). w(pasta).
w(taffy). w(flame). w(swoop). w(aloof).
w(sight). w(broke). w(teary). w(chart).
w(sixty). w(wordy). w(sheer). w(leper).
w(nosey). w(bulge). w(savor). w(clamp).
w(funky). w(foamy). w(toxic). w(brand).
w(plumb). w(dingy). w(butte). w(drill).
w(tripe). w(bicep). w(tenor). w(krill).
w(worse). w(drama). w(hyena). w(think).
w(ratio). w(cobra). w(basil). w(scrum).
w(bused). w(phone). w(court). w(camel).
w(proof). w(heard). w(angel). w(petal).
w(pouty). w(throb). w(maybe). w(fetal).
w(sprig). w(spine). w(shout). w(cadet).
w(macro). w(dodgy). w(satyr). w(rarer).
w(binge). w(trend). w(nutty). w(leapt).
w(amiss). w(split). w(myrrh). w(width).
w(sonar). w(tower). w(baron). w(fever).
w(waver). w(spark). w(belie). w(sloop).
w(expel). w(smote). w(baler). w(above).
w(north). w(wafer). w(scant). w(frill).
w(awash). w(snack). w(scowl). w(frail).
w(drift). w(limbo). w(fence). w(motel).
w(ounce). w(wreak). w(revel). w(talon).
w(prior). w(knelt). w(cello). w(flake).
w(debug). w(anode). w(crime). w(salve).
w(scout). w(imbue). w(pinky). w(stave).
w(vague). w(chock). w(fight). w(video).
w(stone). w(teach). w(cleft). w(frost).
w(prawn). w(booty). w(twist). w(apnea).
w(stiff). w(plaza). w(ledge). w(tweak).
w(board). w(grant). w(medic). w(bacon).
w(cable). w(brawl). w(slunk). w(raspy).
w(forum). w(drone). w(women). w(mucus).
w(boast). w(toddy). w(coven). w(tumor).
w(truer). w(wrath). w(stall). w(steam).
w(axial). w(purer). w(daily). w(trail).
w(niche). w(mealy). w(juice). w(nylon).
w(plump). w(merry). w(flail). w(papal).
w(wheat). w(berry). w(cower). w(erect).
w(brute). w(leggy). w(snipe). w(sinew).
w(skier). w(penny). w(jumpy). w(rally).
w(umbra). w(scary). w(modem). w(gross).
w(avian). w(greed). w(satin). w(tonic).
w(parka). w(sniff). w(livid). w(stark).
w(trump). w(giddy). w(reuse). w(taboo).
w(avoid). w(quote). w(devil). w(liken).
w(gloss). w(gayer). w(beret). w(noise).
w(gland). w(dealt). w(sling). w(rumor).
w(opera). w(thigh). w(tonga). w(flare).
w(wound). w(white). w(bulky). w(etude).
w(horse). w(circa). w(paddy). w(inbox).
w(fizzy). w(grain). w(exert). w(surge).
w(gleam). w(belle). w(salvo). w(crush).
w(fruit). w(sappy). w(taker). w(tract).
w(ovine). w(spiky). w(frank). w(reedy).
w(filth). w(spasm). w(heave). w(mambo).
w(right). w(clank). w(trust). w(lumen).
w(borne). w(spook). w(sauce). w(amber).
w(lathe). w(carat). w(corer). w(dirty).
w(slyly). w(affix). w(alloy). w(taint).
w(sheep). w(kinky). w(wooly). w(mauve).
w(flung). w(yacht). w(fried). w(quail).
w(brunt). w(grimy). w(curvy). w(cagey).
w(rinse). w(deuce). w(state). w(grasp).
w(milky). w(bison). w(graft). w(sandy).
w(baste). w(flask). w(hedge). w(girly).
w(swash). w(boney). w(coupe). w(endow).
w(abhor). w(welch). w(blade). w(tight).
w(geese). w(miser). w(mirth). w(cloud).
w(cabal). w(leech). w(close). w(tenth).
w(pecan). w(droit). w(grail). w(clone).
w(guise). w(ralph). w(tango). w(biddy).
w(smith). w(mower). w(payee). w(serif).
w(drape). w(fifth). w(spank). w(glaze).
w(allot). w(truck). w(kayak). w(virus).
w(testy). w(tepee). w(fully). w(zonal).
w(metro). w(curry). w(grand). w(banjo).
w(axion). w(bezel). w(occur). w(chain).
w(nasal). w(gooey). w(filer). w(brace).
w(allay). w(pubic). w(raven). w(plead).
w(gnash). w(flaky). w(munch). w(dully).
w(eking). w(thing). w(slink). w(hurry).
w(theft). w(shorn). w(pygmy). w(ranch).
w(wring). w(lemon). w(shore). w(mamma).
w(froze). w(newer). w(style). w(moose).
w(antic). w(drown). w(vegan). w(chess).
w(guppy). w(union). w(lever). w(lorry).
w(image). w(cabby). w(druid). w(exact).
w(truth). w(dopey). w(spear). w(cried).
w(chime). w(crony). w(stunk). w(timid).
w(batch). w(gauge). w(rotor). w(crack).
w(curve). w(latte). w(witch). w(bunch).
w(repel). w(anvil). w(soapy). w(meter).
w(broth). w(madly). w(dried). w(scene).
w(known). w(magma). w(roost). w(woman).
w(thong). w(punch). w(pasty). w(downy).
w(knead). w(whirl). w(rapid). w(clang).
w(anger). w(drive). w(goofy). w(email).
w(music). w(stuff). w(bleep). w(rider).
w(mecca). w(folio). w(setup). w(verso).
w(quash). w(fauna). w(gummy). w(happy).
w(newly). w(fussy). w(relic). w(guava).
w(ratty). w(fudge). w(femur). w(chirp).
w(forte). w(alibi). w(whine). w(petty).
w(golly). w(plait). w(fleck). w(felon).
w(gourd). w(brown). w(thrum). w(ficus).
w(stash). w(decry). w(wiser). w(junta).
w(visor). w(daunt). w(scree). w(impel).
w(await). w(press). w(whose). w(turbo).
w(stoop). w(speak). w(mangy). w(eying).
w(inlet). w(crone). w(pulse). w(mossy).
w(staid). w(hence). w(pinch). w(teddy).
w(sully). w(snore). w(ripen). w(snowy).
w(attic). w(going). w(leach). w(mouth).
w(hound). w(clump). w(tonal). w(bigot).
w(peril). w(piece). w(blame). w(haute).
w(spied). w(undid). w(intro). w(basal).
w(shine). w(gecko). w(rodeo). w(guard).
w(steer). w(loamy). w(scamp). w(scram).
w(manly). w(hello). w(vaunt). w(organ).
w(feral). w(knock). w(extra). w(condo).
w(adapt). w(willy). w(polka). w(rayon).
w(skirt). w(faith). w(torso). w(match).
w(mercy). w(tepid). w(sleek). w(riser).
w(twixt). w(peace). w(flush). w(catty).
w(login). w(eject). w(roger). w(rival).
w(untie). w(refit). w(aorta). w(adult).
w(judge). w(rower). w(artsy). w(rural).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment