hsblst-0.0.1: Haskell bindings to BLST
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.BLST.Internal.Bindings.Types

Description

Types for lower-level bindings

Synopsis

Documentation

type SkSerializeSize = 32 Source #

Scalar serialized size.

type P2CompressSize = 96 Source #

Compressed serialized size of P2.

type P2SerializeSize = 192 Source #

Serialized size of P2.

type P1CompressSize = 48 Source #

Compressed serialized size of P1.

type P1SerializeSize = 96 Source #

Serialized size of P1.

newtype PairingCtx Source #

Pairing context.

Constructors

PairingCtx Bytes 

Instances

Instances details
NFData PairingCtx Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

rnf :: PairingCtx -> () #

newtype Scalar Source #

Scalar value representation.

Instances

Instances details
Show Scalar Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

NFData Scalar Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

rnf :: Scalar -> () #

Eq Scalar Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

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

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

type SizeOf Scalar Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf Scalar = 32

newtype Affine (a :: PointKind) Source #

Affine point representation.

Constructors

Affine 

Instances

Instances details
Show (Affine a) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

showsPrec :: Int -> Affine a -> ShowS #

show :: Affine a -> String #

showList :: [Affine a] -> ShowS #

NFData (Affine a) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

rnf :: Affine a -> () #

Eq (Affine a) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

(==) :: Affine a -> Affine a -> Bool #

(/=) :: Affine a -> Affine a -> Bool #

type SizeOf (Affine 'P1) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Affine 'P1) = 96
type SizeOf (Affine 'P2) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Affine 'P2) = 192

newtype Point (a :: PointKind) Source #

Point representation.

Constructors

Point (SizedByteArray (SizeOf (Point a)) Bytes) 

Instances

Instances details
Show (Point a) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

showsPrec :: Int -> Point a -> ShowS #

show :: Point a -> String #

showList :: [Point a] -> ShowS #

NFData (Point a) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

rnf :: Point a -> () #

Eq (Point a) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

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

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

type SizeOf (Point 'P1) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Point 'P1) = 144
type SizeOf (Point 'P2) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Point 'P2) = 288

type family SizeOf t Source #

Size of type's representation in bytes.

Instances

Instances details
type SizeOf Scalar Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf Scalar = 32
type SizeOf (Affine 'P1) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Affine 'P1) = 96
type SizeOf (Affine 'P2) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Affine 'P2) = 192
type SizeOf (Point 'P1) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Point 'P1) = 144
type SizeOf (Point 'P2) Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings

type SizeOf (Point 'P2) = 288

data PointKind Source #

Kind of point.

Constructors

P1 
P2 

Instances

Instances details
Demote 'P1 Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

demote :: k Source #

Demote 'P2 Source # 
Instance details

Defined in Crypto.BLST.Internal.Bindings.Types

Methods

demote :: k Source #