<div dir="ltr">Hi,<div><br></div><div>I can't think of a terribly good way to achieve GPG/PGP-compatibility without simply using GPG/PGP, since the file format is quite involved.</div><div><br></div><div>That said, here is how to implement a CBC-mode block cipher encryption using Conduit, which is suitable for something like AES256 encryption. It is almost certainly vulnerable to side-channel attacks (timing, cache-poisoning, etc) but as a pure function from input to output it is equivalent to `openssl aes-256-cbc -e -K <KEY-IN-HEX> -iv <IV-IN-HEX> -in data/plain-text.txt` which I should hope would be standard enough for analysis.</div><div><br></div><div>This leaves you with the problem of storing the key and IV securely, encrypted using the asymmetric key that you first thought of, but hopefully that problem is surmountable!</div><div><br></div><div>Cheers,</div><div><br></div><div>David</div><div><br></div><div><br></div><div><br></div><div><br></div><div><br></div><div><div>import           Control.Monad</div><div>import           Control.Monad.IO.Class</div><div>import           Control.Monad.Trans.Resource</div><div>import           Crypto.Cipher.AES</div><div>import           Crypto.Cipher.Types</div><div>import           Crypto.Data.Padding</div><div>import           Crypto.Error</div><div>import qualified Data.ByteString              as B</div><div>import           Data.Conduit</div><div>import           Data.Conduit.Binary</div><div>import           Data.Monoid</div><div><br></div><div>loadKey :: IO B.ByteString</div><div>loadKey = B.readFile "data/key.dat"</div><div><br></div><div>loadIV :: IO (IV AES256)</div><div>loadIV = do</div><div>  bytes <- B.readFile "data/iv.dat"</div><div>  maybe (error "makeIV failed") return $ makeIV bytes</div><div><br></div><div>loadCipher :: IO AES256</div><div>loadCipher = throwCryptoErrorIO =<< cipherInit <$> loadKey</div><div><br></div><div>loadPlainText :: IO B.ByteString</div><div>loadPlainText = B.readFile "data/plain-text.txt"</div><div><br></div><div>encryptConduit :: (BlockCipher c, Monad m) => c -> IV c -> B.ByteString -> Conduit B.ByteString m B.ByteString</div><div>encryptConduit cipher iv partialBlock = await >>= \case</div><div>  Nothing -> yield $ cbcEncrypt cipher iv $ pad (PKCS7 (blockSize cipher)) partialBlock</div><div>  Just moreBytes -> let</div><div>          fullBlocks           = (B.length moreBytes + B.length partialBlock) `div` blockSize cipher</div><div>          (thisTime, nextTime) = B.splitAt (fullBlocks * blockSize cipher) (partialBlock <> moreBytes)</div><div>    in do</div><div>      iv' <- if B.null thisTime then return iv else do</div><div>        let cipherText            = cbcEncrypt cipher iv thisTime</div><div>            lastBlockOfCipherText = B.drop (B.length cipherText - blockSize cipher) cipherText</div><div>        yield cipherText</div><div>        maybe (error "makeIV failed") return $ makeIV lastBlockOfCipherText</div><div>      encryptConduit cipher iv' nextTime</div><div><br></div><div>go :: IO ()</div><div>go = do</div><div>  c <- loadCipher</div><div>  iv <- loadIV</div><div>  pt <- loadPlainText</div><div>  let padded = pad (PKCS7 (blockSize c)) $ pt</div><div>      encrypted = cbcEncrypt c iv padded</div><div>  B.writeFile "data/haskell-oneshot.dat" encrypted</div><div><br></div><div>  runResourceT $ runConduit</div><div>     $  sourceFile "data/plain-text.txt"</div><div>    =$= encryptConduit c iv mempty</div><div>    =$= sinkFile   "data/haskell-streaming.dat"</div></div><div><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On 6 July 2017 at 23:29, Ivan Lazar Miljenovic <span dir="ltr"><<a href="mailto:ivan.miljenovic@gmail.com" target="_blank">ivan.miljenovic@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><span class="">On 7 July 2017 at 01:44, Viktor Dukhovni <<a href="mailto:ietf-dane@dukhovni.org">ietf-dane@dukhovni.org</a>> wrote:<br>
><br>
>> On Jul 6, 2017, at 12:58 AM, Ivan Lazar Miljenovic <<a href="mailto:ivan.miljenovic@gmail.com">ivan.miljenovic@gmail.com</a>> wrote:<br>
>><br>
>> I have a use case for needing to use public key cryptography to<br>
>> encrypt a large amount of data in a streaming fashion (get it out of a<br>
>> DB, encrypt, put into an AWS S3 bucket).<br>
><br>
> What are the data-format requirements?  Do you need (binary) CMS output?<br>
> GPG-compatible output?  Or just roll your own?<br>
<br>
</span>The intent is to be able to transfer data between two parties such<br>
that only the recipient is able to view it (hence the usage of public<br>
key cryptography).  GPG/PGP compatability is preferable as it's<br>
common, but anything that is sufficiently standardised (as this will<br>
potentially be used by others that aren't me doing so with Haskell and<br>
thus can't just use a library to do so) will suffice.<br>
<br>
(The other advantage of GPG/PGP is that the security testing team is<br>
more familiar with it and thus likely to sign off on it.)<br>
<span class=""><br>
><br>
> Integrity protection can be tricky with large data streams.  Most data<br>
> formats for enveloped data have a single MAC at the end, which means<br>
> that the decoder has to consume all the data before it is known to be<br>
> valid!<br>
><br>
> So if you're in a position to avoid a standard all-in-one format, it<br>
> makes sense to "packetize" the stream, with integrity protection for<br>
> each "packet", and packet sequence numbers to preserve overall stream<br>
> integrity.  With vast amounts of data, you'll want to be careful with<br>
> the symmetric cipher modes, AEAD (AES-GCM, for example) protects only<br>
> a limited amount of data before you need to rekey.  It may be simplest<br>
> to just generate a new symmetric key for every N megabytes of data.<br>
><br>
> With a careful design of the "packet" format, you can use in-memory<br>
> crypto for each packet.  Don't forget to include an "end-of-stream"<br>
> packet to defeat truncation attacks.<br>
<br>
</span>This sounds good in theory, but in practice I'm not versed enough in<br>
security to want to try and roll my own if I could avoid it, and<br>
trying to document such a format for others to use could be<br>
problematic.allowed to post.<br>
<span class="im HOEnZb"><br>
--<br>
Ivan Lazar Miljenovic<br>
<a href="mailto:Ivan.Miljenovic@gmail.com">Ivan.Miljenovic@gmail.com</a><br>
<a href="http://IvanMiljenovic.wordpress.com" rel="noreferrer" target="_blank">http://IvanMiljenovic.<wbr>wordpress.com</a><br>
</span><div class="HOEnZb"><div class="h5">______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</div></div></blockquote></div><br></div>