{-# LANGUAGE OverloadedStrings #-} {-| Module : Network.Haskoin.Keys.Mnemonic Copyright : No rights reserved License : UNLICENSE Maintainer : xenog@protonmail.com Stability : experimental Portability : POSIX Mnemonic keys (BIP-39). Only English dictionary. -} module Network.Haskoin.Keys.Mnemonic ( -- * Mnemonic Sentences Entropy , Mnemonic , Passphrase , Seed , toMnemonic , fromMnemonic , mnemonicToSeed ) where import Control.Monad (when) import Crypto.Hash (SHA256 (..), hashWith) import Crypto.KDF.PBKDF2 (Parameters (..), fastPBKDF2_SHA512) import Data.Bits (shiftL, shiftR) import qualified Data.ByteArray as BA import Data.ByteString (ByteString) import qualified Data.ByteString as BS import Data.List import qualified Data.Map.Strict as M import Data.Maybe import Data.String.Conversions (cs) import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.Encoding as E import Data.Vector (Vector, (!)) import qualified Data.Vector as V import Network.Haskoin.Util -- | Random data used to create a mnemonic sentence. Use a good entropy source. -- You will get your coins stolen if you don't. You have been warned. type Entropy = ByteString -- | Human-readable mnemonic sentence. type Mnemonic = Text -- | Optional passphrase for mnemnoic sentence. type Passphrase = ByteString -- | Seed for a private key from a mnemonic sentence. type Seed = ByteString -- | Mnemonic key checksum. type Checksum = ByteString -- | Paremeters for PBKDF2 function. pbkdfParams :: Parameters pbkdfParams = Parameters {iterCounts = 2048, outputLength = 64} -- | Provide intial 'Entropy' as a 'ByteString' of length multiple of 4 bytes. -- Output a 'Mnemonic' sentence. toMnemonic :: Entropy -> Either String Mnemonic toMnemonic ent = do when (BS.null ent) $ Left "toMnemonic: entropy can not be empty" when (remainder /= 0) $ Left "toMnemonic: entropy must be multiples of 4 bytes" when (cs_len > 16) $ Left "toMnemonic: maximum entropy is 64 bytes (512 bits)" return ms where (cs_len, remainder) = BS.length ent `quotRem` 4 c = calcCS cs_len ent indices = bsToIndices $ ent `BS.append` c ms = T.unwords $ map (wl!) indices -- | Revert 'toMnemonic'. Do not use this to generate a 'Seed'. Instead use -- 'mnemonicToSeed'. This outputs the original 'Entropy' used to generate a -- 'Mnemonic' sentence. fromMnemonic :: Mnemonic -> Either String Entropy fromMnemonic ms = do when (T.null ms) $ Left "fromMnemonic: empty mnemonic" when (word_count > 48) $ Left $ "fromMnemonic: too many words: " ++ show word_count when (word_count `mod` 3 /= 0) $ Left $ "fromMnemonic: wrong number of words:" ++ show word_count ms_bs <- indicesToBS =<< getIndices ms_words let (ms_ent, ms_cs) = BS.splitAt (ent_len * 4) ms_bs ms_cs_num = numCS cs_len ms_cs ent_cs_num = numCS cs_len $ calcCS cs_len ms_ent when (ent_cs_num /= ms_cs_num) $ Left $ "fromMnemonic: checksum failed: " ++ sh ent_cs_num ms_cs_num return ms_ent where ms_words = T.words ms word_count = length ms_words (ent_len, cs_len) = (word_count * 11) `quotRem` 32 sh cs_a cs_b = show cs_a ++ " /= " ++ show cs_b -- | Compute 'Checksum'. calcCS :: Int -> Entropy -> Checksum calcCS len = getBits len . BA.convert . hashWith SHA256 numCS :: Int -> Entropy -> Integer numCS len = shiftCS . bsToInteger where shiftCS = case 8 - len `mod` 8 of 8 -> id x -> flip shiftR x -- | Turn an arbitrary sequence of characters into a 512-bit 'Seed'. Use -- 'mnemonicToSeed' to get a seed from a 'Mnemonic' sentence. Warning: Does not -- perform NFKD normalization. anyToSeed :: Passphrase -> Mnemonic -> Seed anyToSeed pf ms = fastPBKDF2_SHA512 pbkdfParams (E.encodeUtf8 ms) ("mnemonic" `mappend` pf) -- | Get a 512-bit 'Seed' from a 'Mnemonic' sentence. Will validate checksum. -- 'Passphrase' can be used to protect the 'Mnemonic'. Use an empty string as -- 'Passphrase' if none is required. mnemonicToSeed :: Passphrase -> Mnemonic -> Either String Seed mnemonicToSeed pf ms = do ent <- fromMnemonic ms mnm <- toMnemonic ent return $ anyToSeed pf mnm -- | Get indices of words in word list. getIndices :: [Text] -> Either String [Int] getIndices ws | null n = return $ catMaybes i | otherwise = Left $ "getIndices: words not found: " ++ cs w where i = map (`M.lookup` wl') ws n = elemIndices Nothing i w = T.unwords $ map (ws !!) n -- | Turn a list of 11-bit numbers into a 'ByteString' indicesToBS :: [Int] -> Either String ByteString indicesToBS is = do when lrg $ Left "indicesToBS: index larger or equal than 2048" return . pad . integerToBS $ foldl' f 0 is `shiftL` shift_width where lrg = isJust $ find (>= 2048) is (q, r) = (length is * 11) `quotRem` 8 shift_width = if r == 0 then 0 else 8 - r bl = if r == 0 then q else q + 1 -- length of resulting ByteString pad bs = BS.append (BS.replicate (bl - BS.length bs) 0x00) bs f acc x = (acc `shiftL` 11) + fromIntegral x -- | Turn a 'ByteString' into a list of 11-bit numbers. bsToIndices :: ByteString -> [Int] bsToIndices bs = reverse . go q $ bsToInteger bs `shiftR` r where (q, r) = (BS.length bs * 8) `quotRem` 11 go 0 _ = [] go n i = fromIntegral (i `mod` 2048) : go (n - 1) (i `shiftR` 11) wl' :: M.Map Text Int wl' = V.ifoldr' (\i w m -> M.insert w i m) M.empty wl -- | Standard English dictionary from BIP-39 specification. wl :: Vector Text wl = V.fromListN 2048 [ "abandon", "ability", "able", "about", "above", "absent" , "absorb", "abstract", "absurd", "abuse", "access", "accident" , "account", "accuse", "achieve", "acid", "acoustic", "acquire" , "across", "act", "action", "actor", "actress", "actual" , "adapt", "add", "addict", "address", "adjust", "admit" , "adult", "advance", "advice", "aerobic", "affair", "afford" , "afraid", "again", "age", "agent", "agree", "ahead" , "aim", "air", "airport", "aisle", "alarm", "album" , "alcohol", "alert", "alien", "all", "alley", "allow" , "almost", "alone", "alpha", "already", "also", "alter" , "always", "amateur", "amazing", "among", "amount", "amused" , "analyst", "anchor", "ancient", "anger", "angle", "angry" , "animal", "ankle", "announce", "annual", "another", "answer" , "antenna", "antique", "anxiety", "any", "apart", "apology" , "appear", "apple", "approve", "april", "arch", "arctic" , "area", "arena", "argue", "arm", "armed", "armor" , "army", "around", "arrange", "arrest", "arrive", "arrow" , "art", "artefact", "artist", "artwork", "ask", "aspect" , "assault", "asset", "assist", "assume", "asthma", "athlete" , "atom", "attack", "attend", "attitude", "attract", "auction" , "audit", "august", "aunt", "author", "auto", "autumn" , "average", "avocado", "avoid", "awake", "aware", "away" , "awesome", "awful", "awkward", "axis", "baby", "bachelor" , "bacon", "badge", "bag", "balance", "balcony", "ball" , "bamboo", "banana", "banner", "bar", "barely", "bargain" , "barrel", "base", "basic", "basket", "battle", "beach" , "bean", "beauty", "because", "become", "beef", "before" , "begin", "behave", "behind", "believe", "below", "belt" , "bench", "benefit", "best", "betray", "better", "between" , "beyond", "bicycle", "bid", "bike", "bind", "biology" , "bird", "birth", "bitter", "black", "blade", "blame" , "blanket", "blast", "bleak", "bless", "blind", "blood" , "blossom", "blouse", "blue", "blur", "blush", "board" , "boat", "body", "boil", "bomb", "bone", "bonus" , "book", "boost", "border", "boring", "borrow", "boss" , "bottom", "bounce", "box", "boy", "bracket", "brain" , "brand", "brass", "brave", "bread", "breeze", "brick" , "bridge", "brief", "bright", "bring", "brisk", "broccoli" , "broken", "bronze", "broom", "brother", "brown", "brush" , "bubble", "buddy", "budget", "buffalo", "build", "bulb" , "bulk", "bullet", "bundle", "bunker", "burden", "burger" , "burst", "bus", "business", "busy", "butter", "buyer" , "buzz", "cabbage", "cabin", "cable", "cactus", "cage" , "cake", "call", "calm", "camera", "camp", "can" , "canal", "cancel", "candy", "cannon", "canoe", "canvas" , "canyon", "capable", "capital", "captain", "car", "carbon" , "card", "cargo", "carpet", "carry", "cart", "case" , "cash", "casino", "castle", "casual", "cat", "catalog" , "catch", "category", "cattle", "caught", "cause", "caution" , "cave", "ceiling", "celery", "cement", "census", "century" , "cereal", "certain", "chair", "chalk", "champion", "change" , "chaos", "chapter", "charge", "chase", "chat", "cheap" , "check", "cheese", "chef", "cherry", "chest", "chicken" , "chief", "child", "chimney", "choice", "choose", "chronic" , "chuckle", "chunk", "churn", "cigar", "cinnamon", "circle" , "citizen", "city", "civil", "claim", "clap", "clarify" , "claw", "clay", "clean", "clerk", "clever", "click" , "client", "cliff", "climb", "clinic", "clip", "clock" , "clog", "close", "cloth", "cloud", "clown", "club" , "clump", "cluster", "clutch", "coach", "coast", "coconut" , "code", "coffee", "coil", "coin", "collect", "color" , "column", "combine", "come", "comfort", "comic", "common" , "company", "concert", "conduct", "confirm", "congress", "connect" , "consider", "control", "convince", "cook", "cool", "copper" , "copy", "coral", "core", "corn", "correct", "cost" , "cotton", "couch", "country", "couple", "course", "cousin" , "cover", "coyote", "crack", "cradle", "craft", "cram" , "crane", "crash", "crater", "crawl", "crazy", "cream" , "credit", "creek", "crew", "cricket", "crime", "crisp" , "critic", "crop", "cross", "crouch", "crowd", "crucial" , "cruel", "cruise", "crumble", "crunch", "crush", "cry" , "crystal", "cube", "culture", "cup", "cupboard", "curious" , "current", "curtain", "curve", "cushion", "custom", "cute" , "cycle", "dad", "damage", "damp", "dance", "danger" , "daring", "dash", "daughter", "dawn", "day", "deal" , "debate", "debris", "decade", "december", "decide", "decline" , "decorate", "decrease", "deer", "defense", "define", "defy" , "degree", "delay", "deliver", "demand", "demise", "denial" , "dentist", "deny", "depart", "depend", "deposit", "depth" , "deputy", "derive", "describe", "desert", "design", "desk" , "despair", "destroy", "detail", "detect", "develop", "device" , "devote", "diagram", "dial", "diamond", "diary", "dice" , "diesel", "diet", "differ", "digital", "dignity", "dilemma" , "dinner", "dinosaur", "direct", "dirt", "disagree", "discover" , "disease", "dish", "dismiss", "disorder", "display", "distance" , "divert", "divide", "divorce", "dizzy", "doctor", "document" , "dog", "doll", "dolphin", "domain", "donate", "donkey" , "donor", "door", "dose", "double", "dove", "draft" , "dragon", "drama", "drastic", "draw", "dream", "dress" , "drift", "drill", "drink", "drip", "drive", "drop" , "drum", "dry", "duck", "dumb", "dune", "during" , "dust", "dutch", "duty", "dwarf", "dynamic", "eager" , "eagle", "early", "earn", "earth", "easily", "east" , "easy", "echo", "ecology", "economy", "edge", "edit" , "educate", "effort", "egg", "eight", "either", "elbow" , "elder", "electric", "elegant", "element", "elephant", "elevator" , "elite", "else", "embark", "embody", "embrace", "emerge" , "emotion", "employ", "empower", "empty", "enable", "enact" , "end", "endless", "endorse", "enemy", "energy", "enforce" , "engage", "engine", "enhance", "enjoy", "enlist", "enough" , "enrich", "enroll", "ensure", "enter", "entire", "entry" , "envelope", "episode", "equal", "equip", "era", "erase" , "erode", "erosion", "error", "erupt", "escape", "essay" , "essence", "estate", "eternal", "ethics", "evidence", "evil" , "evoke", "evolve", "exact", "example", "excess", "exchange" , "excite", "exclude", "excuse", "execute", "exercise", "exhaust" , "exhibit", "exile", "exist", "exit", "exotic", "expand" , "expect", "expire", "explain", "expose", "express", "extend" , "extra", "eye", "eyebrow", "fabric", "face", "faculty" , "fade", "faint", "faith", "fall", "false", "fame" , "family", "famous", "fan", "fancy", "fantasy", "farm" , "fashion", "fat", "fatal", "father", "fatigue", "fault" , "favorite", "feature", "february", "federal", "fee", "feed" , "feel", "female", "fence", "festival", "fetch", "fever" , "few", "fiber", "fiction", "field", "figure", "file" , "film", "filter", "final", "find", "fine", "finger" , "finish", "fire", "firm", "first", "fiscal", "fish" , "fit", "fitness", "fix", "flag", "flame", "flash" , "flat", "flavor", "flee", "flight", "flip", "float" , "flock", "floor", "flower", "fluid", "flush", "fly" , "foam", "focus", "fog", "foil", "fold", "follow" , "food", "foot", "force", "forest", "forget", "fork" , "fortune", "forum", "forward", "fossil", "foster", "found" , "fox", "fragile", "frame", "frequent", "fresh", "friend" , "fringe", "frog", "front", "frost", "frown", "frozen" , "fruit", "fuel", "fun", "funny", "furnace", "fury" , "future", "gadget", "gain", "galaxy", "gallery", "game" , "gap", "garage", "garbage", "garden", "garlic", "garment" , "gas", "gasp", "gate", "gather", "gauge", "gaze" , "general", "genius", "genre", "gentle", "genuine", "gesture" , "ghost", "giant", "gift", "giggle", "ginger", "giraffe" , "girl", "give", "glad", "glance", "glare", "glass" , "glide", "glimpse", "globe", "gloom", "glory", "glove" , "glow", "glue", "goat", "goddess", "gold", "good" , "goose", "gorilla", "gospel", "gossip", "govern", "gown" , "grab", "grace", "grain", "grant", "grape", "grass" , "gravity", "great", "green", "grid", "grief", "grit" , "grocery", "group", "grow", "grunt", "guard", "guess" , "guide", "guilt", "guitar", "gun", "gym", "habit" , "hair", "half", "hammer", "hamster", "hand", "happy" , "harbor", "hard", "harsh", "harvest", "hat", "have" , "hawk", "hazard", "head", "health", "heart", "heavy" , "hedgehog", "height", "hello", "helmet", "help", "hen" , "hero", "hidden", "high", "hill", "hint", "hip" , "hire", "history", "hobby", "hockey", "hold", "hole" , "holiday", "hollow", "home", "honey", "hood", "hope" , "horn", "horror", "horse", "hospital", "host", "hotel" , "hour", "hover", "hub", "huge", "human", "humble" , "humor", "hundred", "hungry", "hunt", "hurdle", "hurry" , "hurt", "husband", "hybrid", "ice", "icon", "idea" , "identify", "idle", "ignore", "ill", "illegal", "illness" , "image", "imitate", "immense", "immune", "impact", "impose" , "improve", "impulse", "inch", "include", "income", "increase" , "index", "indicate", "indoor", "industry", "infant", "inflict" , "inform", "inhale", "inherit", "initial", "inject", "injury" , "inmate", "inner", "innocent", "input", "inquiry", "insane" , "insect", "inside", "inspire", "install", "intact", "interest" , "into", "invest", "invite", "involve", "iron", "island" , "isolate", "issue", "item", "ivory", "jacket", "jaguar" , "jar", "jazz", "jealous", "jeans", "jelly", "jewel" , "job", "join", "joke", "journey", "joy", "judge" , "juice", "jump", "jungle", "junior", "junk", "just" , "kangaroo", "keen", "keep", "ketchup", "key", "kick" , "kid", "kidney", "kind", "kingdom", "kiss", "kit" , "kitchen", "kite", "kitten", "kiwi", "knee", "knife" , "knock", "know", "lab", "label", "labor", "ladder" , "lady", "lake", "lamp", "language", "laptop", "large" , "later", "latin", "laugh", "laundry", "lava", "law" , "lawn", "lawsuit", "layer", "lazy", "leader", "leaf" , "learn", "leave", "lecture", "left", "leg", "legal" , "legend", "leisure", "lemon", "lend", "length", "lens" , "leopard", "lesson", "letter", "level", "liar", "liberty" , "library", "license", "life", "lift", "light", "like" , "limb", "limit", "link", "lion", "liquid", "list" , "little", "live", "lizard", "load", "loan", "lobster" , "local", "lock", "logic", "lonely", "long", "loop" , "lottery", "loud", "lounge", "love", "loyal", "lucky" , "luggage", "lumber", "lunar", "lunch", "luxury", "lyrics" , "machine", "mad", "magic", "magnet", "maid", "mail" , "main", "major", "make", "mammal", "man", "manage" , "mandate", "mango", "mansion", "manual", "maple", "marble" , "march", "margin", "marine", "market", "marriage", "mask" , "mass", "master", "match", "material", "math", "matrix" , "matter", "maximum", "maze", "meadow", "mean", "measure" , "meat", "mechanic", "medal", "media", "melody", "melt" , "member", "memory", "mention", "menu", "mercy", "merge" , "merit", "merry", "mesh", "message", "metal", "method" , "middle", "midnight", "milk", "million", "mimic", "mind" , "minimum", "minor", "minute", "miracle", "mirror", "misery" , "miss", "mistake", "mix", "mixed", "mixture", "mobile" , "model", "modify", "mom", "moment", "monitor", "monkey" , "monster", "month", "moon", "moral", "more", "morning" , "mosquito", "mother", "motion", "motor", "mountain", "mouse" , "move", "movie", "much", "muffin", "mule", "multiply" , "muscle", "museum", "mushroom", "music", "must", "mutual" , "myself", "mystery", "myth", "naive", "name", "napkin" , "narrow", "nasty", "nation", "nature", "near", "neck" , "need", "negative", "neglect", "neither", "nephew", "nerve" , "nest", "net", "network", "neutral", "never", "news" , "next", "nice", "night", "noble", "noise", "nominee" , "noodle", "normal", "north", "nose", "notable", "note" , "nothing", "notice", "novel", "now", "nuclear", "number" , "nurse", "nut", "oak", "obey", "object", "oblige" , "obscure", "observe", "obtain", "obvious", "occur", "ocean" , "october", "odor", "off", "offer", "office", "often" , "oil", "okay", "old", "olive", "olympic", "omit" , "once", "one", "onion", "online", "only", "open" , "opera", "opinion", "oppose", "option", "orange", "orbit" , "orchard", "order", "ordinary", "organ", "orient", "original" , "orphan", "ostrich", "other", "outdoor", "outer", "output" , "outside", "oval", "oven", "over", "own", "owner" , "oxygen", "oyster", "ozone", "pact", "paddle", "page" , "pair", "palace", "palm", "panda", "panel", "panic" , "panther", "paper", "parade", "parent", "park", "parrot" , "party", "pass", "patch", "path", "patient", "patrol" , "pattern", "pause", "pave", "payment", "peace", "peanut" , "pear", "peasant", "pelican", "pen", "penalty", "pencil" , "people", "pepper", "perfect", "permit", "person", "pet" , "phone", "photo", "phrase", "physical", "piano", "picnic" , "picture", "piece", "pig", "pigeon", "pill", "pilot" , "pink", "pioneer", "pipe", "pistol", "pitch", "pizza" , "place", "planet", "plastic", "plate", "play", "please" , "pledge", "pluck", "plug", "plunge", "poem", "poet" , "point", "polar", "pole", "police", "pond", "pony" , "pool", "popular", "portion", "position", "possible", "post" , "potato", "pottery", "poverty", "powder", "power", "practice" , "praise", "predict", "prefer", "prepare", "present", "pretty" , "prevent", "price", "pride", "primary", "print", "priority" , "prison", "private", "prize", "problem", "process", "produce" , "profit", "program", "project", "promote", "proof", "property" , "prosper", "protect", "proud", "provide", "public", "pudding" , "pull", "pulp", "pulse", "pumpkin", "punch", "pupil" , "puppy", "purchase", "purity", "purpose", "purse", "push" , "put", "puzzle", "pyramid", "quality", "quantum", "quarter" , "question", "quick", "quit", "quiz", "quote", "rabbit" , "raccoon", "race", "rack", "radar", "radio", "rail" , "rain", "raise", "rally", "ramp", "ranch", "random" , "range", "rapid", "rare", "rate", "rather", "raven" , "raw", "razor", "ready", "real", "reason", "rebel" , "rebuild", "recall", "receive", "recipe", "record", "recycle" , "reduce", "reflect", "reform", "refuse", "region", "regret" , "regular", "reject", "relax", "release", "relief", "rely" , "remain", "remember", "remind", "remove", "render", "renew" , "rent", "reopen", "repair", "repeat", "replace", "report" , "require", "rescue", "resemble", "resist", "resource", "response" , "result", "retire", "retreat", "return", "reunion", "reveal" , "review", "reward", "rhythm", "rib", "ribbon", "rice" , "rich", "ride", "ridge", "rifle", "right", "rigid" , "ring", "riot", "ripple", "risk", "ritual", "rival" , "river", "road", "roast", "robot", "robust", "rocket" , "romance", "roof", "rookie", "room", "rose", "rotate" , "rough", "round", "route", "royal", "rubber", "rude" , "rug", "rule", "run", "runway", "rural", "sad" , "saddle", "sadness", "safe", "sail", "salad", "salmon" , "salon", "salt", "salute", "same", "sample", "sand" , "satisfy", "satoshi", "sauce", "sausage", "save", "say" , "scale", "scan", "scare", "scatter", "scene", "scheme" , "school", "science", "scissors", "scorpion", "scout", "scrap" , "screen", "script", "scrub", "sea", "search", "season" , "seat", "second", "secret", "section", "security", "seed" , "seek", "segment", "select", "sell", "seminar", "senior" , "sense", "sentence", "series", "service", "session", "settle" , "setup", "seven", "shadow", "shaft", "shallow", "share" , "shed", "shell", "sheriff", "shield", "shift", "shine" , "ship", "shiver", "shock", "shoe", "shoot", "shop" , "short", "shoulder", "shove", "shrimp", "shrug", "shuffle" , "shy", "sibling", "sick", "side", "siege", "sight" , "sign", "silent", "silk", "silly", "silver", "similar" , "simple", "since", "sing", "siren", "sister", "situate" , "six", "size", "skate", "sketch", "ski", "skill" , "skin", "skirt", "skull", "slab", "slam", "sleep" , "slender", "slice", "slide", "slight", "slim", "slogan" , "slot", "slow", "slush", "small", "smart", "smile" , "smoke", "smooth", "snack", "snake", "snap", "sniff" , "snow", "soap", "soccer", "social", "sock", "soda" , "soft", "solar", "soldier", "solid", "solution", "solve" , "someone", "song", "soon", "sorry", "sort", "soul" , "sound", "soup", "source", "south", "space", "spare" , "spatial", "spawn", "speak", "special", "speed", "spell" , "spend", "sphere", "spice", "spider", "spike", "spin" , "spirit", "split", "spoil", "sponsor", "spoon", "sport" , "spot", "spray", "spread", "spring", "spy", "square" , "squeeze", "squirrel", "stable", "stadium", "staff", "stage" , "stairs", "stamp", "stand", "start", "state", "stay" , "steak", "steel", "stem", "step", "stereo", "stick" , "still", "sting", "stock", "stomach", "stone", "stool" , "story", "stove", "strategy", "street", "strike", "strong" , "struggle", "student", "stuff", "stumble", "style", "subject" , "submit", "subway", "success", "such", "sudden", "suffer" , "sugar", "suggest", "suit", "summer", "sun", "sunny" , "sunset", "super", "supply", "supreme", "sure", "surface" , "surge", "surprise", "surround", "survey", "suspect", "sustain" , "swallow", "swamp", "swap", "swarm", "swear", "sweet" , "swift", "swim", "swing", "switch", "sword", "symbol" , "symptom", "syrup", "system", "table", "tackle", "tag" , "tail", "talent", "talk", "tank", "tape", "target" , "task", "taste", "tattoo", "taxi", "teach", "team" , "tell", "ten", "tenant", "tennis", "tent", "term" , "test", "text", "thank", "that", "theme", "then" , "theory", "there", "they", "thing", "this", "thought" , "three", "thrive", "throw", "thumb", "thunder", "ticket" , "tide", "tiger", "tilt", "timber", "time", "tiny" , "tip", "tired", "tissue", "title", "toast", "tobacco" , "today", "toddler", "toe", "together", "toilet", "token" , "tomato", "tomorrow", "tone", "tongue", "tonight", "tool" , "tooth", "top", "topic", "topple", "torch", "tornado" , "tortoise", "toss", "total", "tourist", "toward", "tower" , "town", "toy", "track", "trade", "traffic", "tragic" , "train", "transfer", "trap", "trash", "travel", "tray" , "treat", "tree", "trend", "trial", "tribe", "trick" , "trigger", "trim", "trip", "trophy", "trouble", "truck" , "true", "truly", "trumpet", "trust", "truth", "try" , "tube", "tuition", "tumble", "tuna", "tunnel", "turkey" , "turn", "turtle", "twelve", "twenty", "twice", "twin" , "twist", "two", "type", "typical", "ugly", "umbrella" , "unable", "unaware", "uncle", "uncover", "under", "undo" , "unfair", "unfold", "unhappy", "uniform", "unique", "unit" , "universe", "unknown", "unlock", "until", "unusual", "unveil" , "update", "upgrade", "uphold", "upon", "upper", "upset" , "urban", "urge", "usage", "use", "used", "useful" , "useless", "usual", "utility", "vacant", "vacuum", "vague" , "valid", "valley", "valve", "van", "vanish", "vapor" , "various", "vast", "vault", "vehicle", "velvet", "vendor" , "venture", "venue", "verb", "verify", "version", "very" , "vessel", "veteran", "viable", "vibrant", "vicious", "victory" , "video", "view", "village", "vintage", "violin", "virtual" , "virus", "visa", "visit", "visual", "vital", "vivid" , "vocal", "voice", "void", "volcano", "volume", "vote" , "voyage", "wage", "wagon", "wait", "walk", "wall" , "walnut", "want", "warfare", "warm", "warrior", "wash" , "wasp", "waste", "water", "wave", "way", "wealth" , "weapon", "wear", "weasel", "weather", "web", "wedding" , "weekend", "weird", "welcome", "west", "wet", "whale" , "what", "wheat", "wheel", "when", "where", "whip" , "whisper", "wide", "width", "wife", "wild", "will" , "win", "window", "wine", "wing", "wink", "winner" , "winter", "wire", "wisdom", "wise", "wish", "witness" , "wolf", "woman", "wonder", "wood", "wool", "word" , "work", "world", "worry", "worth", "wrap", "wreck" , "wrestle", "wrist", "write", "wrong", "yard", "year" , "yellow", "you", "young", "youth", "zebra", "zero" , "zone", "zoo" ]