botan-bindings-0.0.1.0: Raw Botan bindings
Copyright(c) Leo D 2023
LicenseBSD-3-Clause
Maintainerleo@apotheca.io
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Botan.Bindings.MPI

Description

 
Synopsis

Documentation

data BotanMPStruct Source #

Opaque MP struct

newtype BotanMP Source #

Botan MP object

Constructors

MkBotanMP 

Instances

Instances details
Storable BotanMP Source # 
Instance details

Defined in Botan.Bindings.MPI

Eq BotanMP Source # 
Instance details

Defined in Botan.Bindings.MPI

Methods

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

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

Ord BotanMP Source # 
Instance details

Defined in Botan.Bindings.MPI

botan_mp_destroy :: FinalizerPtr BotanMPStruct Source #

Destroy (deallocate) an MPI

botan_mp_init Source #

Arguments

:: Ptr BotanMP

mp

-> IO CInt 

Initialize an MPI

botan_mp_to_hex Source #

Arguments

:: BotanMP

mp

-> Ptr CChar

out

-> IO CInt 

Convert the MPI to a hex string. Writes botan_mp_num_bytes(mp)*2 + 1 bytes

botan_mp_to_str Source #

Arguments

:: BotanMP

mp

-> Word8

base

-> Ptr CChar

out

-> Ptr CSize

out_len

-> IO CInt 

Convert the MPI to a string. Currently base == 10 and base == 16 are supported.

NOTE: base 16 encoding has an `0x` prefix, base 10 does not.

NOTE: Despite the size ptr, this appears to be returning null-terminated CStrings

botan_mp_clear Source #

Arguments

:: BotanMP

mp

-> IO CInt 

Set the MPI to zero

botan_mp_set_from_int Source #

Arguments

:: BotanMP

mp

-> CInt

initial_value

-> IO CInt 

Set the MPI value from an int

botan_mp_set_from_mp Source #

Arguments

:: BotanMP

dest

-> BotanMP

source

-> IO CInt 

Set the MPI value from another MP object

botan_mp_set_from_str Source #

Arguments

:: BotanMP

dest

-> ConstPtr CChar

str

-> IO CInt 

Set the MPI value from a string

botan_mp_set_from_radix_str Source #

Arguments

:: BotanMP

dest

-> ConstPtr CChar

str

-> CSize

radix

-> IO CInt 

Set the MPI value from a string with arbitrary radix. For arbitrary being 10 or 16.

botan_mp_num_bits Source #

Arguments

:: BotanMP

n

-> Ptr CSize

bits

-> IO CInt 

Return the number of significant bits in the MPI

botan_mp_num_bytes Source #

Arguments

:: BotanMP

n

-> Ptr CSize

bytes

-> IO CInt 

Return the number of significant bytes in the MPI

botan_mp_to_bin Source #

Arguments

:: BotanMP

mp

-> Ptr Word8

vec[]

-> IO CInt 

Convert the MPI to a big-endian binary string. Writes botan_mp_num_bytes to vec

botan_mp_from_bin Source #

Arguments

:: BotanMP

mp

-> ConstPtr Word8

vec[]

-> CSize

vec_len

-> IO CInt 

Set an MP to the big-endian binary value

botan_mp_to_uint32 Source #

Arguments

:: BotanMP

mp

-> Ptr Word32

val

-> IO CInt 

Convert the MPI to a uint32_t, if possible. Fails if MPI is negative or too large.

botan_mp_is_positive Source #

Arguments

:: BotanMP

mp

-> IO CInt 

This function should have been named mp_is_non_negative. Returns 1 iff mp is greater than *or equal to* zero. Use botan_mp_is_negative to detect negative numbers, botan_mp_is_zero to check for zero.

botan_mp_is_negative Source #

Arguments

:: BotanMP

mp

-> IO CInt 

Return 1 iff mp is less than 0

botan_mp_add_u32 Source #

Arguments

:: BotanMP

result

-> BotanMP

x

-> Word32

y

-> IO CInt 

botan_mp_sub_u32 Source #

Arguments

:: BotanMP

result

-> BotanMP

x

-> Word32

y

-> IO CInt 

botan_mp_add Source #

Arguments

:: BotanMP

result

-> BotanMP

x

-> BotanMP

y

-> IO CInt 

botan_mp_sub Source #

Arguments

:: BotanMP

result

-> BotanMP

x

-> BotanMP

y

-> IO CInt 

botan_mp_mul Source #

Arguments

:: BotanMP

result

-> BotanMP

x

-> BotanMP

y

-> IO CInt 

botan_mp_div Source #

Arguments

:: BotanMP

quotient

-> BotanMP

remainder

-> BotanMP

x

-> BotanMP

y

-> IO CInt 

botan_mp_mod_mul Source #

Arguments

:: BotanMP

result

-> BotanMP

x

-> BotanMP

y

-> BotanMP

mod

-> IO CInt 

botan_mp_equal Source #

Arguments

:: BotanMP

x

-> BotanMP

y

-> IO CInt 

Returns 0 if x != y Returns 1 if x == y Returns negative number on error

botan_mp_cmp Source #

Arguments

:: Ptr CInt

result

-> BotanMP

x

-> BotanMP

y

-> IO CInt 

Sets *result to comparison result: -1 if x 0 if x == y, 1 if x y Returns negative number on error or zero on success

botan_mp_swap Source #

Arguments

:: BotanMP

x

-> BotanMP

y

-> IO CInt 

Swap two botan_mp_t

botan_mp_powmod Source #

Arguments

:: BotanMP

result

-> BotanMP

base

-> BotanMP

exponent

-> BotanMP

modulus

-> IO CInt 

Return (base^exponent) % modulus

botan_mp_lshift Source #

Arguments

:: BotanMP

result

-> BotanMP

n

-> CSize

shift

-> IO CInt 

botan_mp_rshift Source #

Arguments

:: BotanMP

result

-> BotanMP

n

-> CSize

shift

-> IO CInt 

botan_mp_mod_inverse Source #

Arguments

:: BotanMP

result

-> BotanMP

n

-> BotanMP

modulus

-> IO CInt 

botan_mp_rand_bits Source #

Arguments

:: BotanMP

rand_out

-> BotanRNG

rng

-> CSize

bits

-> IO CInt 

botan_mp_rand_range Source #

Arguments

:: BotanMP

rand_out

-> BotanRNG

rng

-> BotanMP

lower_bound

-> BotanMP

upper_bound

-> IO CInt 

botan_mp_gcd Source #

Arguments

:: BotanMP

out

-> BotanMP

x

-> BotanMP

y

-> IO CInt 

botan_mp_is_prime Source #

Arguments

:: BotanMP

n

-> BotanRNG

rng

-> CSize

test_prob

-> IO CInt 

Returns 0 if n is not prime Returns 1 if n is prime Returns negative number on error

botan_mp_get_bit Source #

Arguments

:: BotanMP

n

-> CSize

bit

-> IO CInt 

Returns 0 if specified bit of n is not set Returns 1 if specified bit of n is set Returns negative number on error

botan_mp_set_bit Source #

Arguments

:: BotanMP

n

-> CSize

bit

-> IO CInt 

Set the specified bit

botan_mp_clear_bit Source #

Arguments

:: BotanMP

n

-> CSize

bit

-> IO CInt 

Clear the specified bit