[ANNOUNCE] First release of crypto-conduit

Hello! I'm pleased to announce the first release of crypto-conduit [1]! The crypto-api [2] package provides APIs for many cryptographic operations, such as cryptographic hashes and block ciphers. This new crypto-conduit package allows you to use many of these operations with conduits [3], giving you safe I/O using constant memory and no leaks. As an example, here's how you could get the SHA1 hash a file: import Crypto.Conduit -- from crypto-conduit import Crypto.Hash.SHA1 (SHA1) -- from cryptohash import Data.Conduit -- from conduit import Data.Conduit.Binary (sourceFile) -- from conduit main = do hash <- runResourceT $ sourceFile "my-file" $$ sinkHash print (hash :: SHA1) The code snippet above, despite having only "sourceFile ... $$ sinkHash" on its core, guarantees that the file handle is not kept open and uses a constant amount of memory. Sweet! Please break this package! Although it comes with a test suite, it has just seen the light of the day. Cheers, =) [1] http://hackage.haskell.org/package/crypto-conduit [2] http://hackage.haskell.org/package/crypto-api [3] http://hackage.haskell.org/package/conduit -- Felipe.

great! I am wondering if you can provide even higher-level APIs for the common case: hash <- runResourceT $ hashFile "my-file" and possibly something that runs the ResourceT transformer: hash <- runHashFile "my-file" On Sat, Jan 7, 2012 at 12:16 AM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
Hello!
I'm pleased to announce the first release of crypto-conduit [1]! The crypto-api [2] package provides APIs for many cryptographic operations, such as cryptographic hashes and block ciphers. This new crypto-conduit package allows you to use many of these operations with conduits [3], giving you safe I/O using constant memory and no leaks.
As an example, here's how you could get the SHA1 hash a file:
import Crypto.Conduit -- from crypto-conduit import Crypto.Hash.SHA1 (SHA1) -- from cryptohash import Data.Conduit -- from conduit import Data.Conduit.Binary (sourceFile) -- from conduit
main = do hash <- runResourceT $ sourceFile "my-file" $$ sinkHash print (hash :: SHA1)
The code snippet above, despite having only "sourceFile ... $$ sinkHash" on its core, guarantees that the file handle is not kept open and uses a constant amount of memory. Sweet!
Please break this package! Although it comes with a test suite, it has just seen the light of the day.
Cheers, =)
[1] http://hackage.haskell.org/package/crypto-conduit [2] http://hackage.haskell.org/package/crypto-api [3] http://hackage.haskell.org/package/conduit
-- Felipe.
_______________________________________________ web-devel mailing list web-devel@haskell.org http://www.haskell.org/mailman/listinfo/web-devel

On Sat, Jan 7, 2012 at 8:06 AM, Greg Weber
I am wondering if you can provide even higher-level APIs for the common case:
hash <- runResourceT $ hashFile "my-file"
and possibly something that runs the ResourceT transformer:
hash <- runHashFile "my-file"
That's dead simple to add, I just wonder which ones should be added (since triplicating the whole API wouldn't be fun). So you're assuming that hashing is the most common case of the library, right? Now, having 'hashFile' inside ResourceT isn't terribly useful and if the user needs it, it's trivial to implement, so I'm thinking of just exporting a single new function: hashFile :: (MonadIO m, Hash ctx d) => FilePath -> m d I'll include it on the next version. =) Cheers, -- Felipe.

And while we're at it, some code to deal with the cumbersome decoding of
those hash objects would be nice!
Cheers,
Aristid
Am 07.01.2012 11:07 schrieb "Greg Weber"
great!
I am wondering if you can provide even higher-level APIs for the common case:
hash <- runResourceT $ hashFile "my-file"
and possibly something that runs the ResourceT transformer:
hash <- runHashFile "my-file"
On Sat, Jan 7, 2012 at 12:16 AM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
Hello!
I'm pleased to announce the first release of crypto-conduit [1]! The crypto-api [2] package provides APIs for many cryptographic operations, such as cryptographic hashes and block ciphers. This new crypto-conduit package allows you to use many of these operations with conduits [3], giving you safe I/O using constant memory and no leaks.
As an example, here's how you could get the SHA1 hash a file:
import Crypto.Conduit -- from crypto-conduit import Crypto.Hash.SHA1 (SHA1) -- from cryptohash import Data.Conduit -- from conduit import Data.Conduit.Binary (sourceFile) -- from conduit
main = do hash <- runResourceT $ sourceFile "my-file" $$ sinkHash print (hash :: SHA1)
The code snippet above, despite having only "sourceFile ... $$ sinkHash" on its core, guarantees that the file handle is not kept open and uses a constant amount of memory. Sweet!
Please break this package! Although it comes with a test suite, it has just seen the light of the day.
Cheers, =)
[1] http://hackage.haskell.org/package/crypto-conduit [2] http://hackage.haskell.org/package/crypto-api [3] http://hackage.haskell.org/package/conduit
-- Felipe.
_______________________________________________ web-devel mailing list web-devel@haskell.org http://www.haskell.org/mailman/listinfo/web-devel
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Jan 7, 2012 at 9:12 AM, Aristid Breitkreuz
And while we're at it, some code to deal with the cumbersome decoding of those hash objects would be nice!
I'm sorry, but what do you mean by "cumbersome decoding"? Cheers, =) -- Felipe.

