
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"