[Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-08 Thread Heinrich Apfelmus

Thomas DuBuisson wrote:

Sorry, the example was all messed up, even if it did communicate what
I wanted its just so broken I must fix.

Slightly contrived example:

   buildAgreementMessage :: (Monad m, CryptoRandomGen g,
ASymetricCipher k) = g - k - m (B.ByteString, (k,k), g)
   buildAgreementMessages g k = do
   ((p,q),g') - eitherToFail (buildKeyPair g)
   let pBS = encode p
   msg = runPut $ do
   putByteString agreementHeader
   putWord16be (B.length pBS)
   putByteString pBS
   return $ (sign msg k, (p,q), g')

Again, this is simply trying to re-enforce the fact that buildKeyPair
(formerly 'generateKeyPair') does have a place.


Granted.

However, the key feature of your example is that a new key is derived 
from an old key, i.e. the function used is


type BuildKeyPair g k = CryptoRandomGen g = g - ((k,k),g)

buildKeyPair' :: k - BuildKeyPair g k

Thanks to the additional argument, this can be added to the  Key  record

data Key = Key { cipher :: BuildKeyPair g k , ... }

In other words, the  Key  can also store a method to generate new keys 
with the same cipher algorithm.



All examples that use  buildKeyPair  and type classes can be 
reformulated in terms of  Key  with this additional field. That's 
because  buildKeyPair  actually expects a type argument; the  cipher 
filed merely shifts that argument to the value level.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-05 Thread Marcel Fourné
Thomas DuBuisson wrote:

There is a blog on this [1], but the main points about the new class
are:

1) Generates bytestrings, not Ints

I like this one because it's semantically truer (tm). ;-)

2) Generalized PRNG construction and reseeding

...which takes the great burden off it's users shoulders, nice!

3) 'split' is in a different class.

Is it necessary for crypto-use? I have never used it for that and I
don't know if somebody other did, but I just ask myself the question.

4) Clean failure via Either (RandomGen forced you to use exceptions)

This is much better and fits nicely into the generateKeyPair of
AsymCipher with a minimum of effort.

What can you do?  Accept this API, help improve the API, or argue that
we should stick with RandomGen (despite short-comings noted on the
blog).  Please pick one and get to it!

I plan to use this (genInteger looks just too convenient), but
RandomGenerator looks nice enough to use it in other
crypto-projects (just my RNG-output consumers view)!

Marcel

