zkfold-base-0.1.0.0: ZkFold Symbolic compiler and zero-knowledge proof protocols
Safe HaskellSafe-Inferred
LanguageHaskell2010

ZkFold.Base.Algebra.EllipticCurve.Class

Documentation

data Point curve Source #

Constructors

Point 

Fields

Inf 

Instances

Instances details
(EllipticCurve curve, AdditiveGroup (BaseField curve)) => Scale Integer (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

scale :: Integer -> Point curve -> Point curve Source #

EllipticCurve curve => Scale Natural (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

scale :: Natural -> Point curve -> Point curve Source #

SymbolicData a (UInt 256 (ArithmeticCircuit a)) => SymbolicData a (Point (Ed25519 (ArithmeticCircuit a))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

(Ring a, Eq (Bool a) (BaseField (Ed25519 a))) => Eq (Bool a) (Point (Ed25519 a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

Methods

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

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

(EllipticCurve curve, Arbitrary (ScalarField curve)) => Arbitrary (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

arbitrary :: Gen (Point curve) #

shrink :: Point curve -> [Point curve] #

(EllipticCurve curve, Show (BaseField curve)) => Show (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

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

show :: Point curve -> String #

showList :: [Point curve] -> ShowS #

(EllipticCurve curve, Binary (BaseField curve)) => Binary (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

put :: Point curve -> Put #

get :: Get (Point curve) #

putList :: [Point curve] -> Put #

(EllipticCurve curve, Eq (BaseField curve)) => Eq (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

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

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

(EllipticCurve curve, AdditiveGroup (BaseField curve)) => AdditiveGroup (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

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

negate :: Point curve -> Point curve Source #

EllipticCurve curve => AdditiveMonoid (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

zero :: Point curve Source #

EllipticCurve curve => AdditiveSemigroup (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

(+) :: Point curve -> Point curve -> Point curve Source #

class EllipticCurve curve where Source #

Associated Types

type BaseField curve :: Type Source #

type ScalarField curve :: Type Source #

Methods

inf :: Point curve Source #

gen :: Point curve Source #

add :: Point curve -> Point curve -> Point curve Source #

mul :: ScalarField curve -> Point curve -> Point curve Source #

Instances

Instances details
EllipticCurve BLS12_381_G1 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

EllipticCurve BLS12_381_G2 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

EllipticCurve (Ed25519 Void) Source #

The purely mathematical implementation of Ed25519. It is available for use as-is and serves as "backend" for the UInt 256 (Zp p) implementation as well.

Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Ed25519

Associated Types

type BaseField (Ed25519 Void) Source #

type ScalarField (Ed25519 Void) Source #

Finite (Zp p) => EllipticCurve (Ed25519 (Zp p) :: Type) Source #

Ed25519 with UInt 256 (Zp p) as computational backend

Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

Associated Types

type BaseField (Ed25519 (Zp p)) Source #

type ScalarField (Ed25519 (Zp p)) Source #

Methods

inf :: Point (Ed25519 (Zp p)) Source #

gen :: Point (Ed25519 (Zp p)) Source #

add :: Point (Ed25519 (Zp p)) -> Point (Ed25519 (Zp p)) -> Point (Ed25519 (Zp p)) Source #

mul :: ScalarField (Ed25519 (Zp p)) -> Point (Ed25519 (Zp p)) -> Point (Ed25519 (Zp p)) Source #

(Arithmetic a, SymbolicData a (UInt 256 (ArithmeticCircuit a)), FromConstant Natural (UInt 512 (ArithmeticCircuit a)), EuclideanDomain (UInt 512 (ArithmeticCircuit a)), BinaryExpansion (UInt 256 (ArithmeticCircuit a))) => EllipticCurve (Ed25519 (ArithmeticCircuit a) :: Type) Source #

Ed25519 with UInt 256 (ArithmeticCircuit a) as computational backend

Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

class (EllipticCurve curve1, EllipticCurve curve2, ScalarField curve1 ~ ScalarField curve2, Eq t, MultiplicativeGroup t, Exponent t (ScalarField curve1)) => Pairing curve1 curve2 t | curve1 curve2 -> t where Source #

Methods

pairing :: Point curve1 -> Point curve2 -> t Source #

pointAdd :: Field (BaseField curve) => Eq (BaseField curve) => Point curve -> Point curve -> Point curve Source #

pointDouble :: Field (BaseField curve) => Point curve -> Point curve Source #

addPoints :: EllipticCurve curve => Field (BaseField curve) => Eq (BaseField curve) => Point curve -> Point curve -> Point curve Source #

pointNegate :: AdditiveGroup (BaseField curve) => Point curve -> Point curve Source #

pointMul :: forall curve. EllipticCurve curve => BinaryExpansion (ScalarField curve) => Eq (ScalarField curve) => ScalarField curve -> Point curve -> Point curve Source #