{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Crypto.Ethereum.Keyfile
(
EncryptedKey(..)
, Cipher(..)
, Kdf(..)
, decrypt
, encrypt
) where
import Crypto.Cipher.AES (AES128)
import Crypto.Cipher.Types (IV, cipherInit, ctrCombine, makeIV)
import Crypto.Error (throwCryptoError)
import qualified Crypto.KDF.PBKDF2 as Pbkdf2 (Parameters (..),
fastPBKDF2_SHA256)
import qualified Crypto.KDF.Scrypt as Scrypt (Parameters (..), generate)
import Crypto.Random (MonadRandom (getRandomBytes))
import Data.Aeson (FromJSON (..), ToJSON (..), Value,
object, withObject, (.:), (.=))
import Data.Aeson.Types (Parser)
import Data.ByteArray (ByteArray, ByteArrayAccess, convert)
import qualified Data.ByteArray as BA (drop, take, unpack)
import Data.Maybe (fromJust)
import Data.Text (Text)
import Data.UUID.Types (UUID)
import Data.UUID.Types.Internal (buildFromBytes)
import Crypto.Ethereum.Utils (keccak256)
import Data.ByteArray.HexString (HexString)
data Kdf = Pbkdf2 !Pbkdf2.Parameters !HexString
| Scrypt !Scrypt.Parameters !HexString
data Cipher = Aes128Ctr
{ Cipher -> IV AES128
cipherIv :: !(IV AES128)
, Cipher -> HexString
cipherText :: !HexString
}
data EncryptedKey = EncryptedKey
{ EncryptedKey -> UUID
encryptedKeyId :: !UUID
, EncryptedKey -> Int
encryptedKeyVersion :: !Int
, EncryptedKey -> Cipher
encryptedKeyCipher :: !Cipher
, EncryptedKey -> Kdf
encryptedKeyKdf :: !Kdf
, EncryptedKey -> HexString
encryptedKeyMac :: !HexString
}
instance Eq EncryptedKey where
EncryptedKey
a == :: EncryptedKey -> EncryptedKey -> Bool
== EncryptedKey
b = EncryptedKey -> UUID
encryptedKeyId EncryptedKey
a UUID -> UUID -> Bool
forall a. Eq a => a -> a -> Bool
== EncryptedKey -> UUID
encryptedKeyId EncryptedKey
b
instance Show EncryptedKey where
show :: EncryptedKey -> String
show EncryptedKey{Int
HexString
UUID
Cipher
Kdf
encryptedKeyMac :: HexString
encryptedKeyKdf :: Kdf
encryptedKeyCipher :: Cipher
encryptedKeyVersion :: Int
encryptedKeyId :: UUID
encryptedKeyMac :: EncryptedKey -> HexString
encryptedKeyKdf :: EncryptedKey -> Kdf
encryptedKeyCipher :: EncryptedKey -> Cipher
encryptedKeyVersion :: EncryptedKey -> Int
encryptedKeyId :: EncryptedKey -> UUID
..} = String
"EncryptedKey " String -> ShowS
forall a. [a] -> [a] -> [a]
++ UUID -> String
forall a. Show a => a -> String
show UUID
encryptedKeyId
instance FromJSON EncryptedKey where
parseJSON :: Value -> Parser EncryptedKey
parseJSON = Value -> Parser EncryptedKey
encryptedKeyParser
instance ToJSON EncryptedKey where
toJSON :: EncryptedKey -> Value
toJSON = EncryptedKey -> Value
encryptedKeyBuilder
encryptedKeyBuilder :: EncryptedKey -> Value
encryptedKeyBuilder :: EncryptedKey -> Value
encryptedKeyBuilder EncryptedKey{Int
HexString
UUID
Cipher
Kdf
encryptedKeyMac :: HexString
encryptedKeyKdf :: Kdf
encryptedKeyCipher :: Cipher
encryptedKeyVersion :: Int
encryptedKeyId :: UUID
encryptedKeyMac :: EncryptedKey -> HexString
encryptedKeyKdf :: EncryptedKey -> Kdf
encryptedKeyCipher :: EncryptedKey -> Cipher
encryptedKeyVersion :: EncryptedKey -> Int
encryptedKeyId :: EncryptedKey -> UUID
..} = [Pair] -> Value
object
[ Text
"id" Text -> UUID -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= UUID
encryptedKeyId
, Text
"version" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
encryptedKeyVersion
, Text
"crypto" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object
[ Text
"cipher" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Cipher -> Text
cipherName Cipher
encryptedKeyCipher
, Text
"cipherparams" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Cipher -> Value
cipherParams Cipher
encryptedKeyCipher
, Text
"ciphertext" Text -> HexString -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Cipher -> HexString
cipherText Cipher
encryptedKeyCipher
, Text
"kdf" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Kdf -> Text
kdfName Kdf
encryptedKeyKdf
, Text
"kdfparams" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Kdf -> Value
kdfParams Kdf
encryptedKeyKdf
, Text
"mac" Text -> HexString -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HexString
encryptedKeyMac
]
]
where
cipherName :: Cipher -> Text
cipherName :: Cipher -> Text
cipherName Aes128Ctr{IV AES128
HexString
cipherText :: HexString
cipherIv :: IV AES128
cipherText :: Cipher -> HexString
cipherIv :: Cipher -> IV AES128
..} = Text
"aes-128-ctr"
cipherParams :: Cipher -> Value
cipherParams :: Cipher -> Value
cipherParams Aes128Ctr{IV AES128
HexString
cipherText :: HexString
cipherIv :: IV AES128
cipherText :: Cipher -> HexString
cipherIv :: Cipher -> IV AES128
..} = [Pair] -> Value
object [ Text
"iv" Text -> HexString -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (IV AES128 -> HexString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert IV AES128
cipherIv :: HexString) ]
kdfName :: Kdf -> Text
kdfName :: Kdf -> Text
kdfName = \case
Pbkdf2 Parameters
_ HexString
_ -> Text
"pbkdf2"
Scrypt Parameters
_ HexString
_ -> Text
"scrypt"
kdfParams :: Kdf -> Value
kdfParams :: Kdf -> Value
kdfParams = \case
Pbkdf2 Parameters
params HexString
salt ->
[Pair] -> Value
object [ Text
"salt" Text -> HexString -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HexString
salt
, Text
"dklen" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Parameters -> Int
Pbkdf2.outputLength Parameters
params
, Text
"c" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Parameters -> Int
Pbkdf2.iterCounts Parameters
params
]
Scrypt Parameters
params HexString
salt ->
[Pair] -> Value
object [ Text
"salt" Text -> HexString -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HexString
salt
, Text
"dklen" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Parameters -> Int
Scrypt.outputLength Parameters
params
, Text
"p" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Parameters -> Int
Scrypt.p Parameters
params
, Text
"r" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Parameters -> Int
Scrypt.r Parameters
params
, Text
"n" Text -> Word64 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Parameters -> Word64
Scrypt.n Parameters
params
]
encryptedKeyParser :: Value -> Parser EncryptedKey
encryptedKeyParser :: Value -> Parser EncryptedKey
encryptedKeyParser = String
-> (Object -> Parser EncryptedKey) -> Value -> Parser EncryptedKey
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"EncryptedKey" ((Object -> Parser EncryptedKey) -> Value -> Parser EncryptedKey)
-> (Object -> Parser EncryptedKey) -> Value -> Parser EncryptedKey
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
UUID
uuid <- Object
v Object -> Text -> Parser UUID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Int
version <- Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"version"
Value
crypto <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"crypto"
Cipher
cipher <- Value -> Parser Cipher
parseCipher Value
crypto
Kdf
kdf <- Value -> Parser Kdf
parseKdf Value
crypto
HexString
mac <- String -> (Object -> Parser HexString) -> Value -> Parser HexString
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Crypto" (Object -> Text -> Parser HexString
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"mac") Value
crypto
EncryptedKey -> Parser EncryptedKey
forall (m :: * -> *) a. Monad m => a -> m a
return (EncryptedKey -> Parser EncryptedKey)
-> EncryptedKey -> Parser EncryptedKey
forall a b. (a -> b) -> a -> b
$ UUID -> Int -> Cipher -> Kdf -> HexString -> EncryptedKey
EncryptedKey UUID
uuid Int
version Cipher
cipher Kdf
kdf HexString
mac
parseCipher :: Value -> Parser Cipher
parseCipher :: Value -> Parser Cipher
parseCipher = String -> (Object -> Parser Cipher) -> Value -> Parser Cipher
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Cipher" ((Object -> Parser Cipher) -> Value -> Parser Cipher)
-> (Object -> Parser Cipher) -> Value -> Parser Cipher
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Text
name <- Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"cipher"
case Text
name :: Text of
Text
"aes-128-ctr" -> do
Object
params <- Object
v Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"cipherparams"
HexString
hexiv <- Object
params Object -> Text -> Parser HexString
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"iv"
HexString
text <- Object
v Object -> Text -> Parser HexString
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ciphertext"
case HexString -> Maybe (IV AES128)
forall b c. (ByteArrayAccess b, BlockCipher c) => b -> Maybe (IV c)
makeIV (HexString
hexiv :: HexString) of
Just IV AES128
iv -> Cipher -> Parser Cipher
forall (m :: * -> *) a. Monad m => a -> m a
return (IV AES128 -> HexString -> Cipher
Aes128Ctr IV AES128
iv HexString
text)
Maybe (IV AES128)
Nothing -> String -> Parser Cipher
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Cipher) -> String -> Parser Cipher
forall a b. (a -> b) -> a -> b
$ String
"Unable to make IV from " String -> ShowS
forall a. [a] -> [a] -> [a]
++ HexString -> String
forall a. Show a => a -> String
show HexString
hexiv
Text
_ -> String -> Parser Cipher
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Cipher) -> String -> Parser Cipher
forall a b. (a -> b) -> a -> b
$ Text -> String
forall a. Show a => a -> String
show Text
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not implemented yet"
parseKdf :: Value -> Parser Kdf
parseKdf :: Value -> Parser Kdf
parseKdf = String -> (Object -> Parser Kdf) -> Value -> Parser Kdf
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Kdf" ((Object -> Parser Kdf) -> Value -> Parser Kdf)
-> (Object -> Parser Kdf) -> Value -> Parser Kdf
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Text
name <- Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"kdf"
Object
params <- Object
v Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"kdfparams"
Int
dklen <- Object
params Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"dklen"
HexString
salt <- Object
params Object -> Text -> Parser HexString
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"salt"
case Text
name :: Text of
Text
"pbkdf2" -> do
Int
iterations <- Object
params Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"c"
Text
prf <- Object
params Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"prf"
case Text
prf :: Text of
Text
"hmac-sha256" -> Kdf -> Parser Kdf
forall (m :: * -> *) a. Monad m => a -> m a
return (Kdf -> Parser Kdf) -> Kdf -> Parser Kdf
forall a b. (a -> b) -> a -> b
$ Parameters -> HexString -> Kdf
Pbkdf2 (Int -> Int -> Parameters
Pbkdf2.Parameters Int
iterations Int
dklen) HexString
salt
Text
_ -> String -> Parser Kdf
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Kdf) -> String -> Parser Kdf
forall a b. (a -> b) -> a -> b
$ Text -> String
forall a. Show a => a -> String
show Text
prf String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not implemented yet"
Text
"scrypt" -> do
Int
p <- Object
params Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"p"
Int
r <- Object
params Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"r"
Word64
n <- Object
params Object -> Text -> Parser Word64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"n"
Kdf -> Parser Kdf
forall (m :: * -> *) a. Monad m => a -> m a
return (Kdf -> Parser Kdf) -> Kdf -> Parser Kdf
forall a b. (a -> b) -> a -> b
$ Parameters -> HexString -> Kdf
Scrypt (Word64 -> Int -> Int -> Int -> Parameters
Scrypt.Parameters Word64
n Int
r Int
p Int
dklen) HexString
salt
Text
_ -> String -> Parser Kdf
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Kdf) -> String -> Parser Kdf
forall a b. (a -> b) -> a -> b
$ Text -> String
forall a. Show a => a -> String
show Text
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not implemented yet"
defaultKdf :: HexString -> Kdf
defaultKdf :: HexString -> Kdf
defaultKdf = Parameters -> HexString -> Kdf
Scrypt (Word64 -> Int -> Int -> Int -> Parameters
Scrypt.Parameters Word64
n Int
r Int
p Int
dklen)
where
dklen :: Int
dklen = Int
32
n :: Word64
n = Word64
262144
r :: Int
r = Int
1
p :: Int
p = Int
8
deriveKey :: (ByteArrayAccess password, ByteArray ba) => Kdf -> password -> ba
deriveKey :: Kdf -> password -> ba
deriveKey Kdf
kdf password
password =
case Kdf
kdf of
Pbkdf2 Parameters
params HexString
salt -> Parameters -> password -> HexString -> ba
forall password salt out.
(ByteArrayAccess password, ByteArrayAccess salt, ByteArray out) =>
Parameters -> password -> salt -> out
Pbkdf2.fastPBKDF2_SHA256 Parameters
params password
password HexString
salt
Scrypt Parameters
params HexString
salt -> Parameters -> password -> HexString -> ba
forall password salt output.
(ByteArrayAccess password, ByteArrayAccess salt,
ByteArray output) =>
Parameters -> password -> salt -> output
Scrypt.generate Parameters
params password
password HexString
salt
decrypt :: (ByteArrayAccess password, ByteArray privateKey)
=> EncryptedKey
-> password
-> Maybe privateKey
decrypt :: EncryptedKey -> password -> Maybe privateKey
decrypt EncryptedKey{Int
HexString
UUID
Cipher
Kdf
encryptedKeyMac :: HexString
encryptedKeyKdf :: Kdf
encryptedKeyCipher :: Cipher
encryptedKeyVersion :: Int
encryptedKeyId :: UUID
encryptedKeyMac :: EncryptedKey -> HexString
encryptedKeyKdf :: EncryptedKey -> Kdf
encryptedKeyCipher :: EncryptedKey -> Cipher
encryptedKeyVersion :: EncryptedKey -> Int
encryptedKeyId :: EncryptedKey -> UUID
..} password
password
| HexString
mac HexString -> HexString -> Bool
forall a. Eq a => a -> a -> Bool
== HexString
encryptedKeyMac = privateKey -> Maybe privateKey
forall a. a -> Maybe a
Just (HexString -> privateKey
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert HexString
privateKey)
| Bool
otherwise = Maybe privateKey
forall a. Maybe a
Nothing
where
privateKey :: HexString
privateKey = AES128 -> IV AES128 -> HexString -> HexString
forall cipher ba.
(BlockCipher cipher, ByteArray ba) =>
cipher -> IV cipher -> ba -> ba
ctrCombine AES128
cipher IV AES128
iv HexString
ciphertext
cipher :: AES128
cipher = CryptoFailable AES128 -> AES128
forall a. CryptoFailable a -> a
throwCryptoError (CryptoFailable AES128 -> AES128)
-> CryptoFailable AES128 -> AES128
forall a b. (a -> b) -> a -> b
$ HexString -> CryptoFailable AES128
forall cipher key.
(Cipher cipher, ByteArray key) =>
key -> CryptoFailable cipher
cipherInit (Int -> HexString -> HexString
forall bs. ByteArray bs => Int -> bs -> bs
BA.take Int
16 HexString
derivedKey) :: AES128
derivedKey :: HexString
derivedKey = Kdf -> password -> HexString
forall password ba.
(ByteArrayAccess password, ByteArray ba) =>
Kdf -> password -> ba
deriveKey Kdf
encryptedKeyKdf password
password
ciphertext :: HexString
ciphertext = Cipher -> HexString
cipherText Cipher
encryptedKeyCipher
mac :: HexString
mac = HexString -> HexString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
keccak256 (Int -> HexString -> HexString
forall bs. ByteArray bs => Int -> bs -> bs
BA.drop Int
16 HexString
derivedKey HexString -> HexString -> HexString
forall a. Semigroup a => a -> a -> a
<> HexString
ciphertext)
iv :: IV AES128
iv = Cipher -> IV AES128
cipherIv Cipher
encryptedKeyCipher
encrypt :: (ByteArray privateKey, ByteArrayAccess password, MonadRandom m)
=> privateKey
-> password
-> m EncryptedKey
encrypt :: privateKey -> password -> m EncryptedKey
encrypt privateKey
privateKey password
password = do
Kdf
kdf <- HexString -> Kdf
defaultKdf (HexString -> Kdf) -> m HexString -> m Kdf
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m HexString
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
16
IV AES128
iv <- m (IV AES128)
randomIV
let derivedKey :: privateKey
derivedKey = Kdf -> password -> privateKey
forall password ba.
(ByteArrayAccess password, ByteArray ba) =>
Kdf -> password -> ba
deriveKey Kdf
kdf password
password
cipher :: AES128
cipher = CryptoFailable AES128 -> AES128
forall a. CryptoFailable a -> a
throwCryptoError (CryptoFailable AES128 -> AES128)
-> CryptoFailable AES128 -> AES128
forall a b. (a -> b) -> a -> b
$ privateKey -> CryptoFailable AES128
forall cipher key.
(Cipher cipher, ByteArray key) =>
key -> CryptoFailable cipher
cipherInit (Int -> privateKey -> privateKey
forall bs. ByteArray bs => Int -> bs -> bs
BA.take Int
16 privateKey
derivedKey) :: AES128
ciphertext :: privateKey
ciphertext = AES128 -> IV AES128 -> privateKey -> privateKey
forall cipher ba.
(BlockCipher cipher, ByteArray ba) =>
cipher -> IV cipher -> ba -> ba
ctrCombine AES128
cipher IV AES128
iv privateKey
privateKey
mac :: HexString
mac = privateKey -> HexString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
keccak256 (Int -> privateKey -> privateKey
forall bs. ByteArray bs => Int -> bs -> bs
BA.drop Int
16 privateKey
derivedKey privateKey -> privateKey -> privateKey
forall a. Semigroup a => a -> a -> a
<> privateKey
ciphertext)
UUID
uuid <- m UUID
randomUUID
EncryptedKey -> m EncryptedKey
forall (m :: * -> *) a. Monad m => a -> m a
return (EncryptedKey -> m EncryptedKey) -> EncryptedKey -> m EncryptedKey
forall a b. (a -> b) -> a -> b
$ UUID -> Int -> Cipher -> Kdf -> HexString -> EncryptedKey
EncryptedKey UUID
uuid Int
3 (IV AES128 -> HexString -> Cipher
Aes128Ctr IV AES128
iv (HexString -> Cipher) -> HexString -> Cipher
forall a b. (a -> b) -> a -> b
$ privateKey -> HexString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert privateKey
ciphertext) Kdf
kdf HexString
mac
where
randomUUID :: m UUID
randomUUID = do
HexString
uuid <- Int -> m HexString
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
16
let bs :: [Word8]
bs = HexString -> [Word8]
forall a. ByteArrayAccess a => a -> [Word8]
BA.unpack (HexString
uuid :: HexString)
UUID -> m UUID
forall (m :: * -> *) a. Monad m => a -> m a
return (UUID -> m UUID) -> UUID -> m UUID
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
buildFromBytes Word8
4
([Word8] -> Word8
forall a. [a] -> a
head [Word8]
bs) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
1) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
2) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
3)
([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
4) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
5) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
6) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
7)
([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
8) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
9) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
10) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
11)
([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
12) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
13) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
14) ([Word8]
bs [Word8] -> Int -> Word8
forall a. [a] -> Int -> a
!! Int
15)
randomIV :: m (IV AES128)
randomIV = do
HexString
iv <- Int -> m HexString
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
16
IV AES128 -> m (IV AES128)
forall (m :: * -> *) a. Monad m => a -> m a
return (IV AES128 -> m (IV AES128)) -> IV AES128 -> m (IV AES128)
forall a b. (a -> b) -> a -> b
$ Maybe (IV AES128) -> IV AES128
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (IV AES128) -> IV AES128) -> Maybe (IV AES128) -> IV AES128
forall a b. (a -> b) -> a -> b
$ HexString -> Maybe (IV AES128)
forall b c. (ByteArrayAccess b, BlockCipher c) => b -> Maybe (IV c)
makeIV (HexString
iv :: HexString)