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