-----------------------------------------------------------------------------
-- |
-- Module      :  Coded.Encryption.RSA
-- Copyright   :  (c) David J. Sankel 2003, Dominic Steinitz 2003
-- License     :  GPL (see the file ReadMe.tex)
--
-- Stability   :  experimental
-- Portability :  non-portable
--
-- A modified version of the RSA module supplied by David J. Sankel
-- (<http://www.electronconsulting.com/rsa-haskell>).
--
-- As the original code is GPL, this has to be.
-- This code is free software; you can redistribute it and\/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation; either version 2 of the License, or
-- (at your option) any later version.
--
-- This code is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this code; if not, write to the Free Software
-- Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111\-1307  USA
-----------------------------------------------------------------------------

module Codec.Encryption.RSA(
  -- * Function Types
  encrypt,
  decrypt
  )where

import Codec.Utils
import Codec.Encryption.RSA.NumberTheory

rsaep :: (Integer , Integer) -> Integer -> Integer
rsaep :: (Integer, Integer) -> Integer -> Integer
rsaep (Integer
n,Integer
e) Integer
m 
   | Integer
m forall a. Ord a => a -> a -> Bool
< Integer
0 Bool -> Bool -> Bool
|| Integer
m forall a. Ord a => a -> a -> Bool
> Integer
nforall a. Num a => a -> a -> a
-Integer
1 = 
        forall a. HasCallStack => [Char] -> a
error [Char]
"Codec.Encryption.RSA.rsaep: message too long"
   | Bool
otherwise = 
        Integer -> Integer -> Integer -> Integer
expmod Integer
m Integer
e Integer
n

-- | Take the modulus of the RSA key and the public exponent expressed
-- as lists of octets and the plaintext also expressed as a list of
-- octets and return the ciphertext as a list of octets. Of course,
-- these are all large integers but using lists of octets makes
-- everything easier. See 
-- <http://www.rsasecurity.com/rsalabs/pkcs/pkcs-1/index.html> for more
-- details.

encrypt :: ([Octet],[Octet]) -> [Octet] -> [Octet]
encrypt :: ([Octet], [Octet]) -> [Octet] -> [Octet]
encrypt ([Octet]
n,[Octet]
e) [Octet]
m =
   forall a. Integral a => Int -> a -> [Octet]
i2osp (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Octet]
n) forall a b. (a -> b) -> a -> b
$ 
    (Integer, Integer) -> Integer -> Integer
rsaep (forall a b. (Integral a, Integral b) => a -> [Octet] -> b
fromOctets Integer
256 [Octet]
n, forall a b. (Integral a, Integral b) => a -> [Octet] -> b
fromOctets Integer
256 [Octet]
e) (forall a b. (Integral a, Integral b) => a -> [Octet] -> b
fromOctets Integer
256 [Octet]
m)

rsadp :: (Integer , Integer) -> Integer -> Integer
rsadp :: (Integer, Integer) -> Integer -> Integer
rsadp (Integer
n,Integer
d) Integer
c 
   | Integer
c forall a. Ord a => a -> a -> Bool
< Integer
0 Bool -> Bool -> Bool
|| Integer
c forall a. Ord a => a -> a -> Bool
> Integer
nforall a. Num a => a -> a -> a
-Integer
1 = 
        forall a. HasCallStack => [Char] -> a
error [Char]
"Codec.Encryption.RSA.rsadp: decryption error"
   | Bool
otherwise = 
        Integer -> Integer -> Integer -> Integer
expmod Integer
c Integer
d Integer
n

-- | Take the modulus of the RSA key and the private exponent expressed
-- as lists of octets and the ciphertext also expressed as a list of
-- octets and return the plaintext as a list of octets.

decrypt :: ([Octet],[Octet]) -> [Octet] -> [Octet]
decrypt :: ([Octet], [Octet]) -> [Octet] -> [Octet]
decrypt ([Octet]
n,[Octet]
e) [Octet]
m
   | Int
lc forall a. Ord a => a -> a -> Bool
> Int
lm =
        forall a. HasCallStack => [Char] -> a
error [Char]
"Codec.Encryption.RSA.rsadp: decryption error"
   | Bool
otherwise =
        forall a. Integral a => Int -> a -> [Octet]
i2osp (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Octet]
n) forall a b. (a -> b) -> a -> b
$
        (Integer, Integer) -> Integer -> Integer
rsadp (forall a b. (Integral a, Integral b) => a -> [Octet] -> b
fromOctets Integer
256 [Octet]
n, forall a b. (Integral a, Integral b) => a -> [Octet] -> b
fromOctets Integer
256 [Octet]
e) (forall a b. (Integral a, Integral b) => a -> [Octet] -> b
fromOctets Integer
256 [Octet]
m)
   where
      lc :: Int
lc = forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
==Octet
0x00) [Octet]
m
      lm :: Int
lm = forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
==Octet
0x00) [Octet]
n