hsblst-0.0.3: Haskell bindings to BLST
Safe HaskellNone
LanguageHaskell2010

Crypto.BLST

Synopsis

Main functions

keygen :: forall ba (n :: Natural). (ByteArrayAccess ba, 32 <= n, KnownNat n) => SizedByteArray n ba -> SecretKey Source #

Generate a secret key from bytes.

skToPk :: forall (c :: Curve). IsCurve c => SecretKey -> PublicKey c Source #

Convert a secret key to the corresponding public key on a given curve.

sign Source #

Arguments

:: forall (c :: Curve) (m :: EncodeMethod) ba ba2. (ToCurve m c, ByteArrayAccess ba, ByteArrayAccess ba2) 
=> SecretKey

Secret key

-> ba

Message to sign

-> Maybe ba2

Optional domain separation tag

-> Signature c m 

Sign a single message.

verify Source #

Arguments

:: forall (c :: Curve) (m :: EncodeMethod) ba ba2. (IsCurve c, Demote m, ByteArrayAccess ba, ByteArrayAccess ba2) 
=> Signature c m

Signature

-> PublicKey c

Public key of the signer

-> ba

Message

-> Maybe ba2

Optional domain separation tag (must be the same as used for signing!)

-> BlstError 

Verify message signature.

serializePk :: forall (c :: Curve). IsCurve c => PublicKey c -> SizedByteArray (SerializedSize (CurveToPkPoint c)) Bytes Source #

Serialize public key.

deserializePk :: forall (c :: Curve) ba. (IsCurve c, ByteArrayAccess ba) => SizedByteArray (SerializedSize (CurveToPkPoint c)) ba -> Either BlstError (PublicKey c) Source #

Deserialize public key.

compressPk :: forall (c :: Curve). IsCurve c => PublicKey c -> SizedByteArray (CompressedSize (CurveToPkPoint c)) Bytes Source #

Compress public key.

decompressPk :: forall (c :: Curve) ba. (IsCurve c, ByteArrayAccess ba) => SizedByteArray (CompressedSize (CurveToPkPoint c)) ba -> Either BlstError (PublicKey c) Source #

Decompress public key.

serializeSignature :: forall (c :: Curve) (m :: EncodeMethod). IsCurve c => Signature c m -> SizedByteArray (SerializedSize (CurveToMsgPoint c)) Bytes Source #

Serialize message signature.

deserializeSignature :: forall (c :: Curve) (m :: EncodeMethod) ba. (IsCurve c, ByteArrayAccess ba) => SizedByteArray (SerializedSize (CurveToMsgPoint c)) ba -> Either BlstError (Signature c m) Source #

Deserialize message signature.

compressSignature :: forall (c :: Curve) (m :: EncodeMethod). IsCurve c => Signature c m -> SizedByteArray (CompressedSize (CurveToMsgPoint c)) Bytes Source #

Serialize and compress message signature.

decompressSignature :: forall (c :: Curve) (m :: EncodeMethod) ba. (IsCurve c, ByteArrayAccess ba) => SizedByteArray (CompressedSize (CurveToMsgPoint c)) ba -> Either BlstError (Signature c m) Source #

Decompress and deserialize message signature.

Aggregate signatures

aggregateSignatures :: forall (c :: Curve) (m :: EncodeMethod). IsCurve c => NonEmpty (Signature c m) -> Signature c m Source #

Aggregate multiple signatures.

aggregateVerify Source #

Arguments

:: forall (c :: Curve) (m :: EncodeMethod) ba ba2. (IsCurve c, Demote m, ByteArrayAccess ba, ByteArrayAccess ba2) 
=> NonEmpty (PublicKey c, ba)

Public keys with corresponding messages

-> Signature c m

Aggregate signature

-> Maybe ba2

Optional domain separation tag (must be the same as used for signing!)

-> Either BlstError Bool 

Aggregate signature verification.

Representation datatypes

data SecretKey Source #

Representation for the secret key.

Instances

Instances details
Show SecretKey Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

NFData SecretKey Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Methods

rnf :: SecretKey -> () #

Eq SecretKey Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

type ByteSize 'Serialize SecretKey Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

data PublicKey (c :: Curve) Source #

Public key representation.

Instances

Instances details
Show (PublicKey c) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

NFData (PublicKey c) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Methods

rnf :: PublicKey c -> () #

Eq (PublicKey c) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Methods

(==) :: PublicKey c -> PublicKey c -> Bool #

(/=) :: PublicKey c -> PublicKey c -> Bool #

type ByteSize 'Compress (PublicKey c) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

type ByteSize 'Serialize (PublicKey c) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

data Signature (c :: Curve) (m :: EncodeMethod) Source #

Signature representation.

Instances

Instances details
Show (Signature c m) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Methods

showsPrec :: Int -> Signature c m -> ShowS #

show :: Signature c m -> String #

showList :: [Signature c m] -> ShowS #

NFData (Signature c m) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Methods

rnf :: Signature c m -> () #

Eq (Signature c m) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Methods

(==) :: Signature c m -> Signature c m -> Bool #

(/=) :: Signature c m -> Signature c m -> Bool #

type ByteSize 'Compress (Signature c _1) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

type ByteSize 'Serialize (Signature c _1) Source # 
Instance details

Defined in Crypto.BLST.Internal.Types

Utility typeclasses

class (KnownNat (SerializedSize p), KnownNat (CompressedSize p)) => IsPoint (p :: PointKind) Source #

Class for operations on points.

class (IsCurve c, Demote meth) => ToCurve (meth :: EncodeMethod) (c :: Curve) Source #

Class for encoding/hashing to curve.

Minimal complete definition

toCurve

Instances

Instances details
ToCurve 'Encode 'G1 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G1)) Source #

ToCurve 'Encode 'G2 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G2)) Source #

ToCurve 'Hash 'G1 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G1)) Source #

ToCurve 'Hash 'G2 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G2)) Source #

class Demote (x :: k) Source #

Demotes a promoted data kind.

Minimal complete definition

demote

Instances

Instances details
Demote 'Encode Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Demote 'Hash Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Demote 'P1 Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Demote 'P2 Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Demote 'G1 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

demote :: Curve Source #

Demote 'G2 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

demote :: Curve Source #

Data kinds

data Curve Source #

Curve data kind.

Constructors

G1 
G2 

Instances

Instances details
Demote 'G1 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

demote :: Curve Source #

Demote 'G2 Source # 
Instance details

Defined in Crypto.BLST.Internal.Classy

Methods

demote :: Curve Source #

Typelevel byte sizes

type family ByteSize (soc :: SerializeOrCompress) a :: Nat Source #

Size in bytes of serialized/compressed representations of basic types.

data SerializeOrCompress Source #

Data kind flag for ByteSize.

Constructors

Serialize 
Compress 

Misc helpers

noDST :: Maybe Bytes Source #

Convenience synonym for Nothing. Do not use domain separation tag.

byteSize :: forall (soc :: SerializeOrCompress) a. KnownNat (ByteSize soc a) => Int Source #

Convenience function to get byte size as an Int value.