{-# LANGUAGE DeriveDataTypeable #-}
module Crypto.PubKey.Rabin.Basic
( PublicKey(..)
, PrivateKey(..)
, Signature(..)
, generate
, encrypt
, encryptWithSeed
, decrypt
, sign
, signWith
, verify
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.Data
import Data.Either (rights)
import Crypto.Hash
import Crypto.Number.Basic (gcde, numBytes)
import Crypto.Number.ModArithmetic (expSafe, jacobi)
import Crypto.Number.Serialize (i2osp, i2ospOf_, os2ip)
import Crypto.PubKey.Rabin.OAEP
import Crypto.PubKey.Rabin.Types
import Crypto.Random (MonadRandom, getRandomBytes)
data PublicKey = PublicKey
{ PublicKey -> Int
public_size :: Int
, PublicKey -> Integer
public_n :: Integer
} deriving (Int -> PublicKey -> ShowS
[PublicKey] -> ShowS
PublicKey -> String
(Int -> PublicKey -> ShowS)
-> (PublicKey -> String)
-> ([PublicKey] -> ShowS)
-> Show PublicKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKey] -> ShowS
$cshowList :: [PublicKey] -> ShowS
show :: PublicKey -> String
$cshow :: PublicKey -> String
showsPrec :: Int -> PublicKey -> ShowS
$cshowsPrec :: Int -> PublicKey -> ShowS
Show, ReadPrec [PublicKey]
ReadPrec PublicKey
Int -> ReadS PublicKey
ReadS [PublicKey]
(Int -> ReadS PublicKey)
-> ReadS [PublicKey]
-> ReadPrec PublicKey
-> ReadPrec [PublicKey]
-> Read PublicKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublicKey]
$creadListPrec :: ReadPrec [PublicKey]
readPrec :: ReadPrec PublicKey
$creadPrec :: ReadPrec PublicKey
readList :: ReadS [PublicKey]
$creadList :: ReadS [PublicKey]
readsPrec :: Int -> ReadS PublicKey
$creadsPrec :: Int -> ReadS PublicKey
Read, PublicKey -> PublicKey -> Bool
(PublicKey -> PublicKey -> Bool)
-> (PublicKey -> PublicKey -> Bool) -> Eq PublicKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKey -> PublicKey -> Bool
$c/= :: PublicKey -> PublicKey -> Bool
== :: PublicKey -> PublicKey -> Bool
$c== :: PublicKey -> PublicKey -> Bool
Eq, Typeable PublicKey
DataType
Constr
Typeable PublicKey
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey)
-> (PublicKey -> Constr)
-> (PublicKey -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PublicKey))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey))
-> ((forall b. Data b => b -> b) -> PublicKey -> PublicKey)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r)
-> (forall u. (forall d. Data d => d -> u) -> PublicKey -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PublicKey -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey)
-> Data PublicKey
PublicKey -> DataType
PublicKey -> Constr
(forall b. Data b => b -> b) -> PublicKey -> PublicKey
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PublicKey -> u
forall u. (forall d. Data d => d -> u) -> PublicKey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PublicKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey)
$cPublicKey :: Constr
$tPublicKey :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
gmapMp :: (forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
gmapM :: (forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
gmapQi :: Int -> (forall d. Data d => d -> u) -> PublicKey -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PublicKey -> u
gmapQ :: (forall d. Data d => d -> u) -> PublicKey -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PublicKey -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
gmapT :: (forall b. Data b => b -> b) -> PublicKey -> PublicKey
$cgmapT :: (forall b. Data b => b -> b) -> PublicKey -> PublicKey
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PublicKey)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PublicKey)
dataTypeOf :: PublicKey -> DataType
$cdataTypeOf :: PublicKey -> DataType
toConstr :: PublicKey -> Constr
$ctoConstr :: PublicKey -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
$cp1Data :: Typeable PublicKey
Data)
data PrivateKey = PrivateKey
{ PrivateKey -> PublicKey
private_pub :: PublicKey
, PrivateKey -> Integer
private_p :: Integer
, PrivateKey -> Integer
private_q :: Integer
, PrivateKey -> Integer
private_a :: Integer
, PrivateKey -> Integer
private_b :: Integer
} deriving (Int -> PrivateKey -> ShowS
[PrivateKey] -> ShowS
PrivateKey -> String
(Int -> PrivateKey -> ShowS)
-> (PrivateKey -> String)
-> ([PrivateKey] -> ShowS)
-> Show PrivateKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrivateKey] -> ShowS
$cshowList :: [PrivateKey] -> ShowS
show :: PrivateKey -> String
$cshow :: PrivateKey -> String
showsPrec :: Int -> PrivateKey -> ShowS
$cshowsPrec :: Int -> PrivateKey -> ShowS
Show, ReadPrec [PrivateKey]
ReadPrec PrivateKey
Int -> ReadS PrivateKey
ReadS [PrivateKey]
(Int -> ReadS PrivateKey)
-> ReadS [PrivateKey]
-> ReadPrec PrivateKey
-> ReadPrec [PrivateKey]
-> Read PrivateKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrivateKey]
$creadListPrec :: ReadPrec [PrivateKey]
readPrec :: ReadPrec PrivateKey
$creadPrec :: ReadPrec PrivateKey
readList :: ReadS [PrivateKey]
$creadList :: ReadS [PrivateKey]
readsPrec :: Int -> ReadS PrivateKey
$creadsPrec :: Int -> ReadS PrivateKey
Read, PrivateKey -> PrivateKey -> Bool
(PrivateKey -> PrivateKey -> Bool)
-> (PrivateKey -> PrivateKey -> Bool) -> Eq PrivateKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrivateKey -> PrivateKey -> Bool
$c/= :: PrivateKey -> PrivateKey -> Bool
== :: PrivateKey -> PrivateKey -> Bool
$c== :: PrivateKey -> PrivateKey -> Bool
Eq, Typeable PrivateKey
DataType
Constr
Typeable PrivateKey
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey)
-> (PrivateKey -> Constr)
-> (PrivateKey -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrivateKey))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrivateKey))
-> ((forall b. Data b => b -> b) -> PrivateKey -> PrivateKey)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r)
-> (forall u. (forall d. Data d => d -> u) -> PrivateKey -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PrivateKey -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey)
-> Data PrivateKey
PrivateKey -> DataType
PrivateKey -> Constr
(forall b. Data b => b -> b) -> PrivateKey -> PrivateKey
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PrivateKey -> u
forall u. (forall d. Data d => d -> u) -> PrivateKey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrivateKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey)
$cPrivateKey :: Constr
$tPrivateKey :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
gmapMp :: (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
gmapM :: (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateKey -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PrivateKey -> u
gmapQ :: (forall d. Data d => d -> u) -> PrivateKey -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PrivateKey -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
gmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey
$cgmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PrivateKey)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrivateKey)
dataTypeOf :: PrivateKey -> DataType
$cdataTypeOf :: PrivateKey -> DataType
toConstr :: PrivateKey -> Constr
$ctoConstr :: PrivateKey -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
$cp1Data :: Typeable PrivateKey
Data)
data Signature = Signature (Integer, Integer) deriving (Int -> Signature -> ShowS
[Signature] -> ShowS
Signature -> String
(Int -> Signature -> ShowS)
-> (Signature -> String)
-> ([Signature] -> ShowS)
-> Show Signature
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Signature] -> ShowS
$cshowList :: [Signature] -> ShowS
show :: Signature -> String
$cshow :: Signature -> String
showsPrec :: Int -> Signature -> ShowS
$cshowsPrec :: Int -> Signature -> ShowS
Show, ReadPrec [Signature]
ReadPrec Signature
Int -> ReadS Signature
ReadS [Signature]
(Int -> ReadS Signature)
-> ReadS [Signature]
-> ReadPrec Signature
-> ReadPrec [Signature]
-> Read Signature
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Signature]
$creadListPrec :: ReadPrec [Signature]
readPrec :: ReadPrec Signature
$creadPrec :: ReadPrec Signature
readList :: ReadS [Signature]
$creadList :: ReadS [Signature]
readsPrec :: Int -> ReadS Signature
$creadsPrec :: Int -> ReadS Signature
Read, Signature -> Signature -> Bool
(Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool) -> Eq Signature
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Signature -> Signature -> Bool
$c/= :: Signature -> Signature -> Bool
== :: Signature -> Signature -> Bool
$c== :: Signature -> Signature -> Bool
Eq, Typeable Signature
DataType
Constr
Typeable Signature
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature)
-> (Signature -> Constr)
-> (Signature -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Signature))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature))
-> ((forall b. Data b => b -> b) -> Signature -> Signature)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r)
-> (forall u. (forall d. Data d => d -> u) -> Signature -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Signature -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature)
-> Data Signature
Signature -> DataType
Signature -> Constr
(forall b. Data b => b -> b) -> Signature -> Signature
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Signature -> u
forall u. (forall d. Data d => d -> u) -> Signature -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Signature)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature)
$cSignature :: Constr
$tSignature :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Signature -> m Signature
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
gmapMp :: (forall d. Data d => d -> m d) -> Signature -> m Signature
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
gmapM :: (forall d. Data d => d -> m d) -> Signature -> m Signature
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
gmapQi :: Int -> (forall d. Data d => d -> u) -> Signature -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Signature -> u
gmapQ :: (forall d. Data d => d -> u) -> Signature -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Signature -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
gmapT :: (forall b. Data b => b -> b) -> Signature -> Signature
$cgmapT :: (forall b. Data b => b -> b) -> Signature -> Signature
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Signature)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Signature)
dataTypeOf :: Signature -> DataType
$cdataTypeOf :: Signature -> DataType
toConstr :: Signature -> Constr
$ctoConstr :: Signature -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
$cp1Data :: Typeable Signature
Data)
generate :: MonadRandom m
=> Int
-> m (PublicKey, PrivateKey)
generate :: Int -> m (PublicKey, PrivateKey)
generate Int
size = do
(Integer
p, Integer
q) <- Int -> PrimeCondition -> PrimeCondition -> m (Integer, Integer)
forall (m :: * -> *).
MonadRandom m =>
Int -> PrimeCondition -> PrimeCondition -> m (Integer, Integer)
generatePrimes Int
size (\Integer
p -> Integer
p Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
4 Integer -> PrimeCondition
forall a. Eq a => a -> a -> Bool
== Integer
3) (\Integer
q -> Integer
q Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
4 Integer -> PrimeCondition
forall a. Eq a => a -> a -> Bool
== Integer
3)
(PublicKey, PrivateKey) -> m (PublicKey, PrivateKey)
forall (m :: * -> *) a. Monad m => a -> m a
return ((PublicKey, PrivateKey) -> m (PublicKey, PrivateKey))
-> (PublicKey, PrivateKey) -> m (PublicKey, PrivateKey)
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> (PublicKey, PrivateKey)
generateKeys Integer
p Integer
q
where
generateKeys :: Integer -> Integer -> (PublicKey, PrivateKey)
generateKeys Integer
p Integer
q =
let n :: Integer
n = Integer
pInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
q
(Integer
a, Integer
b, Integer
_) = Integer -> Integer -> (Integer, Integer, Integer)
gcde Integer
p Integer
q
publicKey :: PublicKey
publicKey = PublicKey :: Int -> Integer -> PublicKey
PublicKey { public_size :: Int
public_size = Int
size
, public_n :: Integer
public_n = Integer
n }
privateKey :: PrivateKey
privateKey = PrivateKey :: PublicKey -> Integer -> Integer -> Integer -> Integer -> PrivateKey
PrivateKey { private_pub :: PublicKey
private_pub = PublicKey
publicKey
, private_p :: Integer
private_p = Integer
p
, private_q :: Integer
private_q = Integer
q
, private_a :: Integer
private_a = Integer
a
, private_b :: Integer
private_b = Integer
b }
in (PublicKey
publicKey, PrivateKey
privateKey)
encryptWithSeed :: HashAlgorithm hash
=> ByteString
-> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> Either Error ByteString
encryptWithSeed :: ByteString
-> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> Either Error ByteString
encryptWithSeed ByteString
seed OAEPParams hash ByteString ByteString
oaep PublicKey
pk ByteString
m =
let n :: Integer
n = PublicKey -> Integer
public_n PublicKey
pk
k :: Int
k = Integer -> Int
numBytes Integer
n
in do
ByteString
m' <- ByteString
-> OAEPParams hash ByteString ByteString
-> Int
-> ByteString
-> Either Error ByteString
forall hash.
HashAlgorithm hash =>
ByteString
-> OAEPParams hash ByteString ByteString
-> Int
-> ByteString
-> Either Error ByteString
pad ByteString
seed OAEPParams hash ByteString ByteString
oaep Int
k ByteString
m
let m'' :: Integer
m'' = ByteString -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
os2ip ByteString
m'
ByteString -> Either Error ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Either Error ByteString)
-> ByteString -> Either Error ByteString
forall a b. (a -> b) -> a -> b
$ Integer -> ByteString
forall ba. ByteArray ba => Integer -> ba
i2osp (Integer -> ByteString) -> Integer -> ByteString
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer -> Integer
expSafe Integer
m'' Integer
2 Integer
n
encrypt :: (HashAlgorithm hash, MonadRandom m)
=> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> m (Either Error ByteString)
encrypt :: OAEPParams hash ByteString ByteString
-> PublicKey -> ByteString -> m (Either Error ByteString)
encrypt OAEPParams hash ByteString ByteString
oaep PublicKey
pk ByteString
m = do
ByteString
seed <- Int -> m ByteString
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
hashLen
Either Error ByteString -> m (Either Error ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Error ByteString -> m (Either Error ByteString))
-> Either Error ByteString -> m (Either Error ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString
-> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> Either Error ByteString
forall hash.
HashAlgorithm hash =>
ByteString
-> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> Either Error ByteString
encryptWithSeed ByteString
seed OAEPParams hash ByteString ByteString
oaep PublicKey
pk ByteString
m
where
hashLen :: Int
hashLen = hash -> Int
forall a. HashAlgorithm a => a -> Int
hashDigestSize (OAEPParams hash ByteString ByteString -> hash
forall hash seed output. OAEPParams hash seed output -> hash
oaepHash OAEPParams hash ByteString ByteString
oaep)
decrypt :: HashAlgorithm hash
=> OAEPParams hash ByteString ByteString
-> PrivateKey
-> ByteString
-> Maybe ByteString
decrypt :: OAEPParams hash ByteString ByteString
-> PrivateKey -> ByteString -> Maybe ByteString
decrypt OAEPParams hash ByteString ByteString
oaep PrivateKey
pk ByteString
c =
let p :: Integer
p = PrivateKey -> Integer
private_p PrivateKey
pk
q :: Integer
q = PrivateKey -> Integer
private_q PrivateKey
pk
a :: Integer
a = PrivateKey -> Integer
private_a PrivateKey
pk
b :: Integer
b = PrivateKey -> Integer
private_b PrivateKey
pk
n :: Integer
n = PublicKey -> Integer
public_n (PublicKey -> Integer) -> PublicKey -> Integer
forall a b. (a -> b) -> a -> b
$ PrivateKey -> PublicKey
private_pub PrivateKey
pk
k :: Int
k = Integer -> Int
numBytes Integer
n
c' :: Integer
c' = ByteString -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
os2ip ByteString
c
solutions :: [ByteString]
solutions = [Either Error ByteString] -> [ByteString]
forall a b. [Either a b] -> [b]
rights ([Either Error ByteString] -> [ByteString])
-> [Either Error ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ (Either Error ByteString, Either Error ByteString,
Either Error ByteString, Either Error ByteString)
-> [Either Error ByteString]
forall a. (a, a, a, a) -> [a]
toList ((Either Error ByteString, Either Error ByteString,
Either Error ByteString, Either Error ByteString)
-> [Either Error ByteString])
-> (Either Error ByteString, Either Error ByteString,
Either Error ByteString, Either Error ByteString)
-> [Either Error ByteString]
forall a b. (a -> b) -> a -> b
$ (Integer -> Either Error ByteString)
-> (Integer, Integer, Integer, Integer)
-> (Either Error ByteString, Either Error ByteString,
Either Error ByteString, Either Error ByteString)
forall t d. (t -> d) -> (t, t, t, t) -> (d, d, d, d)
mapTuple (OAEPParams hash ByteString ByteString
-> Int -> ByteString -> Either Error ByteString
forall hash.
HashAlgorithm hash =>
OAEPParams hash ByteString ByteString
-> Int -> ByteString -> Either Error ByteString
unpad OAEPParams hash ByteString ByteString
oaep Int
k (ByteString -> Either Error ByteString)
-> (Integer -> ByteString) -> Integer -> Either Error ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer -> ByteString
forall ba. ByteArray ba => Int -> Integer -> ba
i2ospOf_ Int
k) ((Integer, Integer, Integer, Integer)
-> (Either Error ByteString, Either Error ByteString,
Either Error ByteString, Either Error ByteString))
-> (Integer, Integer, Integer, Integer)
-> (Either Error ByteString, Either Error ByteString,
Either Error ByteString, Either Error ByteString)
forall a b. (a -> b) -> a -> b
$ Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> (Integer, Integer, Integer, Integer)
sqroot' Integer
c' Integer
p Integer
q Integer
a Integer
b Integer
n
in if [ByteString] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ByteString]
solutions Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 then Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. [a] -> a
head [ByteString]
solutions
where toList :: (a, a, a, a) -> [a]
toList (a
w, a
x, a
y, a
z) = a
wa -> [a] -> [a]
forall a. a -> [a] -> [a]
:a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:a
za -> [a] -> [a]
forall a. a -> [a] -> [a]
:[]
mapTuple :: (t -> d) -> (t, t, t, t) -> (d, d, d, d)
mapTuple t -> d
f (t
w, t
x, t
y, t
z) = (t -> d
f t
w, t -> d
f t
x, t -> d
f t
y, t -> d
f t
z)
signWith :: HashAlgorithm hash
=> ByteString
-> PrivateKey
-> hash
-> ByteString
-> Either Error Signature
signWith :: ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Signature
signWith ByteString
padding PrivateKey
pk hash
hashAlg ByteString
m = do
Integer
h <- ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Integer
forall hash.
HashAlgorithm hash =>
ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Integer
calculateHash ByteString
padding PrivateKey
pk hash
hashAlg ByteString
m
Signature
signature <- Integer -> Either Error Signature
calculateSignature Integer
h
Signature -> Either Error Signature
forall (m :: * -> *) a. Monad m => a -> m a
return Signature
signature
where
calculateSignature :: Integer -> Either Error Signature
calculateSignature Integer
h =
let p :: Integer
p = PrivateKey -> Integer
private_p PrivateKey
pk
q :: Integer
q = PrivateKey -> Integer
private_q PrivateKey
pk
a :: Integer
a = PrivateKey -> Integer
private_a PrivateKey
pk
b :: Integer
b = PrivateKey -> Integer
private_b PrivateKey
pk
n :: Integer
n = PublicKey -> Integer
public_n (PublicKey -> Integer) -> PublicKey -> Integer
forall a b. (a -> b) -> a -> b
$ PrivateKey -> PublicKey
private_pub PrivateKey
pk
in if Integer
h Integer -> PrimeCondition
forall a. Ord a => a -> a -> Bool
>= Integer
n then Error -> Either Error Signature
forall a b. a -> Either a b
Left Error
MessageTooLong
else let (Integer
r, Integer
_, Integer
_, Integer
_) = Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> (Integer, Integer, Integer, Integer)
sqroot' Integer
h Integer
p Integer
q Integer
a Integer
b Integer
n
in Signature -> Either Error Signature
forall a b. b -> Either a b
Right (Signature -> Either Error Signature)
-> Signature -> Either Error Signature
forall a b. (a -> b) -> a -> b
$ (Integer, Integer) -> Signature
Signature (ByteString -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
os2ip ByteString
padding, Integer
r)
sign :: (MonadRandom m, HashAlgorithm hash)
=> PrivateKey
-> hash
-> ByteString
-> m (Either Error Signature)
sign :: PrivateKey -> hash -> ByteString -> m (Either Error Signature)
sign PrivateKey
pk hash
hashAlg ByteString
m = do
ByteString
padding <- m ByteString
findPadding
Either Error Signature -> m (Either Error Signature)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Error Signature -> m (Either Error Signature))
-> Either Error Signature -> m (Either Error Signature)
forall a b. (a -> b) -> a -> b
$ ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Signature
forall hash.
HashAlgorithm hash =>
ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Signature
signWith ByteString
padding PrivateKey
pk hash
hashAlg ByteString
m
where
findPadding :: m ByteString
findPadding = do
ByteString
padding <- Int -> m ByteString
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
8
case ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Integer
forall hash.
HashAlgorithm hash =>
ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Integer
calculateHash ByteString
padding PrivateKey
pk hash
hashAlg ByteString
m of
Right Integer
_ -> ByteString -> m ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
padding
Either Error Integer
_ -> m ByteString
findPadding
calculateHash :: HashAlgorithm hash
=> ByteString
-> PrivateKey
-> hash
-> ByteString
-> Either Error Integer
calculateHash :: ByteString
-> PrivateKey -> hash -> ByteString -> Either Error Integer
calculateHash ByteString
padding PrivateKey
pk hash
hashAlg ByteString
m =
let p :: Integer
p = PrivateKey -> Integer
private_p PrivateKey
pk
q :: Integer
q = PrivateKey -> Integer
private_q PrivateKey
pk
h :: Integer
h = Digest hash -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
os2ip (Digest hash -> Integer) -> Digest hash -> Integer
forall a b. (a -> b) -> a -> b
$ hash -> ByteString -> Digest hash
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith hash
hashAlg (ByteString -> Digest hash) -> ByteString -> Digest hash
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> ByteString
B.append ByteString
padding ByteString
m
in case (Integer -> Integer -> Maybe Integer
jacobi (Integer
h Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
p) Integer
p, Integer -> Integer -> Maybe Integer
jacobi (Integer
h Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
q) Integer
q) of
(Just Integer
1, Just Integer
1) -> Integer -> Either Error Integer
forall a b. b -> Either a b
Right Integer
h
(Maybe Integer, Maybe Integer)
_ -> Error -> Either Error Integer
forall a b. a -> Either a b
Left Error
InvalidParameters
verify :: HashAlgorithm hash
=> PublicKey
-> hash
-> ByteString
-> Signature
-> Bool
verify :: PublicKey -> hash -> ByteString -> Signature -> Bool
verify PublicKey
pk hash
hashAlg ByteString
m (Signature (Integer
padding, Integer
s)) =
let n :: Integer
n = PublicKey -> Integer
public_n PublicKey
pk
p :: ByteString
p = Integer -> ByteString
forall ba. ByteArray ba => Integer -> ba
i2osp Integer
padding
h :: Integer
h = Digest hash -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
os2ip (Digest hash -> Integer) -> Digest hash -> Integer
forall a b. (a -> b) -> a -> b
$ hash -> ByteString -> Digest hash
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith hash
hashAlg (ByteString -> Digest hash) -> ByteString -> Digest hash
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> ByteString
B.append ByteString
p ByteString
m
h' :: Integer
h' = Integer -> Integer -> Integer -> Integer
expSafe Integer
s Integer
2 Integer
n
in Integer
h' Integer -> PrimeCondition
forall a. Eq a => a -> a -> Bool
== Integer
h
sqroot :: Integer
-> Integer
-> (Integer, Integer)
sqroot :: Integer -> Integer -> (Integer, Integer)
sqroot Integer
a Integer
p =
let r :: Integer
r = Integer -> Integer -> Integer -> Integer
expSafe Integer
a ((Integer
p Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
4) Integer
p
in (Integer
r, -Integer
r)
sqroot' :: Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> (Integer, Integer, Integer, Integer)
sqroot' :: Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> (Integer, Integer, Integer, Integer)
sqroot' Integer
a Integer
p Integer
q Integer
c Integer
d Integer
n =
let (Integer
r, Integer
_) = Integer -> Integer -> (Integer, Integer)
sqroot Integer
a Integer
p
(Integer
s, Integer
_) = Integer -> Integer -> (Integer, Integer)
sqroot Integer
a Integer
q
x :: Integer
x = (Integer
rInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
dInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
q Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
sInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
cInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
p) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
n
y :: Integer
y = (Integer
rInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
dInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
q Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
sInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
cInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
p) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
n
in (Integer
x, (-Integer
x) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
n, Integer
y, (-Integer
y) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
n)