{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} -- | Words is special because GHC can't handle this many Symbols. -- The `Choose` trick helps, but only to about 1024 words, after -- which the compiler fails. module Data.Memorable.Theme.Words where import Data.Memorable type Words12 = Words type Words11 = LeftSide Words12 type Words10 = LeftSide Words11 type Words9 = LeftSide Words10 type Words8 = LeftSide Words9 type Words7 = LeftSide Words8 type Words6 = LeftSide Words7 type Words5 = LeftSide Words6 type Words4 = LeftSide Words5 -- | A collection of words words12 :: Proxy Words12 words12 = Proxy words11 :: Proxy Words11 words11 = leftSide words12 words10 :: Proxy Words10 words10 = leftSide words11 words9 :: Proxy Words9 words9 = leftSide words10 words8 :: Proxy Words8 words8 = leftSide words9 words7 :: Proxy Words7 words7 = leftSide words8 words6 :: Proxy Words6 words6 = leftSide words7 words5 :: Proxy Words5 words5 = leftSide words6 words4 :: Proxy Words4 words4 = leftSide words5 -- | Three words made to fit into 32 bits threeWordsFor32Bits :: Proxy (Words12 :- Words10 :- Words10) threeWordsFor32Bits = Proxy -- | Six words made to fit into 64 bits sixWordsFor64Bits :: Proxy (Words12 :- Words12 :- Words10 :- Words9 :- Words9 :- Words12) sixWordsFor64Bits = Proxy type FLW10 = FourLetterWords type FLW9 = LeftSide FLW10 type FLW8 = LeftSide FLW9 type FLW7 = LeftSide FLW8 type FLW6 = LeftSide FLW7 type FLW5 = LeftSide FLW6 type FLW4 = LeftSide FLW5 -- | Four letter words (useful for even lengths) flw10 :: Proxy FLW10 flw10 = Proxy flw9 :: Proxy FLW9 flw9 = Proxy flw8 :: Proxy FLW8 flw8 = leftSide flw9 flw7 :: Proxy FLW7 flw7 = leftSide flw8 flw6 :: Proxy FLW6 flw6 = leftSide flw7 flw5 :: Proxy FLW5 flw5 = leftSide flw6 flw4 :: Proxy FLW4 flw4 = leftSide flw5 -- | Four equal length words made to fit 32 bits fourEqualWordsFor32Bits :: Proxy (FLW8 :- FLW8 :- FLW8 :- FLW8) fourEqualWordsFor32Bits = Proxy -- | Seven equal length words for 64 bits sevenEqualWordsFor64Bits :: Proxy (FLW10 :- FLW9 :- FLW9 :- FLW9 :- FLW9 :- FLW9 :- FLW9) sevenEqualWordsFor64Bits = Proxy -- | Eight equal length words made to fit 64 bits eightEqualWordsFor64Bits :: Proxy (FLW8 :- FLW8 :- FLW8 :- FLW8 :- FLW8 :- FLW8 :- FLW8 :- FLW8) eightEqualWordsFor64Bits = Proxy -- Sorted by word length so that when you `leftSide` it, you keep only the -- smaller words. type Words = ToTree '[ "act" , "ads" , "ago" , "air" , "all" , "and" , "any" , "art" , "ash" , "ass" , "bad" , "bag" , "big" , "bit" , "bow" , "box" , "bus" , "but" , "cry" , "dry" , "far" , "fat" , "few" , "fix" , "fly" , "fog" , "for" , "fun" , "gas" , "hey" , "him" , "his" , "hot" , "how" , "ice" , "ill" , "its" , "joy" , "let" , "lit" , "low" , "mad" , "man" , "may" , "mix" , "mud" , "nor" , "not" , "now" , "off" , "old" , "one" , "out" , "per" , "raw" , "red" , "sad" , "say" , "see" , "sex" , "she" , "shy" , "sir" , "six" , "sky" , "spy" , "tax" , "the" , "too" , "try" , "via" , "who" , "why" , "yes" , "yet" , "you" , "able" , "ache" , "acid" , "acne" , "acre" , "acts" , "adds" , "afar" , "ages" , "ahoy" , "aide" , "aids" , "ails" , "aims" , "ajar" , "akin" , "alas" , "ally" , "also" , "amid" , "anew" , "anti" , "apex" , "aqua" , "arch" , "area" , "aria" , "arms" , "army" , "arts" , "asks" , "atom" , "atop" , "aunt" , "aura" , "auto" , "avid" , "avow" , "away" , "awry" , "axis" , "axle" , "babe" , "baby" , "back" , "bade" , "bags" , "bail" , "bait" , "bake" , "bald" , "bale" , "balk" , "ball" , "balm" , "band" , "bane" , "bang" , "bank" , "bans" , "barb" , "bard" , "bare" , "bark" , "barn" , "bars" , "base" , "bash" , "bask" , "bass" , "bath" , "bats" , "bawl" , "bays" , "bead" , "beak" , "beam" , "bean" , "bear" , "beat" , "beds" , "beef" , "been" , "beep" , "beer" , "bees" , "begs" , "bell" , "belt" , "bend" , "bent" , "best" , "beta" , "bets" , "bias" , "bids" , "bike" , "bile" , "bill" , "bind" , "bird" , "bite" , "bled" , "blip" , "blob" , "blog" , "blot" , "blow" , "blue" , "blur" , "boar" , "boat" , "bode" , "body" , "boil" , "bold" , "bolt" , "bomb" , "bond" , "bone" , "bong" , "bonk" , "bony" , "book" , "boom" , "boon" , "boot" , "bore" , "born" , "boss" , "both" , "bout" , "bowl" , "boys" , "brag" , "bran" , "brat" , "bred" , "brew" , "brim" , "buck" , "buff" , "bugs" , "bulb" , "bulk" , "bull" , "bump" , "bunk" , "buoy" , "burn" , "burp" , "bury" , "bush" , "busk" , "bust" , "busy" , "butt" , "buys" , "byte" , "cabs" , "cage" , "cake" , "call" , "calm" , "came" , "camp" , "cane" , "cans" , "cape" , "caps" , "card" , "care" , "cars" , "cart" , "case" , "cash" , "cask" , "cast" , "cats" , "cave" , "cede" , "cell" , "cent" , "chap" , "chat" , "chef" , "chew" , "chin" , "chip" , "chop" , "chug" , "cite" , "city" , "clad" , "clam" , "clan" , "clap" , "claw" , "clay" , "clip" , "clog" , "clop" , "clot" , "club" , "clue" , "coal" , "coat" , "code" , "coil" , "coin" , "cold" , "colt" , "coma" , "comb" , "come" , "cone" , "cook" , "cool" , "cope" , "cops" , "copy" , "cord" , "core" , "cork" , "corn" , "cost" , "cosy" , "coup" , "cove" , "cowl" , "cows" , "cozy" , "crab" , "cram" , "crew" , "crib" , "crop" , "crow" , "crux" , "cube" , "cues" , "cuff" , "cull" , "cult" , "cups" , "curb" , "curd" , "cure" , "curl" , "cusp" , "cuss" , "cute" , "cuts" , "cyan" , "cyst" , "czar" , "dads" , "daft" , "dame" , "damn" , "damp" , "dams" , "dare" , "dark" , "dart" , "dash" , "data" , "date" , "dawn" , "days" , "daze" , "dead" , "deaf" , "deal" , "dean" , "dear" , "debt" , "deck" , "deed" , "deem" , "deep" , "deer" , "deft" , "defy" , "deli" , "dell" , "demo" , "dent" , "deny" , "desk" , "dial" , "dice" , "died" , "dies" , "diet" , "diff" , "digs" , "dill" , "dime" , "dine" , "dips" , "dire" , "dirt" , "disc" , "dish" , "disk" , "dive" , "dock" , "does" , "dogs" , "doll" , "dolt" , "dome" , "done" , "doom" , "door" , "dope" , "dork" , "dorm" , "dose" , "dote" , "dots" , "dove" , "down" , "drab" , "drag" , "draw" , "drew" , "drip" , "drop" , "drug" , "drum" , "dual" , "duck" , "duct" , "dude" , "duel" , "dues" , "duet" , "duke" , "dull" , "duly" , "dumb" , "dump" , "dune" , "dunk" , "dusk" , "dust" , "duty" , "each" , "earl" , "earn" , "ears" , "ease" , "east" , "easy" , "eats" , "eave" , "echo" , "edge" , "edgy" , "edit" , "eels" , "eggs" , "egos" , "else" , "emit" , "ends" , "envy" , "epic" , "eras" , "ergo" , "etch" , "euro" , "even" , "ever" , "eves" , "evil" , "exam" , "exit" , "expo" , "eyes" , "face" , "fact" , "fade" , "fail" , "fair" , "fake" , "fall" , "fame" , "fang" , "fans" , "fare" , "farm" , "fart" , "fast" , "fate" , "faun" , "fawn" , "fear" , "feat" , "feed" , "feel" , "fees" , "feet" , "fell" , "felt" , "fend" , "fern" , "fest" , "feud" , "file" , "fill" , "film" , "find" , "fine" , "fire" , "firm" , "fish" , "fist" , "fits" , "five" , "fizz" , "flag" , "flak" , "flap" , "flat" , "flaw" , "flay" , "flea" , "fled" , "flee" , "flew" , "flex" , "flip" , "flog" , "flow" , "flux" , "foal" , "foam" , "foil" , "fold" , "folk" , "fond" , "font" , "food" , "fool" , "foot" , "ford" , "fore" , "fork" , "form" , "fort" , "foul" , "four" , "fowl" , "foxy" , "frag" , "fray" , "free" , "fret" , "frog" , "from" , "fuel" , "full" , "fume" , "fund" , "furs" , "fury" , "fuse" , "fuss" , "gain" , "gait" , "gala" , "game" , "gang" , "gape" , "gaps" , "garb" , "gash" , "gasp" , "gate" , "gave" , "gawk" , "gaze" , "gear" , "geek" , "gems" , "gene" , "germ" , "gets" , "ghee" , "gift" , "girl" , "gist" , "give" , "glad" , "glam" , "glee" , "glen" , "glib" , "glow" , "glue" , "glum" , "gnat" , "gnaw" , "goal" , "goat" , "goes" , "gold" , "golf" , "gone" , "gong" , "good" , "goof" , "gore" , "gory" , "gosh" , "goth" , "gout" , "gown" , "grab" , "gram" , "gray" , "grew" , "grid" , "grim" , "grin" , "grip" , "grit" , "grow" , "grub" , "gulf" , "gull" , "gulp" , "gunk" , "guns" , "guru" , "gush" , "gust" , "guts" , "guys" , "gyms" , "hack" , "hail" , "hair" , "half" , "hall" , "halo" , "halt" , "hand" , "hang" , "hard" , "hare" , "harm" , "harp" , "hash" , "hate" , "hats" , "haul" , "have" , "hawk" , "hays" , "haze" , "hazy" , "head" , "heal" , "heap" , "hear" , "heat" , "heed" , "heel" , "heft" , "heir" , "held" , "hell" , "helm" , "help" , "hemp" , "herb" , "herd" , "here" , "hero" , "hers" , "hide" , "high" , "hike" , "hill" , "hilt" , "hind" , "hint" , "hips" , "hire" , "hiss" , "hits" , "hive" , "hoax" , "hold" , "hole" , "holy" , "home" , "hone" , "honk" , "hood" , "hoof" , "hook" , "hoop" , "hoot" , "hope" , "horn" , "hose" , "host" , "hour" , "howl" , "huge" , "hugs" , "hulk" , "hull" , "hump" , "hung" , "hunt" , "hurl" , "hurt" , "hush" , "husk" , "hymn" , "hype" , "icon" , "idea" , "idle" , "idol" , "inch" , "info" , "into" , "iris" , "iron" , "isle" , "itch" , "item" , "jack" , "jade" , "jail" , "jars" , "java" , "jaws" , "jazz" , "jean" , "jeer" , "jest" , "jets" , "jinx" , "jobs" , "john" , "join" , "joke" , "jolt" , "jump" , "junk" , "jury" , "just" , "keen" , "keep" , "kelp" , "kept" , "keys" , "kick" , "kids" , "kill" , "kiln" , "kilt" , "kind" , "king" , "kink" , "kiss" , "kite" , "kits" , "knee" , "knew" , "knit" , "knob" , "knot" , "know" , "labs" , "lace" , "lack" , "lady" , "laid" , "lair" , "lake" , "lamb" , "lame" , "lamp" , "land" , "lane" , "laps" , "lard" , "lash" , "last" , "late" , "lava" , "lawn" , "laws" , "lays" , "laze" , "lazy" , "lead" , "leaf" , "leak" , "lean" , "leap" , "leek" , "leer" , "left" , "legs" , "lend" , "lens" , "less" , "lest" , "levy" , "lewd" , "liar" , "lice" , "lick" , "lids" , "lies" , "life" , "lift" , "like" , "limb" , "lime" , "limp" , "line" , "link" , "lint" , "lion" , "lips" , "lisp" , "list" , "live" , "load" , "loaf" , "loan" , "lobe" , "lock" , "loft" , "logo" , "logs" , "lone" , "long" , "look" , "loom" , "loop" , "loot" , "lord" , "lore" , "lose" , "loss" , "lost" , "lots" , "loud" , "love" , "luck" , "lull" , "lump" , "lung" , "lure" , "lurk" , "lush" , "lust" , "lute" , "mace" , "made" , "maid" , "mail" , "maim" , "main" , "make" , "male" , "mall" , "malt" , "many" , "maps" , "mare" , "mark" , "mash" , "mask" , "mass" , "mast" , "mate" , "math" , "matt" , "maul" , "maze" , "mead" , "meal" , "mean" , "meat" , "meek" , "meet" , "meld" , "melt" , "meme" , "memo" , "mend" , "menu" , "meow" , "mere" , "mesh" , "mess" , "mice" , "mike" , "mild" , "mile" , "milk" , "mill" , "mime" , "mind" , "mine" , "mini" , "mint" , "miss" , "mist" , "mite" , "moan" , "moat" , "mock" , "mode" , "mold" , "mole" , "molt" , "monk" , "mood" , "moon" , "mope" , "more" , "moss" , "most" , "moth" , "move" , "much" , "mule" , "mull" , "muse" , "mush" , "musk" , "must" , "mute" , "mutt" , "myth" , "nail" , "name" , "navy" , "near" , "neat" , "neck" , "need" , "neon" , "nerd" , "nest" , "nets" , "news" , "newt" , "next" , "nice" , "nick" , "nine" , "node" , "nods" , "none" , "nook" , "noon" , "nope" , "norm" , "nose" , "note" , "noun" , "nude" , "nuke" , "null" , "numb" , "nuts" , "oaks" , "oath" , "obey" , "oboe" , "odds" , "odor" , "oils" , "okay" , "omen" , "omit" , "once" , "ones" , "only" , "onto" , "onus" , "ooze" , "opal" , "open" , "opts" , "oral" , "ouch" , "ours" , "oust" , "oval" , "oven" , "over" , "owes" , "owns" , "pace" , "pack" , "pact" , "pads" , "page" , "paid" , "pail" , "pain" , "pair" , "pale" , "pall" , "palm" , "pane" , "pans" , "pant" , "park" , "part" , "pass" , "past" , "path" , "pats" , "pave" , "pawn" , "pays" , "peak" , "pear" , "peas" , "peck" , "peek" , "peel" , "peep" , "peer" , "pelt" , "pens" , "peon" , "perk" , "pest" , "pets" , "pick" , "pics" , "pier" , "pies" , "pigs" , "pike" , "pile" , "pill" , "pine" , "pink" , "pins" , "pint" , "pipe" , "pits" , "pity" , "plan" , "play" , "plea" , "plot" , "plow" , "ploy" , "plug" , "plum" , "plus" , "poem" , "poet" , "poke" , "pole" , "poll" , "pomp" , "pond" , "pony" , "pool" , "poor" , "pops" , "pore" , "pork" , "port" , "pose" , "posh" , "post" , "posy" , "pots" , "pour" , "pout" , "pray" , "prev" , "prey" , "prod" , "prop" , "puck" , "puff" , "pull" , "pulp" , "pump" , "punk" , "punt" , "puny" , "pure" , "push" , "puts" , "pyre" , "quay" , "quip" , "quit" , "quiz" , "race" , "rack" , "raft" , "rage" , "raid" , "rail" , "rain" , "rake" , "ramp" , "rang" , "rank" , "rant" , "rape" , "rare" , "rash" , "rate" , "rats" , "rave" , "raze" , "read" , "real" , "reap" , "rear" , "redo" , "reed" , "reef" , "reek" , "reel" , "rely" , "rent" , "rest" , "ribs" , "rice" , "rich" , "ride" , "rids" , "riff" , "rift" , "rims" , "rind" , "ring" , "rink" , "riot" , "ripe" , "rips" , "rise" , "risk" , "road" , "roam" , "roar" , "robe" , "rock" , "rods" , "role" , "roll" , "romp" , "roof" , "rook" , "room" , "root" , "rope" , "rose" , "rows" , "rubs" , "ruby" , "rude" , "ruin" , "rule" , "rump" , "rune" , "rung" , "runs" , "runt" , "ruse" , "rush" , "rusk" , "rust" , "ruts" , "sack" , "safe" , "saga" , "sage" , "said" , "sail" , "sake" , "sale" , "salt" , "same" , "sand" , "sane" , "sang" , "sank" , "sash" , "save" , "says" , "scab" , "scam" , "scan" , "scar" , "scum" , "seal" , "seam" , "sear" , "seas" , "seat" , "seed" , "seek" , "seem" , "seen" , "seep" , "seer" , "self" , "sell" , "semi" , "send" , "sent" , "serf" , "sets" , "sewn" , "sexy" , "shed" , "shim" , "shin" , "ship" , "shit" , "shod" , "shoe" , "shop" , "shot" , "show" , "shun" , "shut" , "sick" , "side" , "sift" , "sigh" , "sign" , "silk" , "sill" , "silo" , "silt" , "sing" , "sink" , "sins" , "sire" , "site" , "sits" , "size" , "skew" , "skid" , "skim" , "skin" , "skip" , "skis" , "skit" , "slab" , "slam" , "slap" , "slat" , "slay" , "sled" , "slew" , "slid" , "slim" , "slip" , "slit" , "slob" , "slot" , "slow" , "slug" , "slum" , "slur" , "smog" , "smug" , "snag" , "snap" , "snip" , "snob" , "snot" , "snow" , "snub" , "snug" , "soak" , "soap" , "soar" , "sock" , "soda" , "sofa" , "soft" , "soil" , "sold" , "sole" , "solo" , "some" , "song" , "sons" , "soon" , "soot" , "sore" , "sort" , "soul" , "soup" , "sour" , "sown" , "sows" , "spam" , "span" , "spar" , "spat" , "spay" , "sped" , "spew" , "spin" , "spit" , "spot" , "spry" , "spun" , "spur" , "stab" , "stag" , "star" , "stay" , "stem" , "step" , "stew" , "stir" , "stop" , "stow" , "stub" , "stun" , "such" , "suck" , "sues" , "suit" , "sulk" , "sums" , "sung" , "sunk" , "suns" , "sure" , "surf" , "suss" , "swab" , "swag" , "swam" , "swan" , "swap" , "swat" , "sway" , "swig" , "swim" , "swum" , "sync" , "tack" , "tact" , "tags" , "tail" , "take" , "tale" , "talk" , "tall" , "tame" , "tank" , "tape" , "taps" , "tart" , "task" , "taut" , "taxi" , "teal" , "team" , "tear" , "teas" , "tech" , "teen" , "tell" , "tend" , "tens" , "tent" , "term" , "test" , "text" , "than" , "that" , "thaw" , "them" , "then" , "they" , "thin" , "this" , "thud" , "thug" , "thus" , "tick" , "tide" , "tidy" , "tied" , "tier" , "ties" , "tile" , "till" , "tilt" , "time" , "tint" , "tiny" , "tips" , "tire" , "toad" , "toes" , "toil" , "told" , "toll" , "tomb" , "tone" , "tony" , "took" , "tool" , "toot" , "tops" , "tore" , "torn" , "toss" , "tour" , "town" , "toys" , "tram" , "trap" , "tray" , "tree" , "trim" , "trip" , "trod" , "trot" , "true" , "tuba" , "tube" , "tuck" , "tuft" , "tuna" , "tune" , "turf" , "turn" , "tusk" , "twig" , "twin" , "twos" , "type" , "tyre" , "ugly" , "undo" , "unit" , "unto" , "upon" , "urge" , "used" , "user" , "uses" , "vain" , "vale" , "vans" , "vary" , "vase" , "vast" , "veal" , "veer" , "veil" , "vein" , "vend" , "vent" , "verb" , "very" , "vest" , "vial" , "vibe" , "vice" , "view" , "vile" , "vine" , "visa" , "void" , "volt" , "vote" , "wade" , "waft" , "wage" , "wail" , "wait" , "wake" , "walk" , "wall" , "wand" , "wane" , "want" , "ward" , "ware" , "warm" , "warn" , "warp" , "wars" , "wart" , "wary" , "wash" , "wasp" , "wave" , "ways" , "weak" , "wean" , "wear" , "webs" , "weed" , "week" , "weep" , "weld" , "well" , "welt" , "went" , "wept" , "were" , "west" , "wets" , "what" , "when" , "whet" , "whey" , "whim" , "whip" , "whom" , "wick" , "wide" , "wife" , "wild" , "will" , "wilt" , "wimp" , "wind" , "wine" , "wing" , "wink" , "wins" , "wipe" , "wire" , "wiry" , "wise" , "wish" , "with" , "wits" , "woke" , "wolf" , "womb" , "wood" , "wool" , "word" , "wore" , "work" , "worm" , "worn" , "wrap" , "wren" , "wuss" , "yank" , "yard" , "yarn" , "yawn" , "yeah" , "year" , "yell" , "yelp" , "yeti" , "yoga" , "yolk" , "york" , "your" , "yowl" , "zeal" , "zero" , "zest" , "zone" , "zoom" , "about" , "above" , "abuse" , "actor" , "adapt" , "added" , "admit" , "adopt" , "adult" , "after" , "again" , "agent" , "agree" , "ahead" , "aisle" , "alarm" , "album" , "alien" , "alike" , "alive" , "alley" , "allow" , "alone" , "along" , "alter" , "amaze" , "among" , "angel" , "anger" , "angle" , "angry" , "ankle" , "apart" , "apple" , "apply" , "arena" , "argue" , "arise" , "armed" , "array" , "arrow" , "aside" , "asset" , "avoid" , "await" , "awake" , "award" , "aware" , "awful" , "badly" , "basic" , "basis" , "beach" , "beard" , "beast" , "begin" , "being" , "belly" , "below" , "bench" , "birth" , "black" , "blade" , "blame" , "blank" , "blast" , "blend" , "bless" , "blind" , "blink" , "block" , "blond" , "blood" , "board" , "boast" , "bonus" , "boost" , "booth" , "brain" , "brake" , "brand" , "brave" , "bread" , "break" , "brick" , "bride" , "brief" , "bring" , "broad" , "brown" , "brush" , "buddy" , "build" , "bunch" , "burst" , "buyer" , "cabin" , "cable" , "candy" , "cargo" , "carry" , "carve" , "catch" , "cause" , "cease" , "chain" , "chair" , "chaos" , "charm" , "chart" , "chase" , "cheap" , "cheat" , "check" , "cheek" , "cheer" , "chest" , "chief" , "child" , "chill" , "chunk" , "civic" , "civil" , "claim" , "class" , "clean" , "clear" , "clerk" , "click" , "cliff" , "climb" , "cling" , "clock" , "close" , "cloth" , "cloud" , "coach" , "coast" , "color" , "couch" , "could" , "count" , "court" , "cover" , "crack" , "craft" , "crash" , "crawl" , "crazy" , "cream" , "crest" , "crime" , "cross" , "crowd" , "cruel" , "crush" , "curve" , "cycle" , "daily" , "dance" , "death" , "debut" , "delay" , "dense" , "depth" , "devil" , "diary" , "dirty" , "donor" , "doubt" , "dough" , "dozen" , "draft" , "drain" , "drama" , "dream" , "dress" , "dried" , "drift" , "drill" , "drink" , "drive" , "drown" , "drunk" , "dying" , "eager" , "early" , "earth" , "eight" , "elbow" , "elder" , "elect" , "elite" , "empty" , "enact" , "enemy" , "enjoy" , "enter" , "entry" , "equal" , "equip" , "error" , "essay" , "event" , "every" , "exact" , "exist" , "extra" , "faint" , "faith" , "false" , "fatal" , "fault" , "favor" , "fence" , "fever" , "fewer" , "fiber" , "field" , "fifth" , "fifty" , "fight" , "final" , "first" , "fixed" , "flame" , "flash" , "fleet" , "flesh" , "float" , "flood" , "floor" , "flour" , "fluid" , "focus" , "force" , "forth" , "forty" , "forum" , "found" , "frame" , "fraud" , "fresh" , "front" , "frown" , "fruit" , "fully" , "funny" , "genre" , "ghost" , "giant" , "given" , "glass" , "globe" , "glory" , "glove" , "grace" , "grade" , "grain" , "grand" , "grant" , "grape" , "grasp" , "grass" , "grave" , "great" , "green" , "greet" , "grief" , "gross" , "group" , "guard" , "guess" , "guest" , "guide" , "guilt" , "habit" , "happy" , "harsh" , "heart" , "heavy" , "hello" , "hence" , "honey" , "honor" , "horse" , "hotel" , "house" , "human" , "humor" , "hurry" , "ideal" , "image" , "imply" , "index" , "inner" , "input" , "irony" , "issue" , "jeans" , "jewel" , "joint" , "judge" , "juice" , "juror" , "kneel" , "knife" , "knock" , "known" , "label" , "labor" , "large" , "laser" , "later" , "laugh" , "layer" , "learn" , "least" , "leave" , "legal" , "lemon" , "level" , "light" , "limit" , "liver" , "lobby" , "local" , "logic" , "loose" , "lover" , "lower" , "loyal" , "lucky" , "lunch" , "magic" , "major" , "maker" , "march" , "marry" , "match" , "maybe" , "mayor" , "medal" , "media" , "merit" , "metal" , "meter" , "midst" , "might" , "minor" , "mixed" , "model" , "money" , "month" , "moral" , "motor" , "mount" , "mouse" , "mouth" , "movie" , "music" , "naked" , "nasty" , "naval" , "nerve" , "never" , "newly" , "night" , "noise" , "north" , "novel" , "nurse" , "occur" , "ocean" , "offer" , "often" , "onion" , "opera" , "orbit" , "order" , "organ" , "other" , "ought" , "outer" , "owner" , "paint" , "panel" , "panic" , "paper" , "party" , "pasta" , "patch" , "pause" , "peace" , "pearl" , "phase" , "phone" , "photo" , "piano" , "piece" , "pilot" , "pitch" , "pizza" , "place" , "plain" , "plane" , "plant" , "plate" , "plead" , "point" , "porch" , "pound" , "power" , "press" , "price" , "pride" , "prime" , "print" , "prior" , "prize" , "proof" , "proud" , "prove" , "pulse" , "punch" , "purse" , "queen" , "quest" , "quick" , "quiet" , "quite" , "quote" , "radar" , "radio" , "raise" , "rally" , "ranch" , "range" , "rapid" , "ratio" , "reach" , "react" , "ready" , "realm" , "rebel" , "refer" , "relax" , "reply" , "rhyme" , "rider" , "ridge" , "rifle" , "right" , "risky" , "rival" , "river" , "robot" , "rough" , "round" , "route" , "royal" , "rumor" , "rural" , "salad" , "sales" , "sauce" , "scale" , "scare" , "scary" , "scene" , "scent" , "scope" , "score" , "screw" , "seize" , "sense" , "serve" , "seven" , "shade" , "shake" , "shall" , "shame" , "shape" , "share" , "shark" , "sharp" , "sheep" , "sheer" , "sheet" , "shelf" , "shell" , "shift" , "shine" , "shirt" , "shock" , "shoot" , "shore" , "short" , "shout" , "shove" , "shrug" , "sight" , "silly" , "since" , "sixth" , "skill" , "skirt" , "skull" , "slave" , "sleep" , "slice" , "slide" , "slope" , "small" , "smart" , "smell" , "smile" , "smoke" , "snake" , "sneak" , "solar" , "solid" , "solve" , "sorry" , "sound" , "south" , "space" , "spare" , "spark" , "speak" , "speed" , "spell" , "spend" , "spill" , "spine" , "spite" , "split" , "spoon" , "sport" , "spray" , "squad" , "stack" , "staff" , "stage" , "stair" , "stake" , "stand" , "stare" , "start" , "state" , "steak" , "steal" , "steam" , "steel" , "steep" , "steer" , "stick" , "stiff" , "still" , "stock" , "stone" , "stoop" , "store" , "storm" , "story" , "stove" , "straw" , "strip" , "study" , "stuff" , "style" , "sugar" , "suite" , "sunny" , "super" , "swear" , "sweat" , "sweep" , "sweet" , "swell" , "swing" , "sword" , "table" , "taste" , "teach" , "terms" , "thank" , "their" , "theme" , "there" , "these" , "thick" , "thigh" , "thing" , "think" , "third" , "those" , "three" , "throw" , "thumb" , "tight" , "tired" , "title" , "today" , "tooth" , "topic" , "total" , "touch" , "tough" , "towel" , "tower" , "toxic" , "trace" , "track" , "trade" , "trail" , "train" , "trait" , "trash" , "treat" , "trend" , "trial" , "tribe" , "trick" , "troop" , "truck" , "truly" , "trunk" , "trust" , "truth" , "tumor" , "twice" , "twist" , "uncle" , "under" , "union" , "unite" , "unity" , "until" , "upper" , "upset" , "urban" , "usual" , "valid" , "value" , "video" , "virus" , "visit" , "vital" , "vocal" , "voice" , "voter" , "wagon" , "waist" , "waste" , "watch" , "water" , "weave" , "weigh" , "weird" , "whale" , "wheat" , "wheel" , "where" , "which" , "while" , "white" , "whole" , "whose" , "widow" , "woman" , "works" , "world" , "worry" , "worth" , "would" , "wound" , "wrist" , "write" , "wrong" , "yield" , "young" , "yours" , "youth" , "abroad" , "absorb" , "accent" , "accept" , "access" , "accuse" , "across" , "action" , "active" , "actual" , "adjust" , "admire" , "advice" , "advise" , "affair" , "affect" , "afford" , "afraid" , "agency" , "agenda" , "almost" , "always" , "amount" , "animal" , "annual" , "answer" , "anyone" , "anyway" , "appeal" , "appear" , "around" , "arrest" , "arrive" , "artist" , "asleep" , "aspect" , "assert" , "assess" , "assign" , "assist" , "assume" , "assure" , "attach" , "attack" , "attend" , "author" , "ballot" , "banana" , "banker" , "barely" , "barrel" , "basket" , "battle" , "beauty" , "become" , "before" , "behalf" , "behave" , "behind" , "belief" , "belong" , "beside" , "better" , "beyond" , "bishop" , "bitter" , "bloody" , "border" , "boring" , "borrow" , "bother" , "bottle" , "bottom" , "bounce" , "branch" , "breast" , "breath" , "breeze" , "bridge" , "bright" , "broken" , "broker" , "bronze" , "brutal" , "bubble" , "bucket" , "budget" , "bullet" , "burden" , "bureau" , "butter" , "button" , "camera" , "campus" , "cancel" , "cancer" , "candle" , "canvas" , "carbon" , "career" , "carpet" , "carrot" , "casino" , "casual" , "cattle" , "center" , "chance" , "change" , "charge" , "cheese" , "choice" , "choose" , "church" , "circle" , "client" , "clinic" , "closed" , "closer" , "closet" , "coffee" , "collar" , "colony" , "column" , "combat" , "comedy" , "coming" , "commit" , "common" , "compel" , "comply" , "convey" , "cookie" , "corner" , "costly" , "cotton" , "county" , "couple" , "course" , "cousin" , "create" , "credit" , "crisis" , "critic" , "cruise" , "custom" , "damage" , "dancer" , "danger" , "deadly" , "dealer" , "debate" , "debris" , "decade" , "decent" , "decide" , "deeply" , "defeat" , "defend" , "define" , "degree" , "demand" , "denial" , "depart" , "depend" , "depict" , "deploy" , "deputy" , "derive" , "desert" , "design" , "desire" , "detail" , "detect" , "device" , "devote" , "differ" , "dining" , "dinner" , "direct" , "divide" , "divine" , "doctor" , "domain" , "donate" , "double" , "drawer" , "driver" , "during" , "easily" , "eating" , "editor" , "effect" , "effort" , "eighth" , "either" , "emerge" , "empire" , "employ" , "enable" , "endure" , "energy" , "engage" , "engine" , "enough" , "enroll" , "ensure" , "entire" , "entity" , "equity" , "escape" , "estate" , "ethics" , "ethnic" , "evolve" , "exceed" , "except" , "excuse" , "exotic" , "expand" , "expect" , "expert" , "export" , "expose" , "extend" , "extent" , "fabric" , "factor" , "fairly" , "family" , "famous" , "farmer" , "faster" , "father" , "fellow" , "female" , "fierce" , "figure" , "filter" , "finger" , "finish" , "firmly" , "fiscal" , "flavor" , "flight" , "flower" , "flying" , "follow" , "forbid" , "forest" , "forget" , "formal" , "format" , "former" , "foster" , "fourth" , "freely" , "freeze" , "friend" , "frozen" , "future" , "galaxy" , "garage" , "garden" , "garlic" , "gather" , "gender" , "genius" , "gentle" , "gently" , "gifted" , "glance" , "global" , "golden" , "govern" , "ground" , "growth" , "guilty" , "guitar" , "handle" , "happen" , "hardly" , "hazard" , "health" , "heaven" , "height" , "helmet" , "hidden" , "highly" , "hockey" , "honest" , "horror" , "hunger" , "hungry" , "hunter" , "ignore" , "immune" , "impact" , "import" , "impose" , "income" , "indeed" , "infant" , "inform" , "injure" , "injury" , "inmate" , "insect" , "insert" , "inside" , "insist" , "intact" , "intend" , "intent" , "invade" , "invent" , "invest" , "invite" , "island" , "itself" , "jacket" , "jungle" , "junior" , "killer" , "ladder" , "lately" , "latter" , "launch" , "lawyer" , "leader" , "league" , "legacy" , "legend" , "length" , "lesson" , "letter" , "likely" , "liquid" , "listen" , "little" , "living" , "locate" , "lonely" , "lovely" , "mainly" , "makeup" , "manage" , "manner" , "manual" , "marble" , "margin" , "marine" , "marker" , "market" , "master" , "matter" , "medium" , "member" , "memory" , "mental" , "mentor" , "merely" , "method" , "middle" , "minute" , "mirror" , "mobile" , "modern" , "modest" , "modify" , "moment" , "monkey" , "mostly" , "mother" , "motion" , "motive" , "murder" , "muscle" , "museum" , "mutter" , "mutual" , "myself" , "narrow" , "nation" , "native" , "nature" , "nearby" , "nearly" , "needle" , "nobody" , "normal" , "notice" , "notion" , "number" , "object" , "obtain" , "occupy" , "office" , "online" , "openly" , "oppose" , "option" , "orange" , "origin" , "others" , "outfit" , "outlet" , "output" , "oxygen" , "palace" , "parade" , "parent" , "parish" , "partly" , "pastor" , "patent" , "patrol" , "patron" , "peanut" , "pencil" , "people" , "pepper" , "period" , "permit" , "person" , "phrase" , "pickup" , "pillow" , "pistol" , "planet" , "player" , "please" , "plenty" , "plunge" , "pocket" , "poetry" , "police" , "policy" , "poster" , "potato" , "powder" , "praise" , "prayer" , "preach" , "prefer" , "pretty" , "priest" , "prison" , "profit" , "prompt" , "proper" , "public" , "punish" , "purple" , "pursue" , "puzzle" , "rabbit" , "racial" , "racism" , "random" , "rarely" , "rather" , "rating" , "reader" , "really" , "reason" , "recall" , "recent" , "recipe" , "record" , "reduce" , "reform" , "refuge" , "refuse" , "regain" , "regard" , "regime" , "region" , "regret" , "reject" , "relate" , "relief" , "remain" , "remark" , "remind" , "remote" , "remove" , "render" , "rental" , "repair" , "repeat" , "report" , "rescue" , "resign" , "resist" , "resort" , "result" , "resume" , "retail" , "retain" , "retire" , "return" , "reveal" , "review" , "reward" , "rhythm" , "ribbon" , "ritual" , "rocket" , "rubber" , "ruling" , "runner" , "sacred" , "safely" , "safety" , "salary" , "salmon" , "sample" , "saving" , "scared" , "scheme" , "school" , "scream" , "screen" , "script" , "search" , "season" , "second" , "secret" , "sector" , "secure" , "seldom" , "select" , "seller" , "senior" , "sensor" , "series" , "settle" , "severe" , "sexual" , "shadow" , "shared" , "shorts" , "should" , "shower" , "shrimp" , "shrink" , "signal" , "silent" , "silver" , "simple" , "simply" , "singer" , "single" , "sister" , "sleeve" , "slight" , "slowly" , "smooth" , "soccer" , "social" , "sodium" , "soften" , "softly" , "solely" , "source" , "speech" , "sphere" , "spirit" , "spouse" , "spread" , "spring" , "square" , "stable" , "stance" , "statue" , "status" , "steady" , "strain" , "streak" , "stream" , "street" , "stress" , "strict" , "strike" , "string" , "stroke" , "strong" , "studio" , "stupid" , "submit" , "subtle" , "suburb" , "sudden" , "suffer" , "summer" , "summit" , "supply" , "surely" , "survey" , "switch" , "symbol" , "system" , "tackle" , "tactic" , "talent" , "target" , "temple" , "tender" , "tennis" , "terror" , "thanks" , "theory" , "thirty" , "though" , "thread" , "threat" , "thrive" , "throat" , "ticket" , "timber" , "timing" , "tissue" , "toilet" , "tomato" , "tongue" , "toward" , "tragic" , "trauma" , "travel" , "treaty" , "tribal" , "tunnel" , "turkey" , "twelve" , "twenty" , "unable" , "unfair" , "unfold" , "unique" , "unless" , "unlike" , "update" , "useful" , "vacuum" , "valley" , "vanish" , "vendor" , "verbal" , "versus" , "vessel" , "victim" , "viewer" , "virtue" , "vision" , "visual" , "volume" , "voting" , "wander" , "warmth" , "weaken" , "wealth" , "weapon" , "weekly" , "weight" , "widely" , "window" , "winner" , "winter" , "wisdom" , "within" , "wonder" , "wooden" , "worker" , "writer" , "yellow" , "abandon" , "ability" , "absence" , "account" , "achieve" , "acquire" , "actress" , "address" , "advance" , "adviser" , "against" , "airline" , "airport" , "alcohol" , "alleged" , "already" , "analyst" , "analyze" , "ancient" , "another" , "anxiety" , "anxious" , "anybody" , "anymore" , "apology" , "appoint" , "approve" , "arrange" , "arrival" , "article" , "assault" , "athlete" , "attempt" , "attract" , "auction" , "average" , "balance" , "balloon" , "banking" , "barrier" , "battery" , "because" , "bedroom" , "believe" , "beneath" , "benefit" , "besides" , "between" , "bicycle" , "billion" , "biology" , "blanket" , "bombing" , "breathe" , "briefly" , "brother" , "builder" , "burning" , "cabinet" , "capable" , "capital" , "captain" , "capture" , "careful" , "carrier" , "cartoon" , "catalog" , "ceiling" , "central" , "century" , "certain" , "chamber" , "channel" , "chapter" , "charity" , "charter" , "chicken" , "chronic" , "circuit" , "citizen" , "classic" , "clearly" , "climate" , "closely" , "closest" , "clothes" , "cluster" , "coastal" , "cocaine" , "collect" , "college" , "combine" , "comfort" , "command" , "comment" , "company" , "compare" , "compete" , "complex" , "compose" , "concede" , "concept" , "concern" , "concert" , "condemn" , "conduct" , "confess" , "confirm" , "confuse" , "connect" , "consent" , "consist" , "consult" , "consume" , "contact" , "contain" , "contend" , "content" , "contest" , "context" , "control" , "convert" , "convict" , "cooking" , "correct" , "costume" , "cottage" , "council" , "counsel" , "counter" , "country" , "courage" , "crowded" , "crucial" , "crystal" , "culture" , "curious" , "current" , "curtain" , "custody" , "dancing" , "declare" , "decline" , "defense" , "deficit" , "delight" , "deliver" , "density" , "deposit" , "descend" , "deserve" , "despite" , "dessert" , "destroy" , "develop" , "diamond" , "dictate" , "digital" , "dignity" , "dilemma" , "discuss" , "disease" , "dismiss" , "display" , "dispute" , "distant" , "disturb" , "diverse" , "divorce" , "doorway" , "drawing" , "driving" , "dynamic" , "eastern" , "economy" , "edition" , "educate" , "elderly" , "elegant" , "element" , "embrace" , "emotion" , "endless" , "endorse" , "enforce" , "enhance" , "entitle" , "episode" , "equally" , "essence" , "ethical" , "evening" , "evident" , "exactly" , "examine" , "example" , "excited" , "exclude" , "execute" , "exhaust" , "exhibit" , "expense" , "explain" , "explode" , "exploit" , "explore" , "express" , "extreme" , "eyebrow" , "factory" , "faculty" , "failure" , "fantasy" , "fashion" , "fatigue" , "feather" , "feature" , "federal" , "feeling" , "fiction" , "fifteen" , "fighter" , "finally" , "finance" , "finding" , "fishing" , "fitness" , "foreign" , "forever" , "forgive" , "formula" , "fortune" , "forward" , "founder" , "fragile" , "frankly" , "freedom" , "fuchsia" , "fucking" , "funding" , "funeral" , "gallery" , "garbage" , "general" , "genetic" , "genuine" , "gesture" , "glimpse" , "gravity" , "greatly" , "grimace" , "grocery" , "growing" , "habitat" , "halfway" , "hallway" , "handful" , "happily" , "harmony" , "harvest" , "healthy" , "hearing" , "heavily" , "helpful" , "herself" , "highway" , "himself" , "history" , "holiday" , "horizon" , "hormone" , "hostage" , "hostile" , "housing" , "however" , "hundred" , "hunting" , "husband" , "illegal" , "illness" , "imagine" , "impress" , "improve" , "impulse" , "include" , "inherit" , "initial" , "inquiry" , "insight" , "inspire" , "install" , "instant" , "instead" , "intense" , "involve" , "isolate" , "jewelry" , "journal" , "journey" , "justice" , "justify" , "killing" , "kingdom" , "kitchen" , "landing" , "largely" , "laundry" , "lawsuit" , "leading" , "leather" , "lecture" , "legally" , "liberal" , "liberty" , "library" , "license" , "lightly" , "limited" , "logical" , "loyalty" , "machine" , "manager" , "mandate" , "mansion" , "married" , "massive" , "maximum" , "meaning" , "measure" , "medical" , "meeting" , "mention" , "message" , "million" , "mineral" , "minimal" , "minimum" , "miracle" , "missile" , "missing" , "mission" , "mistake" , "mixture" , "monitor" , "monster" , "monthly" , "morning" , "musical" , "mystery" , "natural" , "neither" , "nervous" , "network" , "neutral" , "nominee" , "nothing" , "nowhere" , "nuclear" , "observe" , "obvious" , "offense" , "officer" , "ongoing" , "opening" , "operate" , "opinion" , "opposed" , "organic" , "outcome" , "outdoor" , "outline" , "outside" , "overall" , "oversee" , "package" , "painful" , "painter" , "parking" , "partial" , "partner" , "passage" , "passing" , "passion" , "patient" , "pattern" , "payment" , "peasant" , "penalty" , "pension" , "perfect" , "perform" , "perhaps" , "persist" , "physics" , "picture" , "pioneer" , "pitcher" , "planner" , "plastic" , "playoff" , "pleased" , "popular" , "portion" , "portray" , "possess" , "poverty" , "precise" , "predict" , "premise" , "premium" , "prepare" , "present" , "pretend" , "prevail" , "prevent" , "primary" , "privacy" , "private" , "problem" , "proceed" , "process" , "produce" , "product" , "profile" , "program" , "project" , "promise" , "promote" , "propose" , "protect" , "protein" , "protest" , "provide" , "provoke" , "publish" , "purpose" , "pursuit" , "qualify" , "quality" , "quarter" , "quickly" , "quietly" , "radical" , "rapidly" , "readily" , "reading" , "reality" , "realize" , "rebuild" , "receive" , "recover" , "recruit" , "reflect" , "refugee" , "regular" , "related" , "release" , "relieve" , "removal" , "replace" , "request" , "require" , "reserve" , "resolve" , "respect" , "respond" , "restore" , "retired" , "retreat" , "revenue" , "reverse" , "rolling" , "romance" , "roughly" , "routine" , "running" , "satisfy" , "scandal" , "scatter" , "scholar" , "science" , "scratch" , "section" , "secular" , "segment" , "seminar" , "senator" , "serious" , "servant" , "service" , "serving" , "session" , "setting" , "seventh" , "several" , "shallow" , "sharply" , "shelter" , "shortly" , "shuttle" , "sibling" , "silence" , "similar" , "skilled" , "slavery" , "society" , "soldier" , "someday" , "somehow" , "someone" , "speaker" , "special" , "species" , "specify" , "sponsor" , "squeeze" , "stadium" , "starter" , "station" , "statute" , "stomach" , "storage" , "strange" , "stretch" , "student" , "stumble" , "subject" , "subsidy" , "succeed" , "success" , "suggest" , "suicide" , "summary" , "support" , "suppose" , "surface" , "surgeon" , "surgery" , "survive" , "suspect" , "suspend" , "sustain" , "swallow" , "sweater" , "symptom" , "teacher" , "teenage" , "tension" , "terrain" , "testify" , "testing" , "texture" , "theater" , "therapy" , "thereby" , "thought" , "through" , "tighten" , "tightly" , "tobacco" , "tonight" , "totally" , "tourism" , "tourist" , "towards" , "trading" , "traffic" , "tragedy" , "trailer" , "trainer" , "transit" , "trigger" , "triumph" , "trouble" , "typical" , "uncover" , "undergo" , "unhappy" , "uniform" , "unknown" , "unusual" , "usually" , "utility" , "utilize" , "vaccine" , "variety" , "various" , "vehicle" , "venture" , "verdict" , "version" , "veteran" , "victory" , "village" , "violate" , "violent" , "virtual" , "visible" , "visitor" , "vitamin" , "walking" , "warning" , "warrior" , "wealthy" , "weather" , "wedding" , "weekend" , "welcome" , "welfare" , "western" , "whereas" , "whether" , "whisper" , "whoever" , "willing" , "without" , "witness" , "working" , "workout" , "worried" , "writing" , "written" , "abortion" , "absolute" , "abstract" , "academic" , "accident" , "accuracy" , "accurate" , "actively" , "activist" , "activity" , "actually" , "addition" , "adequate" , "adoption" , "advanced" , "advocate" , "aircraft" , "airplane" , "alliance" , "although" , "aluminum" , "ambition" , "analysis" , "ancestor" , "announce" , "annually" , "anything" , "anywhere" , "apparent" , "approach" , "approval" , "argument" , "artifact" , "artistic" , "assemble" , "assembly" , "athletic" , "attitude" , "attorney" , "audience" , "autonomy" , "backyard" , "bacteria" , "balanced" , "baseball" , "basement" , "bathroom" , "behavior" , "birthday" , "blessing" , "boundary" , "building" , "business" , "calendar" , "campaign" , "capacity" , "casualty" , "category" , "cemetery" , "ceremony" , "chairman" , "champion" , "changing" , "chemical" , "civilian" , "classify" , "clinical" , "clothing" , "collapse" , "colonial" , "colorful" , "combined" , "commonly" , "complain" , "complete" , "compound" , "comprise" , "computer" , "conceive" , "conclude" , "concrete" , "conflict" , "confront" , "consider" , "constant" , "consumer" , "continue" , "contract" , "contrast" , "convince" , "corridor" , "coverage" , "creation" , "creative" , "creature" , "criminal" , "criteria" , "critical" , "cultural" , "currency" , "customer" , "darkness" , "database" , "daughter" , "deadline" , "decision" , "decorate" , "decrease" , "dedicate" , "defender" , "delicate" , "delivery" , "describe" , "designer" , "detailed" , "diabetes" , "diagnose" , "dialogue" , "diminish" , "diplomat" , "directly" , "director" , "disabled" , "disagree" , "disaster" , "disclose" , "discount" , "discover" , "disorder" , "dissolve" , "distance" , "distinct" , "distract" , "district" , "division" , "doctrine" , "document" , "domestic" , "dominant" , "dominate" , "donation" , "downtown" , "dramatic" , "drinking" , "driveway" , "dynamics" , "earnings" , "economic" , "educator" , "election" , "electric" , "elephant" , "elevator" , "eligible" , "emerging" , "emission" , "emphasis" , "employee" , "employer" , "engineer" , "enormous" , "entirely" , "entrance" , "envelope" , "envision" , "epidemic" , "equality" , "equation" , "estimate" , "evaluate" , "everyday" , "everyone" , "evidence" , "exchange" , "exciting" , "exercise" , "existing" , "expected" , "explicit" , "exposure" , "extended" , "external" , "facility" , "familiar" , "favorite" , "feedback" , "feminist" , "festival" , "fighting" , "flexible" , "football" , "forehead" , "formerly" , "fraction" , "fragment" , "frequent" , "freshman" , "friendly" , "frontier" , "function" , "gasoline" , "generate" , "generous" , "governor" , "graduate" , "grateful" , "greatest" , "guidance" , "handsome" , "hardware" , "headache" , "headline" , "heritage" , "hesitate" , "historic" , "homeland" , "homeless" , "homework" , "honestly" , "horrible" , "hospital" , "humanity" , "identify" , "identity" , "ideology" , "illusion" , "improved" , "incident" , "increase" , "indicate" , "industry" , "informal" , "inherent" , "initiate" , "innocent" , "instance" , "instinct" , "instruct" , "interact" , "interest" , "interior" , "internal" , "interval" , "intimate" , "invasion" , "investor" , "involved" , "isolated" , "judgment" , "judicial" , "landmark" , "language" , "laughter" , "lawmaker" , "learning" , "lifetime" , "lighting" , "likewise" , "listener" , "literary" , "location" , "longtime" , "magazine" , "magnetic" , "maintain" , "majority" , "managing" , "marriage" , "material" , "meantime" , "mechanic" , "medicine" , "mentally" , "merchant" , "metaphor" , "midnight" , "military" , "minimize" , "minister" , "ministry" , "minority" , "moderate" , "molecule" , "momentum" , "monument" , "moreover" , "mortgage" , "motivate" , "mountain" , "movement" , "multiple" , "mushroom" , "musician" , "national" , "negative" , "neighbor" , "normally" , "northern" , "notebook" , "numerous" , "nutrient" , "observer" , "obstacle" , "occasion" , "offender" , "offering" , "official" , "operator" , "opponent" , "opposite" , "ordinary" , "organism" , "organize" , "original" , "outsider" , "overcome" , "overlook" , "painting" , "parental" , "particle" , "patience" , "peaceful" , "perceive" , "personal" , "persuade" , "physical" , "planning" , "platform" , "pleasant" , "pleasure" , "politics" , "portrait" , "position" , "positive" , "possible" , "possibly" , "powerful" , "practice" , "precious" , "predator" , "pregnant" , "presence" , "preserve" , "pressure" , "previous" , "priority" , "prisoner" , "probably" , "proclaim" , "producer" , "profound" , "progress" , "prohibit" , "properly" , "property" , "proposal" , "proposed" , "prospect" , "protocol" , "provided" , "provider" , "province" , "publicly" , "purchase" , "quantity" , "question" , "railroad" , "rational" , "reaction" , "receiver" , "recently" , "recovery" , "regional" , "register" , "regulate" , "relation" , "relative" , "relevant" , "reliable" , "religion" , "remember" , "reminder" , "reporter" , "republic" , "required" , "research" , "resemble" , "resident" , "resource" , "response" , "restrict" , "retailer" , "rhetoric" , "romantic" , "sanction" , "sandwich" , "scenario" , "schedule" , "scramble" , "security" , "selected" , "sentence" , "separate" , "sequence" , "severely" , "sexually" , "shooting" , "shopping" , "shortage" , "shoulder" , "sidewalk" , "slightly" , "socially" , "software" , "solution" , "somebody" , "sometime" , "somewhat" , "southern" , "specific" , "spectrum" , "spending" , "sprinkle" , "standard" , "standing" , "starting" , "steadily" , "stimulus" , "straight" , "stranger" , "strategy" , "strength" , "strictly" , "striking" , "strongly" , "struggle" , "suburban" , "suddenly" , "suitable" , "sunlight" , "superior" , "supplier" , "supposed" , "surprise" , "surround" , "survival" , "survivor" , "swimming" , "symbolic" , "sympathy" , "syndrome" , "talented" , "taxpayer" , "teaching" , "teammate" , "teaspoon" , "teenager" , "tendency" , "terrible" , "terribly" , "terrific" , "textbook" , "theology" , "thinking" , "thousand" , "threaten" , "together" , "tolerate" , "tomorrow" , "training" , "transfer" , "transmit" , "traveler" , "treasure" , "tropical" , "troubled" , "ultimate" , "universe" , "unlikely" , "upstairs" , "vacation" , "validity" , "valuable" , "variable" , "vertical" , "violence" , "weakness" , "whatever" , "whenever" , "wherever" , "wildlife" , "withdraw" , "workshop" , "yourself" , "accompany" , "according" , "admission" , "advantage" , "adventure" , "advertise" , "aesthetic" , "afternoon" , "afterward" , "agreement" , "allegedly" , "alongside" , "ambitious" , "amendment" , "anonymous" , "apartment" , "apologize" , "architect" , "assistant" , "associate" , "attention" , "attribute" , "authority" , "authorize" , "automatic" , "available" , "awareness" , "basically" , "beautiful" , "beginning" , "biography" , "boyfriend" , "breakfast" , "breathing" , "brilliant" , "broadcast" , "butterfly" , "calculate" , "candidate" , "carefully" , "celebrate" , "celebrity" , "certainly" , "challenge" , "character" , "chemistry" , "childhood" , "chocolate" , "cigarette" , "classical" , "classroom" , "coalition" , "cognitive" , "colleague" ] -- Shuffled so that you get an even distribution of words -- when taking `leftSide` type FourLetterWords = ToTree '[ "ergo" , "blur" , "gaze" , "said" , "cone" , "thaw" , "undo" , "than" , "vile" , "rods" , "thug" , "hurt" , "matt" , "spun" , "eggs" , "tail" , "copy" , "says" , "gust" , "rims" , "mild" , "feed" , "hawk" , "pelt" , "pawn" , "suit" , "rain" , "trap" , "bulk" , "slug" , "spay" , "ring" , "hate" , "time" , "mole" , "skip" , "cart" , "pall" , "full" , "glue" , "fate" , "fast" , "keen" , "mead" , "flux" , "jets" , "part" , "bone" , "wept" , "apex" , "lace" , "very" , "dawn" , "lies" , "ware" , "bead" , "anew" , "lint" , "deal" , "slur" , "lung" , "came" , "mace" , "bonk" , "text" , "save" , "dell" , "left" , "clip" , "mute" , "glib" , "gala" , "arts" , "rush" , "raid" , "asks" , "pray" , "amid" , "cram" , "leap" , "best" , "prey" , "laws" , "jazz" , "redo" , "eave" , "fore" , "shoe" , "nice" , "grit" , "paid" , "boom" , "whim" , "used" , "puck" , "smog" , "sack" , "year" , "pens" , "flex" , "hash" , "suss" , "sums" , "bait" , "cyst" , "hilt" , "warp" , "cave" , "fuss" , "spry" , "bunk" , "firm" , "lend" , "pulp" , "port" , "lick" , "aria" , "body" , "sway" , "edgy" , "lewd" , "wuss" , "horn" , "yowl" , "link" , "chop" , "kiln" , "moss" , "dome" , "halo" , "lull" , "fits" , "foul" , "cask" , "bred" , "wink" , "grow" , "helm" , "cage" , "lime" , "lump" , "take" , "wall" , "hoop" , "pore" , "lazy" , "poet" , "sure" , "root" , "nods" , "buck" , "vine" , "seam" , "died" , "toss" , "oven" , "palm" , "rusk" , "bomb" , "tore" , "gash" , "glad" , "maim" , "hips" , "arch" , "skit" , "tree" , "snot" , "bees" , "toll" , "step" , "prod" , "food" , "pits" , "gape" , "welt" , "diet" , "saga" , "limb" , "bent" , "bark" , "tuck" , "gasp" , "heat" , "hind" , "tune" , "buoy" , "buff" , "gaps" , "womb" , "ball" , "hats" , "clog" , "ages" , "cuff" , "lips" , "were" , "pump" , "rate" , "cues" , "damn" , "knit" , "lust" , "seer" , "ford" , "swat" , "dunk" , "iris" , "hack" , "grid" , "tied" , "rats" , "brag" , "mesh" , "lock" , "stir" , "snub" , "bake" , "baby" , "call" , "club" , "cyan" , "boar" , "high" , "tear" , "safe" , "wood" , "hemp" , "play" , "pool" , "rest" , "sail" , "tire" , "corn" , "sold" , "plum" , "webs" , "talk" , "pale" , "plea" , "luck" , "into" , "thud" , "drew" , "seem" , "hump" , "belt" , "kiss" , "each" , "cash" , "jean" , "hill" , "digs" , "null" , "when" , "chap" , "wake" , "rear" , "pike" , "farm" , "mold" , "lean" , "pins" , "gulf" , "buys" , "tool" , "demo" , "made" , "plug" , "bard" , "ears" , "oaks" , "lest" , "plus" , "nuke" , "legs" , "plan" , "dash" , "hair" , "lute" , "army" , "evil" , "look" , "wipe" , "gist" , "meow" , "bail" , "knew" , "nail" , "deck" , "ever" , "snag" , "desk" , "heel" , "some" , "pans" , "germ" , "mind" , "will" , "vans" , "guys" , "dorm" , "bids" , "lays" , "code" , "pays" , "shod" , "lose" , "sash" , "clap" , "grab" , "oral" , "taut" , "cull" , "toys" , "slow" , "molt" , "ties" , "bane" , "salt" , "hike" , "idol" , "uses" , "maid" , "pear" , "gray" , "melt" , "most" , "news" , "cope" , "bawl" , "rank" , "mock" , "clay" , "lard" , "crib" , "noun" , "peel" , "sore" , "nick" , "meld" , "main" , "jars" , "mist" , "skim" , "easy" , "road" , "gosh" , "kite" , "wise" , "foot" , "puff" , "cusp" , "lush" , "boon" , "fray" , "gunk" , "cult" , "garb" , "cent" , "flee" , "rung" , "math" , "dire" , "yard" , "loom" , "kill" , "dice" , "ajar" , "vial" , "rise" , "hone" , "whet" , "skin" , "vase" , "silo" , "flap" , "fork" , "pick" , "meme" , "boat" , "jump" , "sewn" , "memo" , "page" , "chin" , "zeal" , "fees" , "peek" , "furs" , "guts" , "euro" , "tidy" , "site" , "veil" , "labs" , "wilt" , "busk" , "stag" , "ploy" , "tart" , "beer" , "data" , "heap" , "beds" , "tusk" , "heed" , "deem" , "shut" , "clan" , "burn" , "stay" , "size" , "hers" , "glow" , "dope" , "gong" , "pour" , "wave" , "here" , "hiss" , "dial" , "bled" , "prev" , "diff" , "rave" , "loud" , "king" , "fume" , "bare" , "comb" , "claw" , "bars" , "mush" , "dads" , "idea" , "twos" , "glam" , "song" , "tend" , "rust" , "tray" , "over" , "ours" , "caps" , "duet" , "what" , "dote" , "dock" , "case" , "dude" , "bull" , "tuna" , "opts" , "weld" , "west" , "skid" , "upon" , "raft" , "dine" , "stew" , "wren" , "lady" , "slip" , "wine" , "prop" , "fall" , "rule" , "junk" , "pain" , "newt" , "tank" , "game" , "must" , "jaws" , "riot" , "room" , "cook" , "risk" , "race" , "wrap" , "soap" , "dump" , "spur" , "thin" , "duke" , "scan" , "etch" , "mime" , "seen" , "rook" , "gets" , "care" , "neck" , "teen" , "punk" , "post" , "dove" , "brim" , "sole" , "silk" , "bold" , "bale" , "vary" , "lash" , "vein" , "down" , "pave" , "burp" , "does" , "dead" , "also" , "veal" , "snap" , "punt" , "gate" , "john" , "toad" , "swig" , "teas" , "soot" , "drag" , "real" , "fake" , "vale" , "tame" , "swim" , "cake" , "fine" , "balk" , "gone" , "mend" , "oboe" , "grew" , "pond" , "peer" , "view" , "bird" , "gull" , "meet" , "flip" , "seal" , "fail" , "mass" , "team" , "pole" , "hope" , "path" , "yelp" , "mull" , "eels" , "coal" , "wire" , "wade" , "send" , "aids" , "cord" , "bang" , "life" , "push" , "rang" , "slot" , "jail" , "exam" , "raze" , "ramp" , "name" , "rail" , "card" , "boil" , "find" , "pact" , "duck" , "host" , "dogs" , "self" , "tyre" , "sunk" , "butt" , "home" , "bald" , "chat" , "kink" , "show" , "skis" , "jinx" , "tick" , "leaf" , "aqua" , "roar" , "mail" , "your" , "kits" , "fire" , "them" , "colt" , "foxy" , "list" , "serf" , "loft" , "joke" , "type" , "park" , "pail" , "wide" , "male" , "cans" , "ones" , "veer" , "deft" , "cuts" , "tens" , "icon" , "hear" , "pyre" , "wing" , "wets" , "core" , "well" , "perk" , "brat" , "deaf" , "tale" , "mint" , "sang" , "soda" , "girl" , "cops" , "tram" , "pack" , "fuse" , "rent" , "camp" , "acid" , "suck" , "hero" , "kick" , "fowl" , "loss" , "peep" , "week" , "yank" , "feet" , "onto" , "free" , "runs" , "runt" , "mike" , "only" , "hulk" , "turn" , "rude" , "wart" , "faun" , "balm" , "obey" , "czar" , "dams" , "fold" , "slid" , "rich" , "snip" , "scum" , "mean" , "meek" , "ruse" , "hugs" , "term" , "fish" , "tier" , "gyms" , "tony" , "atop" , "ally" , "crow" , "jest" , "ahoy" , "gram" , "hoax" , "dies" , "pout" , "yolk" , "iron" , "nose" , "jade" , "feud" , "bean" , "poor" , "area" , "shot" , "ooze" , "file" , "less" , "sake" , "weep" , "such" , "york" , "puny" , "hole" , "spam" , "fort" , "once" , "foam" , "hazy" , "tall" , "rake" , "lids" , "sane" , "mess" , "nest" , "omit" , "dolt" , "cane" , "warn" , "rage" , "seed" , "lead" , "told" , "knob" , "drop" , "gush" , "riff" , "wear" , "folk" , "dots" , "scab" , "ruby" , "tape" , "gift" , "soak" , "laps" , "quip" , "side" , "vibe" , "rips" , "lots" , "boot" , "ugly" , "hood" , "clue" , "wage" , "sick" , "ride" , "cosy" , "numb" , "pats" , "bans" , "glum" , "read" , "haze" , "taps" , "cold" , "vote" , "mice" , "coin" , "gait" , "idle" , "fend" , "onus" , "born" , "ends" , "help" , "gain" , "spar" , "doom" , "opal" , "tube" , "band" , "tuft" , "rubs" , "sofa" , "soup" , "robe" , "peas" , "spot" , "hush" , "wins" , "hare" , "zoom" , "harm" , "hull" , "come" , "verb" , "lost" , "sigh" , "rump" , "bowl" , "fond" , "warm" , "scam" , "dear" , "jolt" , "swab" , "seek" , "bony" , "laze" , "late" , "aims" , "ouch" , "lava" , "zone" , "whey" , "land" , "nerd" , "eras" , "chef" , "heft" , "turf" , "past" , "mark" , "yeti" , "clop" , "dent" , "epic" , "whom" , "mast" , "dust" , "mall" , "from" , "deer" , "drip" , "deep" , "rows" , "owns" , "base" , "duct" , "woke" , "bays" , "bask" , "tags" , "feel" , "maul" , "logs" , "silt" , "feat" , "herb" , "next" , "sues" , "mite" , "with" , "blob" , "roof" , "geek" , "dull" , "meat" , "pant" , "dual" , "dive" , "open" , "flog" , "spit" , "unto" , "pile" , "acre" , "dusk" , "sank" , "rape" , "pics" , "rink" , "guns" , "oath" , "slam" , "sled" , "okay" , "mope" , "bend" , "trot" , "shim" , "town" , "guru" , "weak" , "fair" , "shit" , "gave" , "deny" , "deed" , "fans" , "hymn" , "soil" , "lice" , "nets" , "zest" , "stop" , "yoga" , "rely" , "mode" , "pots" , "form" , "kelp" , "half" , "coil" , "swap" , "city" , "fern" , "edit" , "fill" , "blip" , "hoof" , "rift" , "spat" , "coup" , "cats" , "yawn" , "leer" , "shed" , "pies" , "malt" , "pint" , "bags" , "gulp" , "leek" , "glen" , "wind" , "stun" , "clam" , "cube" , "bass" , "nope" , "know" , "holy" , "chug" , "herd" , "spin" , "cool" , "word" , "ways" , "that" , "hide" , "eats" , "drab" , "tech" , "took" , "grim" , "book" , "work" , "akin" , "pass" , "bank" , "rare" , "ripe" , "itch" , "mule" , "poke" , "bolt" , "snug" , "wimp" , "loot" , "ward" , "ghee" , "beta" , "dean" , "dime" , "film" , "wane" , "tile" , "muse" , "went" , "fool" , "navy" , "huge" , "even" , "heal" , "visa" , "earn" , "fart" , "pull" , "dart" , "howl" , "debt" , "awry" , "mare" , "auto" , "dark" , "crux" , "isle" , "cozy" , "bump" , "vend" , "font" , "wand" , "sour" , "babe" , "bran" , "bode" , "goal" , "foil" , "knee" , "bade" , "bash" , "aide" , "neat" , "swag" , "hurl" , "rope" , "quit" , "reef" , "bong" , "note" , "fund" , "thus" , "hose" , "sexy" , "grin" , "beep" , "duty" , "fled" , "mill" , "near" , "quay" , "fare" , "lack" , "earl" , "gory" , "fuel" , "tuba" , "sand" , "fear" , "sign" , "live" , "hype" , "door" , "much" , "node" , "snow" ]