-- 
Marcel Fourné
OpenPGP-Key-ID: 0x74545C72
A good library is preferable to a tool, except when you just need that
one tool.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-04 Thread Thomas DuBuisson
On Sat, Sep 4, 2010 at 3:23 AM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 A better reason is the data structure has
 no way to implement generateKeyPair.

 That's a non-problem: each algorithm (RSA, DSA, ...) implements a
 function with the same type as  generateKeyPair . Compare

   rsa :: RangomGen g = BitLength - g - ((Key,Key), g)

 vs

   ((k1 :: RSA, k2), g') = generateKeyPair g

 You always have to write down the name of the algorithm (RSA) when
 using  generateKeyPair , so you may as well drop it entirely.

That simply isn't true.  What if you have a key exchange in which the
ephemeral key is of the same type as your signing key?

Slightly contrived example:

buildAgreementMessage :: (Monad m, CryptoRandomGen g,
ASymetricCipher k) = g - k - m (B.ByteString,g)
buildAgreementMessages g k = do
(e,g') - liftM eitherToFail (buildAsymKey g `asTypeOf` k)
let eBS = encode e
msg = runPut (putByteString agreementHeader  putWord16be
(B.length eBS)  putByteString eBS)
return msg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-04 Thread Thomas DuBuisson
Sorry, the example was all messed up, even if it did communicate what
I wanted its just so broken I must fix.

Slightly contrived example:

   buildAgreementMessage :: (Monad m, CryptoRandomGen g,
ASymetricCipher k) = g - k - m (B.ByteString, (k,k), g)
   buildAgreementMessages g k = do
   ((p,q),g') - eitherToFail (buildKeyPair g)
   let pBS = encode p
   msg = runPut $ do
   putByteString agreementHeader
   putWord16be (B.length pBS)
   putByteString pBS
   return $ (sign msg k, (p,q), g')

Again, this is simply trying to re-enforce the fact that buildKeyPair
(formerly 'generateKeyPair') does have a place.

Cheers,
Thomas

On Sat, Sep 4, 2010 at 7:45 AM, Thomas DuBuisson
thomas.dubuis...@gmail.com wrote:

 Slightly contrived example:

    buildAgreementMessage :: (Monad m, CryptoRandomGen g,
 ASymetricCipher k) = g - k - m (B.ByteString,g)
    buildAgreementMessages g k = do
        (e,g') - liftM eitherToFail (buildAsymKey g `asTypeOf` k)
        let eBS = encode e
            msg = runPut (putByteString agreementHeader  putWord16be
 (B.length eBS)  putByteString eBS)
        return msg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-03 Thread Sebastian Fischer

[CC'ing maintainer of MonadRandom]

On Sep 3, 2010, at 1:59 AM, Thomas DuBuisson wrote:


 data Key = Key {
  encrypt   :: B.ByteString - B.ByteString,
  decrypt   :: B.ByteString - B.ByteString,
  keyLength :: BitLength,
  serialize :: B.ByteString}

 rsa :: RandomGen g = BitLength - g - ((Key,Key), g)


One reason against this is simply that all the other constructs
(block/stream cipher, hashes) are classes, it would be odd for there
to be a single exception.  A better reason is the data structure has
no way to implement generateKeyPair.


Also, the type-class approach is extensible in that new operations  
(for example for signing) can be added via subclasses. Later extending  
the key type above requires nesting.



Why not use

   generateKeypair :: MonadRandom m = BitLength - m (Maybe (p,p))


Because MonadRandom dictates mtl, and is heavier weight than a single
class.  I was hoping to keep this agnostic (mtl is only required for
testing or benchmarks in crypto-api).


I think mtl is only used for the instances, not for the class itself.  
Maybe the maintainer of MonadRandom is inclined to split the package  
if this would raise the number of users of the class.



If MR the more agreeable path
then I'll do it, though this means I use the unholy fail function.


You don't want to use monads because the Monad class defines the fail  
function?



Even if that's the case (and more people weighing in would help) I
still want to include Data.Crypto.Random and welcome comments.


An advantage of using a MonadRandom class would be that the CryptoAPI  
would be independent of RandomGen or your new alternative. One could  
define random monads based on either.


Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-03 Thread Sebastian Fischer


On Sep 3, 2010, at 10:40 AM, Sebastian Fischer wrote:

An advantage of using a MonadRandom class would be that the  
CryptoAPI would be independent of RandomGen or your new alternative.  
One could define random monads based on either.


I was wrong. The MonadRandom class uses the Random class which uses  
RandomGen.





--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-03 Thread Thomas DuBuisson
 If MR the more agreeable path
 then I'll do it, though this means I use the unholy fail function.

 You don't want to use monads because the Monad class defines the fail
 function?

Sorry, I phrased this better on the blog comment.  I don't want to use
MonadRandom m = m (p,p) (MonadRandom + fail) instead of Either
GenError (B,ByteString, g) because it limits my options for failure
down to a piddly fail :: String - m a (ignoring exceptions) - right
now my options for failure are much richer,  I can say ReseedRequred
or NotEnoughEntropy etc, giving the user errors that can be handled by
a simple pattern matching case expression.

 In general, I like this approach, but what are
  encrypt privateKey
or
  decrypt publicKey

 supposed to do? A type-class solution also does not *prevent* programmers to 
 perform such non-sensical calls

Would it be desirable to prohibit such calls using the type system?

As was earlier pointed out, these are actually valid operations for
many public key systems.  In fact, it's possible to use these for
signing or verifying messages:

Signing == encrypt privateKey . encode . hash
Verifying signature == \sig msg - decrypt publicKey sig == encode (hash msg)

What makes a key public and another private is simply your pick of
which to publish and which to protect as jealously as my daughter
guards her cup of water (seriously, I can't get it from her).


Cheers,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Thomas DuBuisson
Marcel noted:
 A central interface to get the output of a PRNG would be nice,
 preferably not constrained to Int like RandomGen.

While BOS said:
 Also, don’t use RandomGen for your asymmetric PRNG. The
 default implementation in System.Random gives absolutely
 disastrous performance, and the typeclass is just
 misdesigned (the split function shouldn’t be present).

Ok, ok.  I never liked RandomGen either - I start this whole thing
because of my PRNG and it doesn't fit RandomGen one bit.

I've build Data.Crypto.Random.RandomGenerator - a new class that fixes
the aspects of RandomGen I don't like.  This is something I was
considering anyway, so it's probably best now and not as an API upset
in a couple months.

There is a blog on this [1], but the main points about the new class are:

1) Generates bytestrings, not Ints
2) Generalized PRNG construction and reseeding
3) 'split' is in a different class.
4) Clean failure via Either (RandomGen forced you to use exceptions)

And minor points
- Providing additional entropy while requesting data is allowed and
has a default instance so most users can ignore this all together.
- a newtype wrapper and instance allows all RandomGenerator instances
to be used as RandomGen when needed.

Who cares about this?  Anyone wanting to get random IVs for block
cipher modes (without getIV_IO) and anyone wanting to generate
asymmetric keys using the AsymCipher class.

What can you do?  Accept this API, help improve the API, or argue that
we should stick with RandomGen (despite short-comings noted on the
blog).  Please pick one and get to it!

Cheers,
Thomas

P.S. I would like to get crypto-api onto hackage by the end of the
first week of September, but understand this is a fairly large change
and will slide that date if there is an unusual strong objection.

[1] 
http://tommd.wordpress.com/2010/09/02/a-better-foundation-for-random-values-in-haskell/


 Designing a random interface that provides something as high a level
 as monad random, is easy enough to make instances for (like RandomGen)
 and is feature rich enough to allow reseeding, additional entropy
 input, personalization, and failure is a non-trivial design task.
 Having ran into the dilemma of how to provide a reasonable high-level
 interface for DRBG, I agree with your statement but don't know how a
 solution would look.

 FYI, BOS had a similar suggestion (on the blog) of moving away from
 RandomGen but I'm not clear on what I'd move toward.

 Cheers,
 Thomas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Sebastian Fischer


On Aug 27, 2010, at 11:12 AM, Heinrich Apfelmus wrote:

Is it actually necessary to use a type class here? The situation is  
very similar to


  Luke Palmer. Haskell Antipattern: Existential Typeclass.
  http://lukepalmer.wordpress.com/2010/01/24/

I suggest to use good old data types

  data Key = Key {
   encrypt   :: B.ByteString - B.ByteString,
   decrypt   :: B.ByteString - B.ByteString,
   keyLength :: BitLength,
   serialize :: B.ByteString}

  rsa :: RandomGen g = BitLength - g - ((Key,Key), g)


In general, I like this approach, but what are

encrypt privateKey

or

decrypt publicKey

supposed to do? A type-class solution also does not *prevent*  
programmers to perform such non-sensical calls, but the data-type  
solution *forces* programmers to provide non-sensical encrypt and  
decrypt functions when creating the public and private keys.



class (Binary p, Serialize p) = AsymCipher p where
  generateKeypair :: RandomGen g = g - BitLength - Maybe  
((p,p),g)

  encryptAsym :: p - B.ByteString - B.ByteString
  decryptAsym :: p - B.ByteString - B.ByteString
  asymKeyLength   :: p - BitLength


Why not use

generateKeypair :: MonadRandom m = BitLength - m (Maybe (p,p))

where MonadRandom is from [1].

Sebastian

[1]: http://hackage.haskell.org/package/MonadRandom


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Sebastian Fischer

On Sep 3, 2010, at 12:07 AM, Sebastian Fischer wrote:


Why not use

   generateKeypair :: MonadRandom m = BitLength - m (Maybe (p,p))


Or if the choice to generate keys or not should solely depend on the  
BitLength (and not on the random generator):


generateKeypair :: MonadRandom m = BitLength - Maybe (m (p,p))



--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Thomas DuBuisson
On Thu, Sep 2, 2010 at 3:07 PM, Sebastian Fischer
s...@informatik.uni-kiel.de wrote:
  data Key = Key {
               encrypt   :: B.ByteString - B.ByteString,
               decrypt   :: B.ByteString - B.ByteString,
               keyLength :: BitLength,
               serialize :: B.ByteString}

  rsa :: RandomGen g = BitLength - g - ((Key,Key), g)

One reason against this is simply that all the other constructs
(block/stream cipher, hashes) are classes, it would be odd for there
to be a single exception.  A better reason is the data structure has
no way to implement generateKeyPair.

 Why not use

    generateKeypair :: MonadRandom m = BitLength - m (Maybe (p,p))

Because MonadRandom dictates mtl, and is heavier weight than a single
class.  I was hoping to keep this agnostic (mtl is only required for
testing or benchmarks in crypto-api).  If MR the more agreeable path
then I'll do it, though this means I use the unholy fail function.
Even if that's the case (and more people weighing in would help) I
still want to include Data.Crypto.Random and welcome comments.

Cheers,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Daniel Peebles
Is there a reason this belongs under the Data. prefix? Why not break it out
into Crypto, so future implementers of algorithms can also put their stuff
under there. Everything at some level can be seen as Data, and it would be
nice to start moving out of the overcrowded module hierarchy.


On Fri, Sep 3, 2010 at 1:59 AM, Thomas DuBuisson thomas.dubuis...@gmail.com
 wrote:

 On Thu, Sep 2, 2010 at 3:07 PM, Sebastian Fischer
 s...@informatik.uni-kiel.de wrote:
   data Key = Key {
encrypt   :: B.ByteString - B.ByteString,
decrypt   :: B.ByteString - B.ByteString,
keyLength :: BitLength,
serialize :: B.ByteString}
 
   rsa :: RandomGen g = BitLength - g - ((Key,Key), g)

 One reason against this is simply that all the other constructs
 (block/stream cipher, hashes) are classes, it would be odd for there
 to be a single exception.  A better reason is the data structure has
 no way to implement generateKeyPair.

  Why not use
 
 generateKeypair :: MonadRandom m = BitLength - m (Maybe (p,p))

 Because MonadRandom dictates mtl, and is heavier weight than a single
 class.  I was hoping to keep this agnostic (mtl is only required for
 testing or benchmarks in crypto-api).  If MR the more agreeable path
 then I'll do it, though this means I use the unholy fail function.
 Even if that's the case (and more people weighing in would help) I
 still want to include Data.Crypto.Random and welcome comments.

 Cheers,
 Thomas
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-27 Thread Heinrich Apfelmus

Thomas DuBuisson wrote:

class (Binary p, Serialize p) = AsymCipher p where
   generateKeypair :: RandomGen g = g - BitLength - Maybe ((p,p),g)
   encryptAsym :: p - B.ByteString - B.ByteString
   decryptAsym :: p - B.ByteString - B.ByteString
   asymKeyLength   :: p - BitLength


Is it actually necessary to use a type class here? The situation is very 
similar to


   Luke Palmer. Haskell Antipattern: Existential Typeclass.
   http://lukepalmer.wordpress.com/2010/01/24/

I suggest to use good old data types

   data Key = Key {
encrypt   :: B.ByteString - B.ByteString,
decrypt   :: B.ByteString - B.ByteString,
keyLength :: BitLength,
serialize :: B.ByteString}

   rsa :: RandomGen g = BitLength - g - ((Key,Key), g)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-27 Thread Maciej Piechotka
On Mon, 2010-08-23 at 10:05 -0700, Thomas DuBuisson wrote:
 All,
 
 Crypto-API - a unified interface to which I hope hash and cipher
 algorithms will adhere - has recently gotten a reasonable amount of
 polish work.  I continue to welcome all comments!  A blog on its
 current interface is online [1] as are darcs repositories of the
 crypto-api package [2].  Recent changes includes added block cipher
 modes, platform-independent RNG, tests, a simplistic benchmark
 framework, and minor tweaks of the classes.  I've made experimental
 hash, block cipher and stream cipher instances.  Almost no
 optimizations have been made as of yet!
 
 Thanks to everyone for their past comments!  I have made numerous
 changes based on input received.  If you feel I didn't respond
 properly to your suggestion then please ping me again - this is purely
 a spare time effort and things do fall through the cracks.
 
 Cheers,
 Thomas
 
 [1] 
 http://tommd.wordpress.com/2010/08/23/a-haskell-api-for-cryptographic-algorithms/
 [2] http://community.haskell.org/~tommd/crypto/
 
 (If you're wondering why you're BCCed its probably because you worked
 on a crypto-related Haskell package)

I wonder - conceptually compression does not differ much from stream
ciphers - you put some data in and you get some data out.

The only real difference is that the compression does not need to have
any private key [but it can have 'public' as the level of compression
etc.].

Except naming they do not differ much (on the other hand - they do share
subsystem in Linux kernel).

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-26 Thread Thomas DuBuisson
class (Binary p, Serialize p) = AsymCipher p where
generateKeypair :: RandomGen g = g - BitLength - Maybe ((p,p),g)
encryptAsym :: p - B.ByteString - B.ByteString
decryptAsym :: p - B.ByteString - B.ByteString
asymKeyLength   :: p - BitLength

 Regarding AsymCipher:
 Some algorithms do not lend themselves to encryption/decryption or have
 special properties which differentiate their use in enc/dec an
 signing/verifying.

 I propose the following two additions for the class:
 signAsym :: p - B.ByteString - B.ByteString
 verifyAsym :: p - B.ByteString - Bool

 This way algorithms can leave parts undefined which do not apply to
 them or hide their different behaviour.

I am strongly against classes for which we already know instanes will
need a good deal of undefined routines.

 Another possibility would be a split of AsymCipher into AsymCipherEnc
 (which is just like the old AsymCipher) and AsymCipherSig for
 Signatures. Textbook-RSA is special, since it can implement both
 classes with a minimum of effort, but a clean separation would be nice
 (and there wouldn't be that many undefined functions).

Perhaps even zero undefined functions.  I like this suggestion, though
I'm not aware of any haskell implementations that will take advantage
of a Signature class yet.  Unless someone can point to something
like a DSA or ECDSA on hackage I'll probably release crypto-api 0.1
without this class (it would still likely appear in a later version
after further consideration).

 Another thing:
 A central interface to get the output of a PRNG would be nice,
 preferably not constrained to Int like RandomGen.

Designing a random interface that provides something as high a level
as monad random, is easy enough to make instances for (like RandomGen)
and is feature rich enough to allow reseeding, additional entropy
input, personalization, and failure is a non-trivial design task.
Having ran into the dilemma of how to provide a reasonable high-level
interface for DRBG, I agree with your statement but don't know how a
solution would look.

FYI, BOS had a similar suggestion (on the blog) of moving away from
RandomGen but I'm not clear on what I'd move toward.

Cheers,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-24 Thread Marcel Fourné
Thomas DuBuisson wrote:

[1]
http://tommd.wordpress.com/2010/08/23/a-haskell-api-for-cryptographic-algorithms/

class (Binary p, Serialize p) = AsymCipher p where
generateKeypair :: RandomGen g = g - BitLength - Maybe ((p,p),g)
encryptAsym :: p - B.ByteString - B.ByteString
decryptAsym :: p - B.ByteString - B.ByteString
asymKeyLength   :: p - BitLength

Regarding AsymCipher:
Some algorithms do not lend themselves to encryption/decryption or have
special properties which differentiate their use in enc/dec an
signing/verifying.

I propose the following two additions for the class:
signAsym :: p - B.ByteString - B.ByteString
verifyAsym :: p - B.ByteString - Bool

This way algorithms can leave parts undefined which do not apply to
them or hide their different behaviour.

Another possibility would be a split of AsymCipher into AsymCipherEnc
(which is just like the old AsymCipher) and AsymCipherSig for
Signatures. Textbook-RSA is special, since it can implement both
classes with a minimum of effort, but a clean separation would be nice
(and there wouldn't be that many undefined functions).

Another thing: 
A central interface to get the output of a PRNG would be nice,
preferably not constrained to Int like RandomGen.
MonadRandom has with getRandomR a nice function, since it takes an
interval (possibly using type Integer), which is very comfortable for
asymmetric cipher usage.
A central interface could spare AsymCipher-implementers the effort of
duplicated work - we are lazy after all. ;-)

Also: Sorry for entering this late into the discussion!

Have a nice day,
Marcel

-- 
Marcel Fourné
OpenPGP-Key-ID: 0x74545C72
A good library is preferable to a tool, except when you just need that
one tool.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe