eccrypto-0.1.0: Elliptic Curve Cryptography for Haskell

Copyright(c) Marcel Fourné 20[14..]
LicenseBSD3
MaintainerMarcel Fourné (haskell@marcelfourne.de)
Stabilityalpha
PortabilityBad
Safe HaskellSafe
LanguageHaskell98

Crypto.ECC.Ed25519.Internal.Ed25519

Description

This module contain the internal functions. It's use should be limited to the Sign module, which exports certain types without constructors, so the timing attack surface is only over the verified functions. In other words: If an external module imports this module or uses unsafecoerce, it may circumvent the verifications against timing attacks!

Short-time plan: custom field arithmetic TODO: optimal const time inversion in 25519, see eccss-20130911b.pdf TODO: convert code to portable, get rid of Integer

Synopsis

Documentation

newtype Point Source #

twisted Edwards curve point, extended point format (x,y,z,t), neutral element (0,1,1,0), c=1, a=-1 https://hyperelliptic.org/EFD/g1p/auto-twisted-extended-1.html, after "Twisted Edwards curves revisited" eprint 2008/522

Constructors

Point (FPrime, FPrime, FPrime, FPrime) 
Instances
Eq Point Source # 
Instance details

Defined in Crypto.ECC.Ed25519.Internal.Ed25519

Methods

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

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

Show Point Source # 
Instance details

Defined in Crypto.ECC.Ed25519.Internal.Ed25519

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

data SigOK Source #

clear signal that everything is ok

Constructors

SigOK 
Instances
Eq SigOK Source # 
Instance details

Defined in Crypto.ECC.Ed25519.Internal.Ed25519

Methods

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

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

Show SigOK Source # 
Instance details

Defined in Crypto.ECC.Ed25519.Internal.Ed25519

Methods

showsPrec :: Int -> SigOK -> ShowS #

show :: SigOK -> String #

showList :: [SigOK] -> ShowS #

type VerifyResult = Either String SigOK Source #

Result of verifying a signature should only yield if it's good or bad, not more, but contains an error string if underlying primitives failed

type PubKey = ByteString Source #

just a newtype for the public key (string of 32 bytes, b=256 bit)

type PubKeyPoint = Point Source #

just a newtype for the public key as a point on the Edwards curve

newtype SecKey Source #

just a wrapper for the secret key (string of 32 bytes, b=256 bit)

Constructors

SecKeyBytes ByteString 

newtype SecFPrime Source #

just a wrapper for the secret key as a number

Constructors

SecNum FPrime 

type Signature = ByteString Source #

just a newtype for the signature (string of 2*32 bytes, b=256 bit)

type Message = ByteString Source #

just a newtype for the message

type SignedMessage = ByteString Source #

just a newtype for the signature with appended message

b :: Int Source #

working on exactly 256 bits

q :: FPrime Source #

the large prime

l :: FPrime Source #

curve parameter l, the group order, f.e. needed to use Farmat's little theorem

d :: FPrime Source #

curve parameter d, non-square element, -(121665/121666)

i :: FPrime Source #

sqrt (-1) on our curve

h :: ByteString -> ByteString Source #

wrapper for our hash function

ph :: ByteString -> ByteString Source #

the prehash function, id in PureEdDSA

by :: FPrime Source #

the y coordinate of the base point of the curve

inf :: Point Source #

additive neutral element, really (0,Z,Z,0)

null :: FPrime Source #

special form of FPrime, no bits set

eins :: FPrime Source #

special form of FPrime, lowest bit set

alleeins :: FPrime Source #

special form of FPrime, all bits set

xrecover :: FPrime -> Integer -> FPrime Source #

recover the x coordinate from the y coordinate and a signum

bPoint :: Point Source #

base point on the curve

pneg :: Point -> Point Source #

point negation

k :: FPrime Source #

k=2*d, constant used for point addition

padd :: Point -> Point -> Point Source #

point addition add-2008-hwcd-3

pdouble :: Point -> Point Source #

point doubling

pmul :: Point -> FPrime -> Point Source #

scalar multiplication, branchfree in k, pattern-matched branch on j (static known length of k)

ison :: Point -> Bool Source #

check if Point is on the curve, prevent some attacks

scale :: Point -> Point Source #

make scalar format Point from projective coordinates

pointtobs :: Point -> ByteString Source #

convert a point on the curve to a ByteString

bstopoint :: ByteString -> Either String Point Source #

convert a ByteString to a point on the curve

clamp :: ByteString -> Either String FPrime Source #

clamping of a string of bytes to make it suitable for usage on the (clamped) Edwards curve in Ed25519, reduces cofactor [ b Bits ] 001..1000 010..0 BigEndian 01x..x000 ==> ((getFPrime N) .&. (2^254-1-(2^0+2^1+2^2)) .|. (2^254)) .&. 28948022309329048855892746252171976963317496166410141009864396001978282409976 .|. 28948022309329048855892746252171976963317496166410141009864396001978282409984

convertLE8ByteTo64BE :: ByteString -> Either String FPrime Source #

convert an 8 Byte little endian ByteString to either an error String (if too short) or a big endian FPrime

convert64BEtoLE8Byte :: FPrime -> ByteString Source #

convert a big endian FPrime to an 8 Byte little endian ByteString

getFPrime32 :: ByteString -> Either String FPrime Source #

converts 32 little endian bytes into one FPrime

getFPrime64 :: ByteString -> Either String FPrime Source #

converts 64 little endian bytes into one FPrime

putFPrime :: FPrime -> ByteString Source #

converts one FPrime into exactly 32 little endian bytes