{-# LANGUAGE OverloadedStrings #-}

{- |
Module      : Haskoin.Keys.Mnemonic
Copyright   : No rights reserved
License     : MIT
Maintainer  : jprupp@protonmail.ch
Stability   : experimental
Portability : POSIX

Mnemonic keys (BIP-39). Only English dictionary.
-}
module 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 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 = Text

-- | 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
pbkdfParams = Parameters :: Int -> Int -> Parameters
Parameters{iterCounts :: Int
iterCounts = Int
2048, outputLength :: Int
outputLength = Int
64}

{- | Provide intial 'Entropy' as a 'ByteString' of length multiple of 4 bytes.
 Output a 'Mnemonic' sentence.
-}
toMnemonic :: Entropy -> Either String Mnemonic
toMnemonic :: Entropy -> Either String Mnemonic
toMnemonic Entropy
ent = do
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Entropy -> Bool
BS.null Entropy
ent) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left String
"toMnemonic: entropy can not be empty"
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
remainder Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left String
"toMnemonic: entropy must be multiples of 4 bytes"
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
cs_len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
16) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left String
"toMnemonic: maximum entropy is 64 bytes (512 bits)"
    Mnemonic -> Either String Mnemonic
forall (m :: * -> *) a. Monad m => a -> m a
return Mnemonic
ms
  where
    (Int
cs_len, Int
remainder) = Entropy -> Int
BS.length Entropy
ent Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
4
    c :: Entropy
c = Int -> Entropy -> Entropy
calcCS Int
cs_len Entropy
ent
    indices :: [Int]
indices = Entropy -> [Int]
bsToIndices (Entropy -> [Int]) -> Entropy -> [Int]
forall a b. (a -> b) -> a -> b
$ Entropy
ent Entropy -> Entropy -> Entropy
`BS.append` Entropy
c
    ms :: Mnemonic
ms = [Mnemonic] -> Mnemonic
T.unwords ([Mnemonic] -> Mnemonic) -> [Mnemonic] -> Mnemonic
forall a b. (a -> b) -> a -> b
$ (Int -> Mnemonic) -> [Int] -> [Mnemonic]
forall a b. (a -> b) -> [a] -> [b]
map (Vector Mnemonic
wl Vector Mnemonic -> Int -> Mnemonic
forall a. Vector a -> Int -> a
!) [Int]
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 :: Mnemonic -> Either String Entropy
fromMnemonic Mnemonic
ms = do
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Mnemonic -> Bool
T.null Mnemonic
ms) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left String
"fromMnemonic: empty mnemonic"
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
word_count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
48) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ String
"fromMnemonic: too many words: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
word_count
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
word_count Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
3 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ String
"fromMnemonic: wrong number of words:" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
word_count
    Entropy
ms_bs <- [Int] -> Either String Entropy
indicesToBS ([Int] -> Either String Entropy)
-> Either String [Int] -> Either String Entropy
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Mnemonic] -> Either String [Int]
getIndices [Mnemonic]
ms_words
    let (Entropy
ms_ent, Entropy
ms_cs) = Int -> Entropy -> (Entropy, Entropy)
BS.splitAt (Int
ent_len Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4) Entropy
ms_bs
        ms_cs_num :: Integer
ms_cs_num = Int -> Entropy -> Integer
numCS Int
cs_len Entropy
ms_cs
        ent_cs_num :: Integer
ent_cs_num = Int -> Entropy -> Integer
numCS Int
cs_len (Entropy -> Integer) -> Entropy -> Integer
forall a b. (a -> b) -> a -> b
$ Int -> Entropy -> Entropy
calcCS Int
cs_len Entropy
ms_ent
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Integer
ent_cs_num Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
/= Integer
ms_cs_num) (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$
        String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ String
"fromMnemonic: checksum failed: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> Integer -> String
forall a a. (Show a, Show a) => a -> a -> String
sh Integer
ent_cs_num Integer
ms_cs_num
    Entropy -> Either String Entropy
forall (m :: * -> *) a. Monad m => a -> m a
return Entropy
ms_ent
  where
    ms_words :: [Mnemonic]
ms_words = Mnemonic -> [Mnemonic]
T.words Mnemonic
ms
    word_count :: Int
word_count = [Mnemonic] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Mnemonic]
ms_words
    (Int
ent_len, Int
cs_len) = (Int
word_count Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
11) Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
32
    sh :: a -> a -> String
