[Haskell-cafe] Re: Codec.Crypto.RSA question

Charles-Pierre Astolfi cpa at crans.org
Sat Nov 20 07:15:47 EST 2010


Here's a working example:

import qualified Codec.Crypto.RSA as Crypto
import System.Random (mkStdGen)
import Data.Binary (encode)
import Data.ByteString.Lazy.UTF8 (toString)

n = 1024
(pubKey,privKey,_) = Crypto.generateKeyPair (mkStdGen n) n

encrypt :: (Data.Binary.Binary a) => a ->
Data.ByteString.Lazy.Internal.ByteString
encrypt str = fst $ Crypto.encrypt (mkStdGen n) pubKey (encode str)

decrypt :: Data.ByteString.Lazy.Internal.ByteString -> String
decrypt = toString . Crypto.decrypt privKey

Thus,
decrypt $ encrypt "haskell" = "\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ahaskell"


I'm using Codec.Crypto.RSA and you're quoting Codec.Encryption.RSA,
which is not the same thing; unfortunately I need to use RSAES-OAEP
(SHA1) so I guess I have to stick with Codec.Crypto.RSA.
Any ideas?
--
Cp



On Sat, Nov 20, 2010 at 12:50, Dominic Steinitz <dominic at steinitz.org> wrote:
> Charles-Pierre Astolfi <cpa <at> crans.org> writes:
>
>>
>> Hi -cafe,
>>
>> I have a question about Codec.Crypto.RSA: how to enforce that
>> (informally) decrypt . encrypt = id
>> Consider this code:
>>
> That's certainly what I would expect and one of the unit tests  that comes with
> http://hackage.haskell.org/packages/archive/Crypto/4.2.2/doc/html/Codec-Encryption-RSA.html
> checks for this. I wasn't able to get you code to compile so I couldn't
> investigate further. Maybe you could post a fully compiling example?
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list