hsblst-0.0.3: Haskell bindings to BLST
Safe HaskellNone
LanguageHaskell2010

Crypto.BLST.Internal.Classy

Description

Bindings with class.

Synopsis

Documentation

class (IsPoint (CurveToMsgPoint c), IsPoint (CurveToPkPoint c)) => IsCurve (c :: Curve) where Source #

Class for operations on curves.

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

Class for operations on points.

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

Class for encoding/hashing to curve.

Methods

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

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 #

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 #

type family CompressedSize (p :: PointKind) = (r :: Nat) | r -> p where ... Source #

Size of compressed serialized point.

type family CurveToMsgPoint (c :: Curve) = (r :: PointKind) | r -> c where ... Source #

Message/signature point depending on the curve.

type family CurveToPkPoint (c :: Curve) = (r :: PointKind) | r -> c where ... Source #

Public key point type depending on the curve.

Equations

CurveToPkPoint 'G1 = 'P1 
CurveToPkPoint 'G2 = 'P2 

type family SerializedSize (p :: PointKind) = (r :: Nat) | r -> p where ... Source #

Size of serialized point.