{-# LANGUAGE ScopedTypeVariables #-}
module Data.Conduit.Crypto
(
decryptPaddedStream
, defaultChunkSize
) where
import Control.Exception (Exception, throw)
import Crypto.Classes (BlockCipher, ByteLength, IV, blockSizeBytes)
import Crypto.Padding (unpadPKCS5safe)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.ByteString.Builder.Extra (defaultChunkSize)
import qualified Data.ByteString.Lazy as BL
import Data.Conduit (ConduitT, yield)
import qualified Data.Conduit.Binary as CB
import Data.Tagged (Tagged, untag)
decryptPaddedStream
:: forall e cipher m.
Exception e
=> BlockCipher cipher
=> Monad m
=> e
-> Int
-> (IV cipher -> ByteString -> (ByteString, IV cipher))
-> IV cipher
-> ConduitT ByteString ByteString m ()
decryptPaddedStream paddingError chunkSize decrypt = go BS.empty
where
go :: ByteString -> IV cipher -> ConduitT ByteString ByteString m ()
go lastBlock currentIv = do
(currentBlock, nextIv) <- decrypt currentIv . BL.toStrict <$> CB.take actualBlockSize
if BS.length currentBlock < actualBlockSize
then
case unpadPKCS5safe (lastBlock `BS.append` currentBlock) of
Just unpadded ->
yield unpadded
Nothing ->
throw paddingError
else do
yield lastBlock
go currentBlock nextIv
actualBlockSize :: Int
actualBlockSize = ((chunkSize `div` cipherBlockSize) * cipherBlockSize) `max` cipherBlockSize
cipherBlockSize :: Int
cipherBlockSize = untag (blockSizeBytes :: Tagged cipher ByteLength)