module OpenSSL.EVP.Cipher
( Cipher
, getCipherByName
, getCipherNames
, CryptoMode(..)
, cipher
, cipherBS
, cipherLBS
, cipherStrictLBS
)
where
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy.Char8 as L8
import Foreign
import Foreign.C
import OpenSSL.Objects
import OpenSSL.Utils
import OpenSSL.EVP.Internal
foreign import ccall unsafe "EVP_get_cipherbyname"
_get_cipherbyname :: CString -> IO (Ptr EVP_CIPHER)
getCipherByName :: String -> IO (Maybe Cipher)
getCipherByName name
= withCString name $ \ namePtr ->
do ptr <- _get_cipherbyname namePtr
if ptr == nullPtr then
return Nothing
else
return $ Just $ Cipher ptr
getCipherNames :: IO [String]
getCipherNames = getObjNames CipherMethodType True
data CryptoMode = Encrypt | Decrypt
cryptoModeToInt :: CryptoMode -> CInt
cryptoModeToInt Encrypt = 1
cryptoModeToInt Decrypt = 0
foreign import ccall unsafe "EVP_CipherInit"
_CipherInit :: Ptr EVP_CIPHER_CTX -> Ptr EVP_CIPHER -> CString -> CString -> CInt -> IO CInt
cipherInit :: Cipher -> String -> String -> CryptoMode -> IO CipherCtx
cipherInit (Cipher c) key iv mode
= do ctx <- newCipherCtx
withCipherCtxPtr ctx $ \ ctxPtr ->
withCString key $ \ keyPtr ->
withCString iv $ \ ivPtr ->
_CipherInit ctxPtr c keyPtr ivPtr (cryptoModeToInt mode)
>>= failIf_ (/= 1)
return ctx
cipherStrictLBS :: Cipher
-> B8.ByteString
-> B8.ByteString
-> CryptoMode
-> L8.ByteString
-> IO L8.ByteString
cipherStrictLBS (Cipher c) key iv mode input =
withNewCipherCtxPtr $ \cptr ->
unsafeUseAsCStringLen key $ \(keyp,_) ->
unsafeUseAsCStringLen iv $ \(ivp, _) -> do
failIf_ (/= 1) =<< _CipherInit cptr c keyp ivp (cryptoModeToInt mode)
cc <- fmap CipherCtx (newForeignPtr_ cptr)
rr <- cipherUpdateBS cc `mapM` L8.toChunks input
rf <- cipherFinalBS cc
return $ L8.fromChunks (rr++[rf])
cipher :: Cipher
-> String
-> String
-> CryptoMode
-> String
-> IO String
cipher c key iv mode input
= fmap L8.unpack $ cipherLBS c key iv mode $ L8.pack input
cipherBS :: Cipher
-> String
-> String
-> CryptoMode
-> B8.ByteString
-> IO B8.ByteString
cipherBS c key iv mode input
= do ctx <- cipherInit c key iv mode
cipherStrictly ctx input
cipherLBS :: Cipher
-> String
-> String
-> CryptoMode
-> L8.ByteString
-> IO L8.ByteString
cipherLBS c key iv mode input
= do ctx <- cipherInit c key iv mode
cipherLazily ctx input