cardano-crypto-class-2.1.1.0: Type classes abstracting over cryptography primitives for Cardano
Safe HaskellNone
LanguageHaskell2010

Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Synopsis

Unsafe Types

data PointPtr curve #

data AffinePtr curve #

Instances

Instances details
BLS curve => Eq (AffinePtr curve) # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Methods

(==) :: AffinePtr curve -> AffinePtr curve -> Bool Source #

(/=) :: AffinePtr curve -> AffinePtr curve -> Bool Source #

data PTPtr #

Phantom Types

Error codes

Safe types

data Affine curve #

Instances

Instances details
BLS curve => Eq (Affine curve) # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Methods

(==) :: Affine curve -> Affine curve -> Bool Source #

(/=) :: Affine curve -> Affine curve -> Bool Source #

data BLSTError #

Instances

Instances details
Bounded BLSTError # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Enum BLSTError # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Show BLSTError # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Eq BLSTError # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Ord BLSTError # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

data Point curve #

A point on an elliptic curve. This type guarantees that the point is part of the | prime order subgroup.

Instances

Instances details
BLS curve => Eq (Point curve) # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Methods

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

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

data PT #

Target element without the final exponantiation. By defining target elements | as such, we save up the final exponantiation when computing a pairing, and only | compute it when necessary (e.g. comparison with another point or serialisation)

Instances

Instances details
Eq PT # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Methods

(==) :: PT -> PT -> Bool Source #

(/=) :: PT -> PT -> Bool Source #

data Scalar #

Instances

Instances details
Eq Scalar # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

The period of scalars

scalarPeriod :: Integer #

The period of scalar modulo operations.

Curve abstraction

class BLS curve where #

BLS curve operations. Class methods are low-level; user code will want to use higher-level wrappers such as blsAddOrDouble, blsMult, blsCneg, blsNeg, etc.

Methods

c_blst_on_curve :: PointPtr curve -> IO Bool #

c_blst_add_or_double :: PointPtr curve -> PointPtr curve -> PointPtr curve -> IO () #

c_blst_mult :: PointPtr curve -> PointPtr curve -> ScalarPtr -> CSize -> IO () #

c_blst_cneg :: PointPtr curve -> Bool -> IO () #

c_blst_hash :: PointPtr curve -> Ptr CChar -> CSize -> Ptr CChar -> CSize -> Ptr CChar -> CSize -> IO () #

c_blst_compress :: Ptr CChar -> PointPtr curve -> IO () #

c_blst_serialize :: Ptr CChar -> PointPtr curve -> IO () #

c_blst_uncompress :: AffinePtr curve -> Ptr CChar -> IO CInt #

c_blst_deserialize :: AffinePtr curve -> Ptr CChar -> IO CInt #

c_blst_in_g :: PointPtr curve -> IO Bool #

c_blst_to_affine :: AffinePtr curve -> PointPtr curve -> IO () #

c_blst_from_affine :: PointPtr curve -> AffinePtr curve -> IO () #

c_blst_affine_in_g :: AffinePtr curve -> IO Bool #

c_blst_generator :: PointPtr curve #

c_blst_p_is_equal :: PointPtr curve -> PointPtr curve -> IO Bool #

c_blst_p_is_inf :: PointPtr curve -> IO Bool #

Instances

Instances details
BLS Curve1 # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

BLS Curve2 # 
Instance details

Defined in Cardano.Crypto.EllipticCurve.BLS12_381.Internal

Pairing check

FP12 functions

Scalar functions

Marshalling functions

sizePoint :: forall curve. BLS curve => Proxy curve -> Int #

Sizes of various representations of elliptic curve points. | Size of a curve point in memory

withPoint :: forall a curve. Point curve -> (PointPtr curve -> IO a) -> IO a #

withNewPoint :: forall curve a. BLS curve => (PointPtr curve -> IO a) -> IO (a, Point curve) #

