-- Cryptonite.hs: shim for cryptonite -- Copyright © 2016 Clint Adams -- This software is released under the terms of the Expat license. -- (See the LICENSE file). {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PackageImports #-} {-# LANGUAGE UndecidableInstances #-} module Codec.Encryption.OpenPGP.Internal.Cryptonite ( HOWrappedCCT(..) ) where import Control.Error.Util (note) import qualified "cryptonite" Crypto.Cipher.Types as CCT import qualified Crypto.Error as CE import Data.Bifunctor (bimap) import qualified Data.ByteString as B import Codec.Encryption.OpenPGP.Internal.HOBlockCipher newtype HOWrappedCCT a = HWCCT a instance CCT.BlockCipher cipher => HOBlockCipher (HOWrappedCCT cipher) where cipherInit = bimap show HWCCT . CE.eitherCryptoError . CCT.cipherInit cipherName (HWCCT c) = CCT.cipherName c cipherKeySize (HWCCT c) = CCT.cipherKeySize c blockSize (HWCCT c) = CCT.blockSize c cfbEncrypt (HWCCT c) iv bs = hammerIV iv >>= \i -> return (CCT.cfbEncrypt c i bs) cfbDecrypt (HWCCT c) iv bs = hammerIV iv >>= \i -> return (CCT.cfbDecrypt c i bs) hammerIV :: CCT.BlockCipher cipher => B.ByteString -> Either String (CCT.IV cipher) hammerIV = note "cryptonite bad IV" . CCT.makeIV