cryptonite-0.24: Cryptography Primitives sink

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Crypto.ECC

Description

Elliptic Curve Cryptography

Synopsis

Documentation

data Curve_P256R1 Source #

P256 Curve

also known as P256

Constructors

Curve_P256R1 

Instances

Data Curve_P256R1 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_P256R1 -> c Curve_P256R1 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_P256R1 #

toConstr :: Curve_P256R1 -> Constr #

dataTypeOf :: Curve_P256R1 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Curve_P256R1) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_P256R1) #

gmapT :: (forall b. Data b => b -> b) -> Curve_P256R1 -> Curve_P256R1 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P256R1 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P256R1 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Curve_P256R1 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_P256R1 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_P256R1 -> m Curve_P256R1 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P256R1 -> m Curve_P256R1 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P256R1 -> m Curve_P256R1 #

Show Curve_P256R1 Source # 
EllipticCurveArith Curve_P256R1 Source # 
EllipticCurveDH Curve_P256R1 Source # 
EllipticCurve Curve_P256R1 Source # 
type Point Curve_P256R1 Source # 
type Scalar Curve_P256R1 Source # 

data Curve_P384R1 Source #

Constructors

Curve_P384R1 

Instances

Data Curve_P384R1 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_P384R1 -> c Curve_P384R1 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_P384R1 #

toConstr :: Curve_P384R1 -> Constr #

dataTypeOf :: Curve_P384R1 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Curve_P384R1) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_P384R1) #

gmapT :: (forall b. Data b => b -> b) -> Curve_P384R1 -> Curve_P384R1 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P384R1 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P384R1 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Curve_P384R1 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_P384R1 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_P384R1 -> m Curve_P384R1 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P384R1 -> m Curve_P384R1 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P384R1 -> m Curve_P384R1 #

Show Curve_P384R1 Source # 
EllipticCurveArith Curve_P384R1 Source # 
EllipticCurveDH Curve_P384R1 Source # 
EllipticCurve Curve_P384R1 Source # 
type Point Curve_P384R1 Source # 
type Scalar Curve_P384R1 Source # 

data Curve_P521R1 Source #

Constructors

Curve_P521R1 

Instances

Data Curve_P521R1 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_P521R1 -> c Curve_P521R1 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_P521R1 #

toConstr :: Curve_P521R1 -> Constr #

dataTypeOf :: Curve_P521R1 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Curve_P521R1) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_P521R1) #

gmapT :: (forall b. Data b => b -> b) -> Curve_P521R1 -> Curve_P521R1 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P521R1 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P521R1 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Curve_P521R1 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_P521R1 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_P521R1 -> m Curve_P521R1 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P521R1 -> m Curve_P521R1 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P521R1 -> m Curve_P521R1 #

Show Curve_P521R1 Source # 
EllipticCurveArith Curve_P521R1 Source # 
EllipticCurveDH Curve_P521R1 Source # 
EllipticCurve Curve_P521R1 Source # 
type Point Curve_P521R1 Source # 
type Scalar Curve_P521R1 Source # 

data Curve_X25519 Source #

Constructors

Curve_X25519 

Instances

Data Curve_X25519 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_X25519 -> c Curve_X25519 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_X25519 #

toConstr :: Curve_X25519 -> Constr #

dataTypeOf :: Curve_X25519 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Curve_X25519) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_X25519) #

gmapT :: (forall b. Data b => b -> b) -> Curve_X25519 -> Curve_X25519 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X25519 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X25519 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Curve_X25519 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_X25519 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_X25519 -> m Curve_X25519 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X25519 -> m Curve_X25519 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X25519 -> m Curve_X25519 #

Show Curve_X25519 Source # 
EllipticCurveDH Curve_X25519 Source # 
EllipticCurve Curve_X25519 Source # 
type Point Curve_X25519 Source # 
type Scalar Curve_X25519 Source # 

data Curve_X448 Source #

Constructors

Curve_X448 

Instances

Data Curve_X448 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_X448 -> c Curve_X448 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_X448 #

toConstr :: Curve_X448 -> Constr #

dataTypeOf :: Curve_X448 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Curve_X448) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_X448) #

gmapT :: (forall b. Data b => b -> b) -> Curve_X448 -> Curve_X448 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X448 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X448 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Curve_X448 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_X448 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_X448 -> m Curve_X448 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X448 -> m Curve_X448 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X448 -> m Curve_X448 #

Show Curve_X448 Source # 
EllipticCurveDH Curve_X448 Source # 
EllipticCurve Curve_X448 Source # 
type Point Curve_X448 Source # 
type Scalar Curve_X448 Source # 

class EllipticCurve curve where Source #

Associated Types

type Point curve :: * Source #

Point on an Elliptic Curve

type Scalar curve :: * Source #

Scalar in the Elliptic Curve domain

Methods

curveGenerateScalar :: MonadRandom randomly => proxy curve -> randomly (Scalar curve) Source #

Generate a new random scalar on the curve. The scalar will represent a number between 1 and the order of the curve non included

curveGenerateKeyPair :: MonadRandom randomly => proxy curve -> randomly (KeyPair curve) Source #

Generate a new random keypair

curveSizeBits :: proxy curve -> Int Source #

Get the curve size in bits

encodePoint :: ByteArray bs => proxy curve -> Point curve -> bs Source #

Encode a elliptic curve point into binary form

decodePoint :: ByteArray bs => proxy curve -> bs -> CryptoFailable (Point curve) Source #

Try to decode the binary form of an elliptic curve point

Instances

EllipticCurve Curve_X448 Source # 
EllipticCurve Curve_X25519 Source # 
EllipticCurve Curve_P521R1 Source # 
EllipticCurve Curve_P384R1 Source # 
EllipticCurve Curve_P256R1 Source # 

class EllipticCurve curve => EllipticCurveDH curve where Source #

Minimal complete definition

ecdh

Methods

ecdhRaw :: proxy curve -> Scalar curve -> Point curve -> SharedSecret Source #

Generate a Diffie hellman secret value.

This is generally just the .x coordinate of the resulting point, that is not hashed.

use pointSmul to keep the result in Point format.

WARNING: Curve implementations may return a special value or an exception when the public point lies in a subgroup of small order. This function is adequate when the scalar is in expected range and contributory behaviour is not needed. Otherwise use ecdh.

ecdh :: proxy curve -> Scalar curve -> Point curve -> CryptoFailable SharedSecret Source #

Generate a Diffie hellman secret value and verify that the result is not the point at infinity.

This additional test avoids risks existing with function ecdhRaw. Implementations always return a CryptoError instead of a special value or an exception.

data KeyPair curve Source #

An elliptic curve key pair composed of the private part (a scalar), and the associated point.

Constructors

KeyPair 

Fields