withNewPoint_ :: BLS curve => (PointPtr curve -> IO a) -> IO a #

withNewPoint' :: BLS curve => (PointPtr curve -> IO a) -> IO (Point curve) #

clonePoint :: forall curve. BLS curve => Point curve -> IO (Point curve) #

compressedSizePoint :: forall curve. BLS curve => Proxy curve -> Int #

Size of a curved point when serialized in compressed form

serializedSizePoint :: forall curve. BLS curve => Proxy curve -> Int #

Size of a curved point when serialized in uncompressed form

sizeAffine :: forall curve. BLS curve => Proxy curve -> Int #

In-memory size of the affine representation of a curve point

withAffine :: forall a curve. Affine curve -> (AffinePtr curve -> IO a) -> IO a #

withNewAffine :: forall curve a. BLS curve => (AffinePtr curve -> IO a) -> IO (a, Affine curve) #

withNewAffine_ :: BLS curve => (AffinePtr curve -> IO a) -> IO a #

withNewAffine' :: BLS curve => (AffinePtr curve -> IO a) -> IO (Affine curve) #

withPT :: PT -> (PTPtr -> IO a) -> IO a #

withNewPT :: (PTPtr -> IO a) -> IO (a, PT) #

withNewPT_ :: (PTPtr -> IO a) -> IO a #

withNewPT' :: (PTPtr -> IO a) -> IO PT #

withScalar :: Scalar -> (ScalarPtr -> IO a) -> IO a #

withNewScalar :: (ScalarPtr -> IO a) -> IO (a, Scalar) #

withNewScalar_ :: (ScalarPtr -> IO a) -> IO a #

withFr :: Fr -> (FrPtr -> IO a) -> IO a #

withNewFr :: (FrPtr -> IO a) -> IO (a, Fr) #

withNewFr_ :: (FrPtr -> IO a) -> IO a #

withNewFr' :: (FrPtr -> IO a) -> IO Fr #

cloneFr :: Fr -> IO Fr #

Utility

integerAsCStrL :: Int -> Integer -> (Ptr CChar -> Int -> IO a) -> IO a #

Point1/G1 operations

blsInGroup :: BLS curve => Point curve -> Bool #

Check whether a point is in the group corresponding to its elliptic curve

blsAddOrDouble :: BLS curve => Point curve -> Point curve -> Point curve #

Curve point addition.

blsMult :: BLS curve => Point curve -> Integer -> Point curve #

Scalar multiplication of a curve point. The scalar will be brought into the range of modular arithmetic by means of a modulo operation over the scalarPeriod. Negative number will also be brought to the range [0, scalarPeriod - 1] via modular reduction.

blsCneg :: BLS curve => Point curve -> Bool -> Point curve #

Conditional curve point negation. blsCneg x cond = if cond then neg x else x

blsNeg :: BLS curve => Point curve -> Point curve #

Unconditional curve point negation

blsCompress :: forall curve. BLS curve => Point curve -> ByteString #

blsSerialize :: forall curve. BLS curve => Point curve -> ByteString #

blsUncompress :: forall curve. BLS curve => ByteString -> Either BLSTError (Point curve) #

blsDeserialize :: forall curve. BLS curve => ByteString -> Either BLSTError (Point curve) #

blsHash :: BLS curve => ByteString -> Maybe ByteString -> Maybe ByteString -> Point curve #

blsHash msg mDST mAug generates the elliptic curve blsHash for the given message msg; mDST and mAug are the optional aug and dst arguments.

blsGenerator :: BLS curve => Point curve #

blsIsInf :: BLS curve => Point curve -> Bool #

Infinity check on curve points.

blsZero :: forall curve. BLS curve => Point curve #

toAffine :: BLS curve => Point curve -> Affine curve #

fromAffine :: BLS curve => Affine curve -> Point curve #

affineInG :: BLS curve => Affine curve -> Bool #

PT operations

ptMult :: PT -> PT -> PT #

Scalar / Fr operations

Pairings