License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | Experimental |
Portability | Excellent |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Curve
- data Point
- type PublicPoint = Point
- type PrivateNumber = Integer
- data CurveBinary = CurveBinary Integer CurveCommon
- data CurvePrime = CurvePrime Integer CurveCommon
- common_curve :: Curve -> CurveCommon
- curveSizeBits :: Curve -> Int
- ecc_fx :: CurveBinary -> Integer
- ecc_p :: CurvePrime -> Integer
- data CurveCommon = CurveCommon {}
- data CurveName
- = SEC_p112r1
- | SEC_p112r2
- | SEC_p128r1
- | SEC_p128r2
- | SEC_p160k1
- | SEC_p160r1
- | SEC_p160r2
- | SEC_p192k1
- | SEC_p192r1
- | SEC_p224k1
- | SEC_p224r1
- | SEC_p256k1
- | SEC_p256r1
- | SEC_p384r1
- | SEC_p521r1
- | SEC_t113r1
- | SEC_t113r2
- | SEC_t131r1
- | SEC_t131r2
- | SEC_t163k1
- | SEC_t163r1
- | SEC_t163r2
- | SEC_t193r1
- | SEC_t193r2
- | SEC_t233k1
- | SEC_t233r1
- | SEC_t239k1
- | SEC_t283k1
- | SEC_t283r1
- | SEC_t409k1
- | SEC_t409r1
- | SEC_t571k1
- | SEC_t571r1
- getCurveByName :: CurveName -> Curve
Documentation
Define either a binary curve or a prime curve.
CurveF2m CurveBinary | 𝔽(2^m) |
CurveFP CurvePrime | 𝔽p |
Instances
Data Curve Source # | |
Defined in Crypto.PubKey.ECC.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve -> c Curve # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve # dataTypeOf :: Curve -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve) # gmapT :: (forall b. Data b => b -> b) -> Curve -> Curve # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve -> m Curve # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve -> m Curve # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve -> m Curve # | |
Read Curve Source # | |
Show Curve Source # | |
Eq Curve Source # | |
Define a point on a curve.
Instances
Data Point Source # | |
Defined in Crypto.PubKey.ECC.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point -> c Point # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Point # dataTypeOf :: Point -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Point) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point) # gmapT :: (forall b. Data b => b -> b) -> Point -> Point # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r # gmapQ :: (forall d. Data d => d -> u) -> Point -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Point -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point -> m Point # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point -> m Point # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point -> m Point # | |
Read Point Source # | |
Show Point Source # | |
NFData Point Source # | |
Defined in Crypto.PubKey.ECC.Types | |
Eq Point Source # | |
type PublicPoint = Point Source #
ECC Public Point
type PrivateNumber = Integer Source #
ECC Private Number
data CurveBinary Source #
Define an elliptic curve in 𝔽(2^m). The firt parameter is the Integer representatioin of the irreducible polynomial f(x).
Instances
data CurvePrime Source #
Define an elliptic curve in 𝔽p. The first parameter is the Prime Number.
Instances
common_curve :: Curve -> CurveCommon Source #
Parameters in common between binary and prime curves.
curveSizeBits :: Curve -> Int Source #
get the size of the curve in bits
ecc_fx :: CurveBinary -> Integer Source #
Irreducible polynomial representing the characteristic of a CurveBinary.
ecc_p :: CurvePrime -> Integer Source #
Prime number representing the characteristic of a CurvePrime.
data CurveCommon Source #
Define common parameters in a curve definition of the form: y^2 = x^3 + ax + b.
Instances
Recommended curves definition
Define names for known recommended curves.
Instances
getCurveByName :: CurveName -> Curve Source #
Get the curve definition associated with a recommended known curve name.