sh a
cs_a a
cs_b = a -> String
forall a. Show a => a -> String
show a
cs_a String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" /= " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
cs_b

-- | Compute 'Checksum'.
calcCS :: Int -> Entropy -> Checksum
calcCS :: Int -> Entropy -> Entropy
calcCS Int
len = Int -> Entropy -> Entropy
getBits Int
len (Entropy -> Entropy) -> (Entropy -> Entropy) -> Entropy -> Entropy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Digest SHA256 -> Entropy
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert (Digest SHA256 -> Entropy)
-> (Entropy -> Digest SHA256) -> Entropy -> Entropy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SHA256 -> Entropy -> Digest SHA256
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith SHA256
SHA256

numCS :: Int -> Entropy -> Integer
numCS :: Int -> Entropy -> Integer
numCS Int
len =
    Integer -> Integer
shiftCS (Integer -> Integer) -> (Entropy -> Integer) -> Entropy -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Entropy -> Integer
bsToInteger
  where
    shiftCS :: Integer -> Integer
shiftCS = case Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
len Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 of
        Int
8 -> Integer -> Integer
forall a. a -> a
id
        Int
x -> (Integer -> Int -> Integer) -> Int -> Integer -> Integer
forall a b c. (a -> b -> c) -> b -> a -> c
flip Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftR Int
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 :: Mnemonic -> Mnemonic -> Entropy
anyToSeed Mnemonic
pf Mnemonic
ms =
    Parameters -> Entropy -> Entropy -> Entropy
forall password salt out.
(ByteArrayAccess password, ByteArrayAccess salt, ByteArray out) =>
Parameters -> password -> salt -> out
fastPBKDF2_SHA512
        Parameters
