NaCl-0.0.5.0: Easy-and-safe-to-use high-level Haskell bindings to NaCl
Safe HaskellNone
LanguageHaskell2010

NaCl.Scalarmult

Description

Scalar multiplication in a group.

This is crypto_scalarmult_* from NaCl.

Note that this primitive is designed to only make the Computational Diffie–Hellman problem hard. It makes no promises about other assumptions, therefore it is the user’s responsibility to hash the output if required for the security of the specific application.

Synopsis

Documentation

newtype Point a Source #

Point in the group.

This type is parametrised by the actual data type that contains bytes. This can be, for example, a ByteString.

Instances

Instances details
ByteArray a => ByteArrayN CRYPTO_SCALARMULT_BYTES (Point a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

allocRet :: Proxy CRYPTO_SCALARMULT_BYTES -> (Ptr p -> IO a0) -> IO (a0, Point a) #

Eq a => Eq (Point a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

(==) :: Point a -> Point a -> Bool #

(/=) :: Point a -> Point a -> Bool #

Ord a => Ord (Point a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

compare :: Point a -> Point a -> Ordering #

(<) :: Point a -> Point a -> Bool #

(<=) :: Point a -> Point a -> Bool #

(>) :: Point a -> Point a -> Bool #

(>=) :: Point a -> Point a -> Bool #

max :: Point a -> Point a -> Point a #

min :: Point a -> Point a -> Point a #

Show a => Show (Point a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

showsPrec :: Int -> Point a -> ShowS #

show :: Point a -> String #

showList :: [Point a] -> ShowS #

ByteArrayAccess a => ByteArrayAccess (Point a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

length :: Point a -> Int #

withByteArray :: Point a -> (Ptr p -> IO a0) -> IO a0 #

copyByteArrayToPtr :: Point a -> Ptr p -> IO () #

toPoint :: ByteArrayAccess bytes => bytes -> Maybe (Point bytes) Source #

Convert bytes to a group point.

newtype Scalar a Source #

Scalar that can be used for group multiplication.

This type is parametrised by the actual data type that contains bytes. This can be, for example, a ByteString.

Instances

Instances details
ByteArray a => ByteArrayN CRYPTO_SCALARMULT_SCALARBYTES (Scalar a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

allocRet :: Proxy CRYPTO_SCALARMULT_SCALARBYTES -> (Ptr p -> IO a0) -> IO (a0, Scalar a) #

Eq a => Eq (Scalar a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

(==) :: Scalar a -> Scalar a -> Bool #

(/=) :: Scalar a -> Scalar a -> Bool #

Ord a => Ord (Scalar a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

compare :: Scalar a -> Scalar a -> Ordering #

(<) :: Scalar a -> Scalar a -> Bool #

(<=) :: Scalar a -> Scalar a -> Bool #

(>) :: Scalar a -> Scalar a -> Bool #

(>=) :: Scalar a -> Scalar a -> Bool #

max :: Scalar a -> Scalar a -> Scalar a #

min :: Scalar a -> Scalar a -> Scalar a #

Show a => Show (Scalar a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

showsPrec :: Int -> Scalar a -> ShowS #

show :: Scalar a -> String #

showList :: [Scalar a] -> ShowS #

ByteArrayAccess a => ByteArrayAccess (Scalar a) Source # 
Instance details

Defined in NaCl.Scalarmult

Methods

length :: Scalar a -> Int #

withByteArray :: Scalar a -> (Ptr p -> IO a0) -> IO a0 #

copyByteArrayToPtr :: Scalar a -> Ptr p -> IO () #

toScalar :: ByteArrayAccess bytes => bytes -> Maybe (Scalar bytes) Source #

Convert bytes to a scalar.

mult Source #

Arguments

:: forall outBytes pointBytes scalarBytes. (ByteArrayAccess pointBytes, ByteArrayAccess scalarBytes, ByteArray outBytes) 
=> Point pointBytes

Group point.

-> Scalar scalarBytes

Scalar.

-> Maybe (Point outBytes) 

Multiply a group point by an integer.

Note that this function is slightly different from the corresponding function in NaCl. Namely, unlike crypto_scalarmult in NaCl, this one will return Nothing if:

  • either the group point has a small order (1, 2, 4, or 8)
  • or the result of the multiplication is the identity point.

This is how it is implemented in libsodium.

multBase Source #

Arguments

:: forall outBytes scalarBytes. (ByteArrayAccess scalarBytes, ByteArray outBytes) 
=> Scalar scalarBytes

Scalar.

-> Point outBytes 

Multiply the standard group point by an integer.