module Data.CryptoID.Poly
( CryptoID(..)
, CryptoIDKey
, genKey
, encrypt
, decrypt
, CryptoIDError(..)
, CryptoCipher, CryptoHash
) where
import Data.CryptoID
import Data.Binary
import Data.Binary.Put
import Data.Binary.Get
import Data.ByteString (ByteString)
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Char8 as ByteString.Char
import qualified Data.ByteString.Lazy as Lazy (ByteString)
import Data.List (sortOn)
import Data.Ord (Down(..))
import Data.ByteArray (ByteArrayAccess)
import qualified Data.ByteArray as ByteArray
import Data.Foldable (asum)
import Control.Monad.Except
import Control.Exception
import Data.Typeable
import GHC.TypeLits
import Crypto.Cipher.Types
import Crypto.Cipher.Blowfish (Blowfish)
import Crypto.Hash (hash, Digest)
import Crypto.Hash.Algorithms (SHAKE128)
import Crypto.Error
import Crypto.Random.Entropy
type CryptoCipher = Blowfish
type CryptoHash = SHAKE128 64
newtype CryptoIDKey = CryptoIDKey { keyMaterial :: ByteString }
deriving (Typeable, ByteArrayAccess)
instance Show CryptoIDKey where
show = show . typeOf
instance Binary CryptoIDKey where
put = putByteString . keyMaterial
get = CryptoIDKey <$> getKey (cipherKeySize cipher)
where
cipher :: CryptoCipher
cipher = undefined
getKey (KeySizeFixed n) = getByteString n
getKey (KeySizeEnum ns) = asum [ getKey $ KeySizeFixed n | n <- sortOn Down ns ]
getKey (KeySizeRange min max) = getKey $ KeySizeEnum [max .. min]
data CryptoIDError
= AlgorithmError CryptoError
| NamespaceHashIsWrongLength ByteString
| CiphertextConversionFailed
| DeserializationError (Lazy.ByteString, ByteOffset, String)
| InvalidNamespaceDetected
deriving (Show, Eq)
instance Exception CryptoIDError
genKey :: MonadIO m => m CryptoIDKey
genKey = CryptoIDKey <$> liftIO (getEntropy keySize)
where
keySize' = cipherKeySize (undefined :: CryptoCipher)
keySize
| KeySizeFixed n <- keySize' = n
| KeySizeEnum ns <- keySize' = maximum ns
| KeySizeRange _ max <- keySize' = max
pad :: ByteArrayAccess a => Int -> a -> ByteString
pad n (ByteArray.unpack -> src) = ByteString.pack $ src ++ replicate (l `mod` n) 0
where
l = length src
namespace' :: forall proxy namespace m.
( KnownSymbol namespace, MonadError CryptoIDError m
) => proxy namespace -> m (IV CryptoCipher)
namespace' p = case makeIV namespaceHash of
Nothing -> throwError . NamespaceHashIsWrongLength $ ByteArray.convert namespaceHash
Just iv -> return iv
where
namespaceHash :: Digest CryptoHash
namespaceHash = hash . ByteString.Char.pack $ symbolVal p
cryptoFailable :: MonadError CryptoIDError m => CryptoFailable a -> m a
cryptoFailable = either (throwError . AlgorithmError) return . eitherCryptoError
encrypt :: forall m namespace.
( KnownSymbol namespace
, MonadError CryptoIDError m
) => CryptoIDKey -> ByteString -> m (CryptoID namespace ByteString)
encrypt (keyMaterial -> key) plaintext = do
cipher <- cryptoFailable (cipherInit key :: CryptoFailable CryptoCipher)
namespace <- namespace' (Proxy :: Proxy namespace)
return . CryptoID . cbcEncrypt cipher namespace $ pad (blockSize cipher) plaintext
decrypt :: forall m namespace.
( KnownSymbol namespace
, MonadError CryptoIDError m
) => CryptoIDKey -> CryptoID namespace ByteString -> m ByteString
decrypt (keyMaterial -> key) CryptoID{..} = do
cipher <- cryptoFailable (cipherInit key :: CryptoFailable CryptoCipher)
namespace <- namespace' (Proxy :: Proxy namespace)
return $ cbcDecrypt cipher namespace ciphertext