pbkdfParams
        (Mnemonic -> Entropy
E.encodeUtf8 Mnemonic
ms)
        (Entropy
"mnemonic" Entropy -> Entropy -> Entropy
forall a. Monoid a => a -> a -> a
`mappend` Mnemonic -> Entropy
E.encodeUtf8 Mnemonic
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 :: Mnemonic -> Mnemonic -> Either String Entropy
mnemonicToSeed Mnemonic
pf Mnemonic
ms = do
    Entropy
ent <- Mnemonic -> Either String Entropy
fromMnemonic Mnemonic
ms
    Mnemonic
mnm <- Entropy -> Either String Mnemonic
toMnemonic Entropy
ent
    Entropy -> Either String Entropy
forall (m :: * -> *) a. Monad m => a -> m a
return (Entropy -> Either String Entropy)
-> Entropy -> Either String Entropy
forall a b. (a -> b) -> a -> b
$ Mnemonic -> Mnemonic -> Entropy
anyToSeed Mnemonic
pf Mnemonic
mnm

-- | Get indices of words in word list.
getIndices :: [Text] -> Either String [Int]
getIndices :: [Mnemonic] -> Either String [Int]
getIndices [Mnemonic]
ws
    | [Int] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
n = [Int] -> Either String [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Int] -> Either String [Int]) -> [Int] -> Either String [Int]
forall a b. (a -> b) -> a -> b
$ [Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
i
    | Bool
otherwise = String -> Either String [Int]
forall a b. a -> Either a b
Left (String -> Either String [Int]) -> String -> Either String [Int]
forall a b. (a -> b) -> a -> b
$ String
"getIndices: words not found: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Mnemonic -> String
forall a b. ConvertibleStrings a b => a -> b
cs Mnemonic
w
  where
    i :: [Maybe Int]
i = (Mnemonic -> Maybe Int) -> [Mnemonic] -> [Maybe Int]
forall a b. (a -> b) -> [a] -> [b]
map (Mnemonic -> Map Mnemonic Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map Mnemonic Int
wl') [Mnemonic]
ws
    n :: [Int]
n = Maybe Int -> [Maybe Int] -> [Int]
forall a. Eq a => a -> [a] -> [Int]
elemIndices Maybe Int
forall a. Maybe a
Nothing [Maybe Int]
i
    w :: Mnemonic
w = [Mnemonic] -> Mnemonic
T.unwords ([Mnemonic] -> Mnemonic) -> [Mnemonic] -> Mnemonic
forall a b. (a -> b) -> a -> b
$ (Int -> Mnemonic) -> [Int] -> [Mnemonic]
forall a b. (a -> b) -> [a] -> [b]
map ([Mnemonic]
ws [Mnemonic] -> Int -> Mnemonic
forall a. [a] -> Int -> a
!!) [Int]
n

-- | Turn a list of 11-bit numbers into a 'ByteString'
indicesToBS :: [Int] -> Either String ByteString
indicesToBS :: [Int] -> Either String Entropy
indicesToBS [Int]
is = do
    Bool -> Either String () -> Either String ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
lrg (Either String () -> Either String ())
-> Either String () -> Either String ()
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left String
"indicesToBS: index larger or equal than 2048"
    Entropy -> Either String Entropy
forall (m :: * -> *) a. Monad m => a -> m a
return (Entropy -> Either String Entropy)
-> (Integer -> Entropy) -> Integer -> Either String Entropy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Entropy -> Entropy
pad (Entropy -> Entropy) -> (Integer -> Entropy) -> Integer -> Entropy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Entropy
integerToBS (Integer -> Either String Entropy)
-> Integer -> Either String Entropy
forall a b. (a -> b) -> a -> b
$ (Integer -> Int -> Integer) -> Integer -> [Int] -> Integer
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Integer -> Int -> Integer
forall a a. (Bits a, Integral a, Num a) => a -> a -> a
f Integer
0 [Int]
is Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
shift_width
  where
    lrg :: Bool
lrg = Maybe Int -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Int -> Bool) -> Maybe Int -> Bool
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> [Int] -> Maybe Int
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2048) [Int]
is
    (Int
q, Int
r) = ([Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
is Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
11) Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
8
    shift_width :: Int
shift_width =
        if Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
            then Int
0
            else Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
r
    bl :: Int
bl =
        if Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
            then Int
q
            else Int
q Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 -- length of resulting ByteString
    pad :: Entropy -> Entropy
pad Entropy
bs = Entropy -> Entropy -> Entropy
BS.append (Int -> Word8 -> Entropy
BS.replicate (Int
bl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Entropy -> Int
BS.length Entropy
bs) Word8
0x00) Entropy
bs
    f :: a -> a -> a
f a
acc a
x = (a
acc a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
11) a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x

-- | Turn a 'ByteString' into a list of 11-bit numbers.
bsToIndices :: ByteString -> [Int]
bsToIndices :: Entropy -> [Int]
bsToIndices Entropy
bs =
    [Int] -> [Int]
forall a. [a] -> [a]
reverse ([Int] -> [Int]) -> (Integer -> [Int]) -> Integer -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer -> [Int]
forall t t a.
(Integral t, Num t, Num a, Bits t, Eq t) =>
t -> t -> [a]
go Int
q (Integer -> [Int]) -> Integer -> [Int]
forall a b. (a -> b) -> a -> b
$ Entropy -> Integer
bsToInteger Entropy
bs Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
r
  where
    (Int
q, Int
r) = (Entropy -> Int
BS.length Entropy
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
11
    go :: t -> t -> [a]
go t
0 t
_ = []
    go t
n t
i = t -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (t
i t -> t -> t
forall a. Integral a => a -> a -> a
`mod` t
2048) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: t -> t -> [a]
go (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (t
i t -> Int -> t
forall a. Bits a => a -> Int -> a
`shiftR` Int
11)

wl' :: M.Map Text Int
wl' :: Map Mnemonic Int
wl' = (Int -> Mnemonic -> Map Mnemonic Int -> Map Mnemonic Int)
-> Map Mnemonic Int -> Vector Mnemonic -> Map Mnemonic Int
forall a b. (Int -> a -> b -> b) -> b -> Vector a -> b
V.ifoldr' ((Mnemonic -> Int -> Map Mnemonic Int -> Map Mnemonic Int)
-> Int -> Mnemonic -> Map Mnemonic Int -> Map Mnemonic Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Mnemonic -> Int -> Map Mnemonic Int -> Map Mnemonic Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert) Map Mnemonic Int
forall k a. Map k a
M.empty Vector Mnemonic
wl

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