The problem in this example is the use of Data.Binary. When using
Data.ByteString.Lazy.Char8 instead, the problem does not exist.

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

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

encrypt :: String -> Data.ByteString.Lazy.ByteString
encrypt str = fst $ Crypto.encrypt (mkStdGen n) pubKey (C8.pack str)

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

decrypt $ encrypt "haskell" = "haskell"



Regards,
Mathias

Am 20.11.2010 13:15, schrieb Charles-Pierre Astolfi:

> > 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 <domi...@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@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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to