| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Crypto.BLST.Internal.Classy
Description
Bindings with class.
Synopsis
- class (IsPoint (CurveToMsgPoint c), IsPoint (CurveToPkPoint c)) => IsCurve (c :: Curve) where
- skToPkPoint :: Scalar -> IO (Point (CurveToPkPoint c))
 - signPk :: Point (CurveToMsgPoint c) -> Scalar -> IO (Point (CurveToMsgPoint c))
 - coreVerifyPk :: (ByteArrayAccess ba, ByteArrayAccess ba2) => Affine (CurveToPkPoint c) -> Affine (CurveToMsgPoint c) -> EncodeMethod -> ba -> Maybe ba2 -> IO BlstError
 - pairingChkNAggrPk :: ByteArrayAccess ba => PairingCtx -> Affine (CurveToPkPoint c) -> Bool -> Maybe (Affine (CurveToMsgPoint c)) -> Bool -> ba -> IO BlstError
 
 - class (KnownNat (SerializedSize p), KnownNat (CompressedSize p)) => IsPoint (p :: PointKind) where
- toAffine :: Point p -> IO (Affine p)
 - fromAffine :: Affine p -> IO (Point p)
 - affSerialize :: Affine p -> IO (SizedByteArray (SerializedSize p) Bytes)
 - affCompress :: Affine p -> IO (SizedByteArray (CompressedSize p) Bytes)
 - uncompress :: ByteArrayAccess ba => SizedByteArray (CompressedSize p) ba -> IO (Either BlstError (Affine p))
 - addOrDoubleAffine :: Point p -> Affine p -> IO (Point p)
 - deserialize :: ByteArrayAccess ba => SizedByteArray (SerializedSize p) ba -> IO (Either BlstError (Affine p))
 
 - class (IsCurve c, Demote meth) => ToCurve (meth :: EncodeMethod) (c :: Curve) where
- toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint c))
 
 - data Curve
 - type family CompressedSize (p :: PointKind) = (r :: Nat) | r -> p where ...
 - type family CurveToMsgPoint (c :: Curve) = (r :: PointKind) | r -> c where ...
 - type family CurveToPkPoint (c :: Curve) = (r :: PointKind) | r -> c where ...
 - type family SerializedSize (p :: PointKind) = (r :: Nat) | r -> p where ...
 
Documentation
class (IsPoint (CurveToMsgPoint c), IsPoint (CurveToPkPoint c)) => IsCurve (c :: Curve) where Source #
Class for operations on curves.
Methods
skToPkPoint :: Scalar -> IO (Point (CurveToPkPoint c)) Source #
signPk :: Point (CurveToMsgPoint c) -> Scalar -> IO (Point (CurveToMsgPoint c)) Source #
coreVerifyPk :: (ByteArrayAccess ba, ByteArrayAccess ba2) => Affine (CurveToPkPoint c) -> Affine (CurveToMsgPoint c) -> EncodeMethod -> ba -> Maybe ba2 -> IO BlstError Source #
pairingChkNAggrPk :: ByteArrayAccess ba => PairingCtx -> Affine (CurveToPkPoint c) -> Bool -> Maybe (Affine (CurveToMsgPoint c)) -> Bool -> ba -> IO BlstError Source #
Instances
class (KnownNat (SerializedSize p), KnownNat (CompressedSize p)) => IsPoint (p :: PointKind) where Source #
Class for operations on points.
Methods
toAffine :: Point p -> IO (Affine p) Source #
fromAffine :: Affine p -> IO (Point p) Source #
affSerialize :: Affine p -> IO (SizedByteArray (SerializedSize p) Bytes) Source #
affCompress :: Affine p -> IO (SizedByteArray (CompressedSize p) Bytes) Source #
uncompress :: ByteArrayAccess ba => SizedByteArray (CompressedSize p) ba -> IO (Either BlstError (Affine p)) Source #
addOrDoubleAffine :: Point p -> Affine p -> IO (Point p) Source #
deserialize :: ByteArrayAccess ba => SizedByteArray (SerializedSize p) ba -> IO (Either BlstError (Affine p)) Source #
Instances
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
| ToCurve 'Encode 'G1 Source # | |
Defined in Crypto.BLST.Internal.Classy Methods toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G1)) Source #  | |
| ToCurve 'Encode 'G2 Source # | |
Defined in Crypto.BLST.Internal.Classy Methods toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G2)) Source #  | |
| ToCurve 'Hash 'G1 Source # | |
Defined in Crypto.BLST.Internal.Classy Methods toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G1)) Source #  | |
| ToCurve 'Hash 'G2 Source # | |
Defined in Crypto.BLST.Internal.Classy Methods toCurve :: (ByteArrayAccess ba, ByteArrayAccess ba2) => ba -> Maybe ba2 -> IO (Point (CurveToMsgPoint 'G2)) Source #  | |
Curve data kind.
type family CompressedSize (p :: PointKind) = (r :: Nat) | r -> p where ... Source #
Size of compressed serialized point.
Equations
| CompressedSize 'P1 = P1CompressSize | |
| CompressedSize 'P2 = P2CompressSize | 
type family CurveToMsgPoint (c :: Curve) = (r :: PointKind) | r -> c where ... Source #
Message/signature point depending on the curve.
Equations
| CurveToMsgPoint 'G1 = 'P2 | |
| CurveToMsgPoint 'G2 = 'P1 | 
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.
Equations
| SerializedSize 'P1 = P1SerializeSize | |
| SerializedSize 'P2 = P2SerializeSize |