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

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.)

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.)

On Thu, Sep 2, 2010 at 3:07 PM, Sebastian Fischer
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

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 wrote: On Thu, Sep 2, 2010 at 3:07 PM, Sebastian Fischer
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

[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.)

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.)

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

Sebastian Fischer wrote:
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.
Chances are that you can express them like this as well. :)
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.
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.
That's an argument in favor of type classes, indeed. However, if the extension applies to *all* key types, i.e. if you could merge the subclasses into the superclass, then you can add the new fields to the Key type. If the record fields are read-only, this will not break backwards compatibility.
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.
Would it be desirable to prohibit such calls using the type system?
Unless the implementor of a new encryption algorithm uses different types to distinguish between public and private key, the type class approach forces him to provide non-sensical encrypt and decrypt functions, too. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Sat, Sep 4, 2010 at 3:23 AM, Heinrich Apfelmus
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

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
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

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? -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)
participants (4)
-
Daniel Peebles
-
Heinrich Apfelmus
-
Sebastian Fischer
-
Thomas DuBuisson