Codec.Crypto.RSA question

Hi -cafe, I have a question about Codec.Crypto.RSA: how to enforce that (informally) decrypt . encrypt = id Consider this code: encrypt2 :: String -> ByteString encrypt2 = fst . encrypt (mkStdGen n) pubKey encode decrypt2 :: ByteString -> String decrypt2 = toString . decrypt privKey Since decrypt2 takes a bytestring which size is a multiple of the modulus, I've guessed that the encrypted bytestring is padded with '\NUL' characters. But then some strange stuff shows up: decrypt2 $ encrypt2 "haskell" returns "\NUL\NUL\NUL\NUL\EOThaskell" decrypt2 $ encrypt2 "foobar" returns "\NUL\NUL\NUL\NUL\65533foobar" I may use dropWhile to get rid of the NUL-padding, but can I assume that I'll always get a random character between my string and the padding? I tried to pad myself with NUL characters but I got almost the same results (the "random char" went to the head of the string) -- Cp

Charles-Pierre Astolfi
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-Encr... 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?

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
Charles-Pierre Astolfi
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-Encr... 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

Charles-Pierre Astolfi wrote:
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? --
I was quoting Codec.Encryption.RSA only to suggest that I would expect that decrypt . encrypt == id. Here's an example using RSAES-OAEP that demonstrates the desired property. I'm not sure what your application is but if you want to interoperate e.g. with openssl, it's pretty essential to be able to be able to handle certificates. Unfortunately, it looks like the asn1 package is now bit-rotted. At one point there was a test against openssl together with instructions on how to interoperate. I still have the instructions if you are interested.
module Main(main) where
import Codec.Utils import Data.Digest.SHA1(hash,Word160(Word160)) import Codec.Encryption.RSA.MGF import Codec.Encryption.RSA.EMEOAEP import Codec.Encryption.RSA import Test.HUnit
import qualified Codec.Crypto.RSA as Crypto import System.Random (mkStdGen) import qualified Data.Binary as Binary import Data.ByteString.Lazy.UTF8 (toString)
import Data.Char import qualified Codec.Encryption.RSA.EMEOAEP as E import Codec.Encryption.RSA.MGF
n1 = 1024 (pubKey,privKey,_) = Crypto.generateKeyPair (mkStdGen n1) n1
encrypt1 str = fst $ Crypto.encrypt (mkStdGen n1) pubKey (Binary.encode str)
decrypt1 = toString . Crypto.decrypt privKey
randomSeed :: [Octet] randomSeed = hash' [3]
hash' xs = let (Word160 a b c d e) = hash xs in concatMap (toOctets 256) [a,b,c,d,e]
ciphertext :: [Octet] -> [Octet] -> String -> [Octet] ciphertext n d x = encrypt (n,d) $ E.encode mgf hash' [] randomSeed n $ map (fromIntegral . ord) x
plaintext :: [Octet] -> [Octet] -> [Octet] -> String plaintext n e x = map (chr . fromIntegral) $ E.decode mgf hash' [] $ decrypt (n,e) $ x
ciphertext1 privKey x = ciphertext (toOctets 256 $ Crypto.private_n privKey) (toOctets 256 $ Crypto.private_d privKey) x
plaintext1 pubKey x = plaintext (toOctets 256 $ Crypto.public_n pubKey) (toOctets 256 $ Crypto.public_e pubKey) x
main = putStrLn $ plaintext1 pubKey $ ciphertext1 privKey "Hello"

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
wrote: Charles-Pierre Astolfi
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-Encr... 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

Thanks Mat, it works, but I still have a problem: I'm heavily using
Data.Binary.encode for various types (Int32, Int8, String, Bool...)
and I don't know how I should manage this using
Data.ByteString.Lazy.Char8.
--
Cp
On Sat, Nov 20, 2010 at 22:35, Mathias Weber
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
wrote: Charles-Pierre Astolfi
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-Encr... 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

Then how about using encode (as in your original example) and decode (both from Data.Binary). IMO it's garanteed that decode . encode = id (at least for the standard types). ... decrypt :: Data.ByteString.Lazy.ByteString -> String decrypt = decode . Crypto.decrypt privKey ... Am 21.11.2010 18:18, schrieb Charles-Pierre Astolfi:
Thanks Mat, it works, but I still have a problem: I'm heavily using Data.Binary.encode for various types (Int32, Int8, String, Bool...) and I don't know how I should manage this using Data.ByteString.Lazy.Char8.
-- Cp
On Sat, Nov 20, 2010 at 22:35, Mathias Weber
wrote: 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
wrote: Charles-Pierre Astolfi
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-Encr... 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
participants (4)
-
Charles-Pierre Astolfi
-
Dominic Steinitz
-
Dominic Steintiz
-
Mathias Weber