Well, how do you get a ByteString from the hash object?
Aristid
Am 07.01.2012 13:04 schrieb "Felipe Almeida Lessa"
On Sat, Jan 7, 2012 at 9:12 AM, Aristid Breitkreuz
wrote: And while we're at it, some code to deal with the cumbersome decoding of those hash objects would be nice!
I'm sorry, but what do you mean by "cumbersome decoding"?
Cheers, =)
-- Felipe.

So I want to take the sha-1 of the file contents prefixed with a string containing the file size (similar to how git hashes files). Is there a nice way to compose this without having to create two sources against the same file? Thanks, Grant

On Sat, Jan 7, 2012 at 8:45 PM, Grant
So I want to take the sha-1 of the file contents prefixed with a string containing the file size (similar to how git hashes files). Is there a nice way to compose this without having to create two sources against the same file?
Thanks, Grant
I can think of three approaches that should work: 1. Create a Sink which "forks" its input to two other Sinks (similar to &&& for Arrow). It would have a type signature like: Sink a m b -> Sink a m c -> Sink a m (b, c) 2. Create a specialized Sink that will wrap a single sink and add the byte count of the input stream, eg: Sink ByteString m a -> Sink ByteString m (Int, a) 3. Use a Conduit that will simply update some mutable variable. I think (1) is the most generally useful, though (3) would be the easiest to put together. If you want help implementing any of these approaches, let me know. Michael

Thanks for getting back to me so fast! Actually, I need to include a string with the file length plus the file stream itself and THEN hash that whole thing together. The example below works, but the file is processed twice. Alternatively, I could create a specialised Source that gets the file size from the handle and then processes the file but that looks ugly. Any ideas? Thanks, Grant {-# LANGUAGE NoMonomorphismRestriction #-} {-# OPTIONS -Wall #-} import Crypto.Conduit import Crypto.Hash.SHA1 (SHA1) import Data.Conduit import qualified Data.Conduit.Binary as CB import qualified Data.Conduit.List as CL import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as C8 import Data.Monoid sinkPrefix::Resource m => Sink B.ByteString m B.ByteString sinkPrefix = sinkState 0 (\sz bs -> return (sz + B.length bs,Processing)) (\sz -> return $ C8.pack ("blob " ++ show sz ++ "\0")) digestFile::FilePath -> IO SHA1 digestFile fn=do a1 <- runResourceT $ CB.sourceFile fn $$ sinkPrefix runResourceT $ (mconcat [CL.sourceList [a1], CB.sourceFile fn]) $$ sinkHash

On Sat, Jan 7, 2012 at 10:04 PM, Grant
Thanks for getting back to me so fast! Actually, I need to include a string with the file length plus the file stream itself and THEN hash that whole thing together. The example below works, but the file is processed twice.
Alternatively, I could create a specialised Source that gets the file size from the handle and then processes the file but that looks ugly. Any ideas?
I think we need the following: openFile :: ResourceIO m :: FilePath -> ResourceT m Handle sourceHandle :: ResourceIO m => Handle -> Source m B.ByteString So you would do something like runResourceT $ do handle <- CB.openFile fp fileSize <- liftIO $ hFileSize handle let source = CL.sourceList [encodeFileSize fileSize] `mappend` CB.sourceHandle handle source $$ sinkHash Cheers! -- Felipe.

On Sun, Jan 8, 2012 at 2:39 AM, Felipe Almeida Lessa
On Sat, Jan 7, 2012 at 10:04 PM, Grant
wrote: Thanks for getting back to me so fast! Actually, I need to include a string with the file length plus the file stream itself and THEN hash that whole thing together. The example below works, but the file is processed twice.
Alternatively, I could create a specialised Source that gets the file size from the handle and then processes the file but that looks ugly. Any ideas?
I think we need the following:
openFile :: ResourceIO m :: FilePath -> ResourceT m Handle sourceHandle :: ResourceIO m => Handle -> Source m B.ByteString
So you would do something like
runResourceT $ do handle <- CB.openFile fp fileSize <- liftIO $ hFileSize handle let source = CL.sourceList [encodeFileSize fileSize] `mappend` CB.sourceHandle handle source $$ sinkHash
Cheers!
-- Felipe.
_______________________________________________ web-devel mailing list web-devel@haskell.org http://www.haskell.org/mailman/listinfo/web-devel
I've added openFile, sourceHandle and sinkHandle on Git[1]. Grant: does that give you enough to solve the issues you were facing? Michael [1] https://github.com/snoyberg/conduit/blob/master/conduit/Data/Conduit/Binary....

I've added openFile, sourceHandle and sinkHandle on Git[1]. Grant: does that give you enough to solve the issues you were facing?
Michael
[1]
https://github.com/snoyberg/conduit/blob/master/conduit/Data/Conduit/Binary....
Fantastic! That's perfect. Thanks!
participants (5)
-
Aristid Breitkreuz
-
Felipe Almeida Lessa
-
Grant
-
Greg Weber
-
Michael Snoyman