Z-Botan-0.1.1.1: Crypto for Haskell
CopyrightDong Han 2021
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Crypto.MPI

Description

This module provide Botan's Multiple Precision Integer, featuring constant-time operations, which is suit for cryptograph usage.

Synopsis

RNG

data MPI Source #

Opaque Botan Multiple Precision Integers.

Instances

Instances details
Enum MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

succ :: MPI -> MPI #

pred :: MPI -> MPI #

toEnum :: Int -> MPI #

fromEnum :: MPI -> Int #

enumFrom :: MPI -> [MPI] #

enumFromThen :: MPI -> MPI -> [MPI] #

enumFromTo :: MPI -> MPI -> [MPI] #

enumFromThenTo :: MPI -> MPI -> MPI -> [MPI] #

Eq MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

(==) :: MPI -> MPI -> Bool #

(/=) :: MPI -> MPI -> Bool #

Integral MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

quot :: MPI -> MPI -> MPI #

rem :: MPI -> MPI -> MPI #

div :: MPI -> MPI -> MPI #

mod :: MPI -> MPI -> MPI #

quotRem :: MPI -> MPI -> (MPI, MPI) #

divMod :: MPI -> MPI -> (MPI, MPI) #

toInteger :: MPI -> Integer #

Num MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

(+) :: MPI -> MPI -> MPI #

(-) :: MPI -> MPI -> MPI #

(*) :: MPI -> MPI -> MPI #

negate :: MPI -> MPI #

abs :: MPI -> MPI #

signum :: MPI -> MPI #

fromInteger :: Integer -> MPI #

Ord MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

compare :: MPI -> MPI -> Ordering #

(<) :: MPI -> MPI -> Bool #

(<=) :: MPI -> MPI -> Bool #

(>) :: MPI -> MPI -> Bool #

(>=) :: MPI -> MPI -> Bool #

max :: MPI -> MPI -> MPI #

min :: MPI -> MPI -> MPI #

Real MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

toRational :: MPI -> Rational #

Show MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

showsPrec :: Int -> MPI -> ShowS #

show :: MPI -> String #

showList :: [MPI] -> ShowS #

JSON MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Print MPI Source # 
Instance details

Defined in Z.Crypto.MPI

Methods

toUTF8BuilderP :: Int -> MPI -> Builder () #

Bits MPI Source #

The testBit implementation ignore sign.

Instance details

Defined in Z.Crypto.MPI

Methods

(.&.) :: MPI -> MPI -> MPI #

(.|.) :: MPI -> MPI -> MPI #

xor :: MPI -> MPI -> MPI #

complement :: MPI -> MPI #

shift :: MPI -> Int -> MPI #

rotate :: MPI -> Int -> MPI #

zeroBits :: MPI #

bit :: Int -> MPI #

setBit :: MPI -> Int -> MPI #

clearBit :: MPI -> Int -> MPI #

complementBit :: MPI -> Int -> MPI #

testBit :: MPI -> Int -> Bool #

bitSizeMaybe :: MPI -> Maybe Int #

bitSize :: MPI -> Int #

isSigned :: MPI -> Bool #

shiftL :: MPI -> Int -> MPI #

unsafeShiftL :: MPI -> Int -> MPI #

shiftR :: MPI -> Int -> MPI #

unsafeShiftR :: MPI -> Int -> MPI #

rotateL :: MPI -> Int -> MPI #

rotateR :: MPI -> Int -> MPI #

popCount :: MPI -> Int #

fromCInt :: CInt -> MPI Source #

Set MPI from an integer value.

toWord32 :: HasCallStack => MPI -> Word32 Source #

Convert a MPI to Word32, the sign is ignored.

byteSize :: MPI -> Int Source #

Get MPI 's byte size.

bitSize :: MPI -> Int Source #

Get MPI 's bit size.

Builder & Parser

toHex :: MPI -> Builder () Source #

Write a MPI in hexadecimal format(without '0x' prefix), the sign is ignored.

toDecimal :: MPI -> Builder () Source #

Write a MPI in decimal format, with negative sign if < 0.

fromHex :: Parser MPI Source #

Parse a MPI in hexadecimal format(without '0x' prefix), no sign is allowed.

fromDecimal :: Parser MPI Source #

Parse a MPI in decimal format, parse leading minus sign.

Predicator

isPrim :: RNG -> MPI -> Int -> IO Bool Source #

Test if n is prime.

The algorithm used (Miller-Rabin) is probabilistic, set test_prob to the desired assurance level. For example if test_prob is 64, then sufficient Miller-Rabin iterations will run to assure there is at most a 1/2**64 chance that n is composite.

MPI specific

mulMod :: MPI -> MPI -> MPI -> MPI Source #

mulMod x y mod = x times y modulo mod

powMod :: MPI -> MPI -> MPI -> MPI Source #

Modular exponentiation. powMod base exp mod = base power exp module mod

modInverse :: MPI -> MPI -> MPI Source #

Modular inverse, find an integer x so that a⋅x ≡ 1 mod m

If no modular inverse exists (for instance because in and modulus are not relatively prime), return 0.

gcd :: MPI -> MPI -> MPI Source #

Compute the greatest common divisor of x and y.

Random MPI

randBits :: RNG -> Int -> IO MPI Source #

Create a random MPI of the specified bit size.

randRange Source #

Arguments

:: RNG 
-> MPI

lower bound

-> MPI

upper bound

-> IO MPI 

Create a random MPI within the provided range.

Internal

newMPI' :: (BotanStructT -> IO a) -> IO (MPI, a) Source #

withMPI :: MPI -> (BotanStructT -> IO a) -> IO a Source #