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

ZkFold.Base.Algebra.Basic.Class

Synopsis

Documentation

class FromConstant a b where Source #

Every algebraic structure has a handful of "constant types" related with it: natural numbers, integers, field of constants etc. This typeclass captures this relation.

Minimal complete definition

Nothing

Methods

fromConstant :: a -> b Source #

Builds an element of an algebraic structure from a constant.

fromConstant should preserve algebraic structure, e.g. if both the structure and the type of constants are additive monoids, the following should hold:

Homomorphism
fromConstant (c + d) == fromConstant c + fromConstant d

default fromConstant :: a ~ b => a -> b Source #

Instances

Instances details
FromConstant Integer Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

FromConstant Integer Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

FromConstant Natural Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

FromConstant Natural Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

FromConstant Natural Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

FromConstant a a Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

fromConstant :: a -> a Source #

KnownNat p => FromConstant Integer (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Integer -> Zp p Source #

FromConstant Integer a => FromConstant Integer (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

KnownNat p => FromConstant Natural (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Natural -> Zp p Source #

FromConstant Natural (UInt 11 'Auto c) => FromConstant Natural (UTCTime c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UTCTime

FromConstant Natural a => FromConstant Natural (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Binary a => FromConstant a (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

fromConstant :: a -> MerkleHash n Source #

FromConstant a (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

fromConstant :: a -> Maybe a Source #

FromConstant b a => FromConstant b [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

fromConstant :: b -> [a] Source #

FromConstant c c' => FromConstant c (Poly c') Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

fromConstant :: c -> Poly c' Source #

(Symbolic c, FromConstant k (BaseField c)) => FromConstant k (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

(Symbolic c, (m * 8) ~ n) => FromConstant ByteString (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(FromConstant Integer c, AdditiveMonoid c, KnownNat size) => FromConstant Integer (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

fromConstant :: Integer -> PolyVec c size Source #

FromConstant Integer (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

(Symbolic c, KnownNat n) => FromConstant Integer (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(FromConstant Natural c, AdditiveMonoid c, KnownNat size) => FromConstant Natural (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

fromConstant :: Natural -> PolyVec c size Source #

FromConstant Natural (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

FromConstant Natural (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

(Symbolic c, KnownNat n) => FromConstant Natural (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

FromConstant a (Var a i) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Internal

Methods

fromConstant :: a -> Var a i Source #

FromConstant a (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

fromConstant :: a -> WitnessF a v Source #

(FromConstant a (Zp p), Symbolic c) => FromConstant a (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

fromConstant :: a -> FFA p c Source #

FromConstant b a => FromConstant b (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

fromConstant :: b -> p -> a Source #

(FromConstant f f', Field f') => FromConstant f (Ext2 f' e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: f -> Ext2 f' e Source #

(FromConstant f f', Field f') => FromConstant f (Ext3 f' ip) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: f -> Ext3 f' ip Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => FromConstant Integer (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

fromConstant :: Integer -> UInt n r c Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => FromConstant Natural (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

fromConstant :: Natural -> UInt n r c Source #

FromConstant c' c => FromConstant c' (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

fromConstant :: c' -> Poly c i j Source #

FromConstant (Poly c) (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

fromConstant :: Poly c -> Poly c Source #

FromConstant (MerkleHash n) (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

FromConstant (FieldElement c) (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

FromConstant Natural a => FromConstant (Maybe Natural) (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

FromConstant [a] [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

fromConstant :: [a] -> [a] Source #

(Field f, Eq f, IrreduciblePoly f e) => FromConstant (Poly f) (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Poly f -> Ext2 f e Source #

(Field f, Eq f, IrreduciblePoly f e) => FromConstant (Poly f) (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Poly f -> Ext3 f e Source #

FromConstant (Ext2 f e) (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Ext2 f e -> Ext2 f e Source #

FromConstant (Ext3 f e) (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Ext3 f e -> Ext3 f e Source #

FromConstant (EuclideanF a v) (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

fromConstant :: EuclideanF a v -> WitnessF a v Source #

FromConstant (FFA p c) (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

fromConstant :: FFA p c -> FFA p c Source #

FromConstant (p -> a) (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

fromConstant :: (p -> a) -> p -> a Source #

FromConstant (Poly c i j) (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

fromConstant :: Poly c i j -> Poly c i j Source #

class ToConstant a where Source #

A class of algebraic structures which can be converted to "constant type" related with it: natural numbers, integers, rationals etc. Subject to the following law:

Inverse
fromConstant (toConstant x) == x

Associated Types

type Const a :: Type Source #

One of "constant types" related with a. Typically the smallest type among them by inclusion.

Methods

toConstant :: a -> Const a Source #

A way to turn element of a into a Const a. According to the law of ToConstant, has to be right inverse to fromConstant.

Instances

Instances details
ToConstant (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Associated Types

type Const (Zp p) Source #

Methods

toConstant :: Zp p -> Const (Zp p) Source #

ToConstant (MerkleHash ('Just n)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Associated Types

type Const (MerkleHash ('Just n)) Source #

ToConstant a => ToConstant (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Associated Types

type Const (Maybe a) Source #

Methods

toConstant :: Maybe a -> Const (Maybe a) Source #

ToConstant (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Associated Types

type Const (WitnessF a v) Source #

Methods

toConstant :: WitnessF a v -> Const (WitnessF a v) Source #

ToConstant (ByteString n (Interpreter (Zp p))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Associated Types

type Const (ByteString n (Interpreter (Zp p))) Source #

(KnownNat p, Arithmetic a) => ToConstant (FFA p (Interpreter a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Associated Types

type Const (FFA p (Interpreter a)) Source #

Methods

toConstant :: FFA p (Interpreter a) -> Const (FFA p (Interpreter a)) Source #

(Symbolic (Interpreter (Zp p)), KnownNat n, KnownRegisterSize r) => ToConstant (UInt n r (Interpreter (Zp p))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Associated Types

type Const (UInt n r (Interpreter (Zp p))) Source #

Methods

toConstant :: UInt n r (Interpreter (Zp p)) -> Const (UInt n r (Interpreter (Zp p))) Source #

class Scale b a where Source #

A class for actions where multiplicative notation is the most natural (including multiplication by constant itself).

Minimal complete definition

Nothing

Methods

scale :: b -> a -> a Source #

A left monoid action on a type. Should satisfy the following:

Compatibility
scale (c * d) a == scale c (scale d a)
Left identity
scale one a == a

If, in addition, a cast from constant is defined, they should agree:

Scale agrees
scale c a == fromConstant c * a
Cast agrees
fromConstant c == scale c one

If the action is on an abelian structure, scaling should respect it:

Left distributivity
scale c (a + b) == scale c a + scale c b
Right absorption
scale c zero == zero

If, in addition, the scaling itself is abelian, this structure should propagate:

Right distributivity
scale (c + d) a == scale c a + scale d a
Left absorption
scale zero a == zero

The default implementation is the multiplication by a constant.

default scale :: (FromConstant b a, MultiplicativeSemigroup a) => b -> a -> a Source #

Instances

Instances details
Scale Integer Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Scale Integer Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: Integer -> Bool -> Bool Source #

Scale Natural Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Scale Natural Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Scale Natural Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: Natural -> Bool -> Bool Source #

MultiplicativeSemigroup a => Scale a a Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: a -> a -> a Source #

KnownNat p => Scale Integer (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: Integer -> Zp p -> Zp p Source #

Scale Integer a => Scale Integer (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: Integer -> Maybe a -> Maybe a Source #

KnownNat p => Scale Natural (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: Natural -> Zp p -> Zp p Source #

Scale Natural a => Scale Natural (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: Natural -> Maybe a -> Maybe a Source #

Binary a => Scale a (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

scale :: a -> MerkleHash n -> MerkleHash n Source #

Scale a a => Scale a (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: a -> Maybe a -> Maybe a Source #

Scale b a => Scale b [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: b -> [a] -> [a] Source #

Scale k c => Scale k (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

scale :: k -> Poly c -> Poly c Source #

(Symbolic c, Scale k (BaseField c)) => Scale k (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Methods

scale :: k -> FieldElement c -> FieldElement c Source #

(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 #

Scale Integer (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

scale :: Integer -> WitnessF a v -> WitnessF a v 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 #

Scale Natural (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

scale :: Natural -> EuclideanF a v -> EuclideanF a v Source #

Scale Natural (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

scale :: Natural -> WitnessF a v -> WitnessF a v Source #

Scale a (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

scale :: a -> WitnessF a v -> WitnessF a v Source #

(KnownNat p, Scale a (Zp p), Symbolic c) => Scale a (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

scale :: a -> FFA p c -> FFA p c Source #

Scale b a => Scale b (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

scale :: b -> Vector n a -> Vector n a Source #

Scale b a => Scale b (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: b -> (p -> a) -> p -> a Source #

Scale c f => Scale c (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: c -> Ext2 f e -> Ext2 f e Source #

Scale c f => Scale c (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: c -> Ext3 f e -> Ext3 f e Source #

Scale c a => Scale c (SVector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Sparse.Vector

Methods

scale :: c -> SVector size a -> SVector size a Source #

Scale c' c => Scale c' (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

scale :: c' -> PolyVec c size -> PolyVec c size Source #

(EllipticCurve curve, Eq s, BinaryExpansion s, Bits s ~ [s]) => Scale s (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

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

(Symbolic c, KnownNat n, KnownRegisterSize r) => Scale Integer (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

scale :: Integer -> UInt n r c -> UInt n r c Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => Scale Natural (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

scale :: Natural -> UInt n r c -> UInt n r c Source #

Scale c' c => Scale c' (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

scale :: c' -> Poly c i j -> Poly c i j Source #

(Field c, Eq c) => Scale (Poly c) (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

scale :: Poly c -> Poly c -> Poly c Source #

Scale (MerkleHash n) (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Symbolic c => Scale (FieldElement c) (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

MultiplicativeSemigroup a => Scale [a] [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: [a] -> [a] -> [a] Source #

(EllipticCurve c, SymbolicData (Point c), l ~ Layout (Point c), Representable l, Traversable l, Representable (Payload (Point c)), ctx ~ Context (Point c), Symbolic ctx, a ~ BaseField ctx, bits ~ NumberOfBits a) => Scale (FieldElement ctx) (Point c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

Methods

scale :: FieldElement ctx -> Point c -> Point c Source #

(Field f, Eq f, IrreduciblePoly f e) => Scale (Ext2 f e) (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: Ext2 f e -> Ext2 f e -> Ext2 f e Source #

(Field f, Eq f, IrreduciblePoly f e) => Scale (Ext3 f e) (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: Ext3 f e -> Ext3 f e -> Ext3 f e Source #

(Field c, KnownNat size) => Scale (PolyVec c size) (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

scale :: PolyVec c size -> PolyVec c size -> PolyVec c size Source #

(KnownNat p, Symbolic c) => Scale (FFA p c) (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

scale :: FFA p c -> FFA p c -> FFA p c Source #

MultiplicativeSemigroup a => Scale (p -> a) (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

scale :: (p -> a) -> (p -> a) -> p -> a Source #

Polynomial c i j => Scale (Poly c i j) (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

scale :: Poly c i j -> Poly c i j -> Poly c i j Source #

class (FromConstant a a, Scale a a) => MultiplicativeSemigroup a where Source #

A class of types with a binary associative operation with a multiplicative feel to it. Not necessarily commutative.

Methods

(*) :: a -> a -> a infixl 7 Source #

A binary associative operation. The following should hold:

Associativity
x * (y * z) == (x * y) * z

Instances

Instances details
MultiplicativeSemigroup Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

MultiplicativeSemigroup BLS12_381_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

MultiplicativeSemigroup BN254_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

MultiplicativeSemigroup Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: Integer -> Integer -> Integer Source #

MultiplicativeSemigroup Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: Natural -> Natural -> Natural Source #

MultiplicativeSemigroup Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: Bool -> Bool -> Bool Source #

MultiplicativeSemigroup a => MultiplicativeSemigroup (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: NonZero a -> NonZero a -> NonZero a Source #

KnownNat p => MultiplicativeSemigroup (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(*) :: Zp p -> Zp p -> Zp p Source #

(Field c, Eq c) => MultiplicativeSemigroup (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(*) :: Poly c -> Poly c -> Poly c Source #

MultiplicativeSemigroup (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

(*) :: MerkleHash n -> MerkleHash n -> MerkleHash n Source #

Symbolic c => MultiplicativeSemigroup (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

MultiplicativeSemigroup a => MultiplicativeSemigroup (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: Maybe a -> Maybe a -> Maybe a Source #

MultiplicativeSemigroup a => MultiplicativeSemigroup [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: [a] -> [a] -> [a] Source #

(Field f, Eq f, IrreduciblePoly f e) => MultiplicativeSemigroup (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(*) :: Ext2 f e -> Ext2 f e -> Ext2 f e Source #

(Field f, Eq f, IrreduciblePoly f e) => MultiplicativeSemigroup (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(*) :: Ext3 f e -> Ext3 f e -> Ext3 f e Source #

Monomial i j => MultiplicativeSemigroup (Mono i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Monomial

Methods

(*) :: Mono i j -> Mono i j -> Mono i j Source #

(Field c, KnownNat size) => MultiplicativeSemigroup (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(*) :: PolyVec c size -> PolyVec c size -> PolyVec c size Source #

MultiplicativeSemigroup (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(*) :: EuclideanF a v -> EuclideanF a v -> EuclideanF a v Source #

MultiplicativeSemigroup (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(*) :: WitnessF a v -> WitnessF a v -> WitnessF a v Source #

(KnownNat p, Symbolic c) => MultiplicativeSemigroup (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

(*) :: FFA p c -> FFA p c -> FFA p c Source #

MultiplicativeSemigroup a => MultiplicativeSemigroup (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: (p -> a) -> (p -> a) -> p -> a Source #

Polynomial c i j => MultiplicativeSemigroup (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

(*) :: Poly c i j -> Poly c i j -> Poly c i j Source #

(Symbolic c, KnownNat n, KnownRegisterSize rs) => MultiplicativeSemigroup (UInt n rs c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(*) :: UInt n rs c -> UInt n rs c -> UInt n rs c Source #

class Exponent a b where Source #

A class for actions on types where exponential notation is the most natural (including an exponentiation itself).

Methods

(^) :: a -> b -> a Source #

A right action on a type.

If exponents form a semigroup, the following should hold:

Compatibility
a ^ (m * n) == (a ^ m) ^ n

If exponents form a monoid, the following should also hold:

Right identity
a ^ one == a

NOTE, however, that even if exponents form a semigroup, left distributivity (that a ^ (m + n) == (a ^ m) * (a ^ n)) is desirable but not required: otherwise instance for Bool as exponent could not be made lawful.

Instances

Instances details
Exponent Rational Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Exponent Rational Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Exponent BLS12_381_GT Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

Exponent BLS12_381_GT Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

Exponent BN254_GT Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

Exponent BN254_GT Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

Exponent Integer Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: Integer -> Natural -> Integer Source #

Exponent Natural Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: Natural -> Natural -> Natural Source #

(Semiring a, Eq a) => Exponent Bool a Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: Bool -> a -> Bool Source #

MultiplicativeMonoid a => Exponent a Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: a -> Bool -> a Source #

(MultiplicativeGroup a, Order a ~ p) => Exponent a (Zp p) Source #

Exponentiation by an element of a finite field is well-defined (and lawful) if and only if the base is a finite multiplicative group of a matching order.

Note that left distributivity is satisfied, meaning a ^ (m + n) = (a ^ m) * (a ^ n).

Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: a -> Zp p -> a Source #

Exponent a b => Exponent (NonZero a) b Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: NonZero a -> b -> NonZero a Source #

Prime p => Exponent (Zp p) Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: Zp p -> Integer -> Zp p Source #

KnownNat p => Exponent (Zp p) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: Zp p -> Natural -> Zp p Source #

(Field c, Eq c) => Exponent (Poly c) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(^) :: Poly c -> Natural -> Poly c Source #

Exponent (MerkleHash n) Integer Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

(^) :: MerkleHash n -> Integer -> MerkleHash n Source #

Exponent (MerkleHash n) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

(^) :: MerkleHash n -> Natural -> MerkleHash n Source #

Symbolic c => Exponent (FieldElement c) Integer Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Symbolic c => Exponent (FieldElement c) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Exponent a Integer => Exponent (Maybe a) Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: Maybe a -> Integer -> Maybe a Source #

Exponent a Natural => Exponent (Maybe a) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: Maybe a -> Natural -> Maybe a Source #

Exponent a b => Exponent [a] b Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: [a] -> b -> [a] Source #

Field (Ext2 f e) => Exponent (Ext2 f e) Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: Ext2 f e -> Integer -> Ext2 f e Source #

MultiplicativeMonoid (Ext2 f e) => Exponent (Ext2 f e) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: Ext2 f e -> Natural -> Ext2 f e Source #

Field (Ext3 f e) => Exponent (Ext3 f e) Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: Ext3 f e -> Integer -> Ext3 f e Source #

MultiplicativeMonoid (Ext3 f e) => Exponent (Ext3 f e) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(^) :: Ext3 f e -> Natural -> Ext3 f e Source #

(Monomial i j, Ring j) => Exponent (Mono i j) Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Monomial

Methods

(^) :: Mono i j -> Integer -> Mono i j Source #

Monomial i j => Exponent (Mono i j) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Monomial

Methods

(^) :: Mono i j -> Natural -> Mono i j Source #

(Field c, KnownNat size) => Exponent (PolyVec c size) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(^) :: PolyVec c size -> Natural -> PolyVec c size Source #

Exponent (EuclideanF a v) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(^) :: EuclideanF a v -> Natural -> EuclideanF a v Source #

Exponent (WitnessF a v) Integer Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(^) :: WitnessF a v -> Integer -> WitnessF a v Source #

Exponent (WitnessF a v) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(^) :: WitnessF a v -> Natural -> WitnessF a v Source #

(Prime p, Symbolic c) => Exponent (FFA p c) Integer Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

(^) :: FFA p c -> Integer -> FFA p c Source #

(KnownNat p, Symbolic c) => Exponent (FFA p c) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

(^) :: FFA p c -> Natural -> FFA p c Source #

Exponent a b => Exponent (p -> a) b Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: (p -> a) -> b -> p -> a Source #

Polynomial c i j => Exponent (Poly c i j) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

(^) :: Poly c i j -> Natural -> Poly c i j Source #

MultiplicativeMonoid (UInt n r c) => Exponent (UInt n r c) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(^) :: UInt n r c -> Natural -> UInt n r c Source #

class (MultiplicativeSemigroup a, Exponent a Natural) => MultiplicativeMonoid a where Source #

A class of types with a binary associative operation with a multiplicative feel to it and an identity element. Not necessarily commutative.

While exponentiation by a natural is specified as a constraint, a default implementation is provided as a natPow function. You can provide a faster alternative, but do not forget to check that it satisfies the following (in addition to the properties already stated in Exponent documentation):

Left identity
one ^ n == one
Absorption
a ^ 0 == one
Left distributivity
a ^ (m + n) == (a ^ m) * (a ^ n)

Finally, if the base monoid operation is commutative, power should distribute over (MultiplicativeSemigroup):

Right distributivity
(a * b) ^ n == (a ^ n) * (b ^ n)

Methods

one :: a Source #

An identity with respect to multiplication:

Left identity
one * x == x
Right identity
x * one == x

Instances

Instances details
MultiplicativeMonoid Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: Rational Source #

MultiplicativeMonoid BLS12_381_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

MultiplicativeMonoid BN254_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

Methods

one :: BN254_GT Source #

MultiplicativeMonoid Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: Integer Source #

MultiplicativeMonoid Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: Natural Source #

MultiplicativeMonoid Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: Bool Source #

MultiplicativeMonoid a => MultiplicativeMonoid (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: NonZero a Source #

KnownNat p => MultiplicativeMonoid (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

one :: Zp p Source #

(Field c, Eq c) => MultiplicativeMonoid (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

one :: Poly c Source #

MultiplicativeMonoid (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

one :: MerkleHash n Source #

Symbolic c => MultiplicativeMonoid (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Methods

one :: FieldElement c Source #

MultiplicativeMonoid a => MultiplicativeMonoid (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: Maybe a Source #

MultiplicativeMonoid a => MultiplicativeMonoid [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: [a] Source #

(Field f, Eq f, IrreduciblePoly f e) => MultiplicativeMonoid (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

one :: Ext2 f e Source #

(Field f, Eq f, IrreduciblePoly f e) => MultiplicativeMonoid (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

one :: Ext3 f e Source #

Monomial i j => MultiplicativeMonoid (Mono i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Monomial

Methods

one :: Mono i j Source #

(Field c, KnownNat size) => MultiplicativeMonoid (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

one :: PolyVec c size Source #

MultiplicativeMonoid (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

one :: EuclideanF a v Source #

MultiplicativeMonoid (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

one :: WitnessF a v Source #

(KnownNat p, Symbolic c) => MultiplicativeMonoid (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

one :: FFA p c Source #

MultiplicativeMonoid a => MultiplicativeMonoid (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: p -> a Source #

Polynomial c i j => MultiplicativeMonoid (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

one :: Poly c i j Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => MultiplicativeMonoid (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

one :: UInt n r c Source #

natPow :: MultiplicativeMonoid a => a -> Natural -> a Source #

A default implementation for natural exponentiation. Uses only (MultiplicativeSemigroup) and one so doesn't loop via an Exponent Natural a instance.

multiExp :: (MultiplicativeMonoid a, Exponent a b, Foldable t) => a -> t b -> a Source #

class (MultiplicativeMonoid a, Exponent a Integer) => MultiplicativeGroup a where Source #

A class of groups in a multiplicative notation.

While exponentiation by an integer is specified in a constraint, a default implementation is provided as an intPow function. You can provide a faster alternative yourself, but do not forget to check that your implementation computes the same results on all inputs.

Minimal complete definition

(invert | (/))

Methods

(/) :: a -> a -> a infixl 7 Source #

Division in a group. The following should hold:

Division
x / x == one
Cancellation
(y / x) * x == y
Agreement
x / y == x * invert y

invert :: a -> a Source #

Inverse in a group. The following should hold:

Left inverse
invert x * x == one
Right inverse
x * invert x == one
Agreement
invert x == one / x

Instances

Instances details
MultiplicativeGroup BLS12_381_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

MultiplicativeGroup BN254_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

MultiplicativeGroup Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(/) :: Bool -> Bool -> Bool Source #

invert :: Bool -> Bool Source #

Field a => MultiplicativeGroup (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(/) :: NonZero a -> NonZero a -> NonZero a Source #

invert :: NonZero a -> NonZero a Source #

MultiplicativeGroup a => MultiplicativeGroup [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(/) :: [a] -> [a] -> [a] Source #

invert :: [a] -> [a] Source #

(Monomial i j, Ring j) => MultiplicativeGroup (Mono i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Monomial

Methods

(/) :: Mono i j -> Mono i j -> Mono i j Source #

invert :: Mono i j -> Mono i j Source #

MultiplicativeGroup a => MultiplicativeGroup (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(/) :: (p -> a) -> (p -> a) -> p -> a Source #

invert :: (p -> a) -> p -> a Source #

intPow :: MultiplicativeGroup a => a -> Integer -> a Source #

A default implementation for integer exponentiation. Uses only natural exponentiation and invert so doesn't loop via an Exponent Integer a instance.

class FromConstant a a => AdditiveSemigroup a where Source #

A class of types with a binary associative, commutative operation.

Methods

(+) :: a -> a -> a infixl 6 Source #

A binary associative commutative operation. The following should hold:

Associativity
x + (y + z) == (x + y) + z
Commutativity
x + y == y + x

Instances

Instances details
AdditiveSemigroup Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

AdditiveSemigroup Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(+) :: Integer -> Integer -> Integer Source #

AdditiveSemigroup Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(+) :: Natural -> Natural -> Natural Source #

AdditiveSemigroup Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(+) :: Bool -> Bool -> Bool Source #

KnownNat p => AdditiveSemigroup (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(+) :: Zp p -> Zp p -> Zp p Source #

(Ring c, Eq c) => AdditiveSemigroup (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(+) :: Poly c -> Poly c -> Poly c Source #

AdditiveSemigroup (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

(+) :: MerkleHash n -> MerkleHash n -> MerkleHash n Source #

Symbolic c => AdditiveSemigroup (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

AdditiveSemigroup a => AdditiveSemigroup (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(+) :: Maybe a -> Maybe a -> Maybe a Source #

AdditiveSemigroup a => AdditiveSemigroup [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(+) :: [a] -> [a] -> [a] Source #

Field f => AdditiveSemigroup (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(+) :: Ext2 f e -> Ext2 f e -> Ext2 f e Source #

Field f => AdditiveSemigroup (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(+) :: Ext3 f e -> Ext3 f e -> Ext3 f e Source #

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

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

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

Ring c => AdditiveSemigroup (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(+) :: PolyVec c size -> PolyVec c size -> PolyVec c size Source #

(KnownNat size, AdditiveMonoid a, Eq a) => AdditiveSemigroup (SVector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Sparse.Vector

Methods

(+) :: SVector size a -> SVector size a -> SVector size a Source #

AdditiveSemigroup a => AdditiveSemigroup (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

(+) :: Vector n a -> Vector n a -> Vector n a Source #

AdditiveSemigroup (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(+) :: EuclideanF a v -> EuclideanF a v -> EuclideanF a v Source #

AdditiveSemigroup (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(+) :: WitnessF a v -> WitnessF a v -> WitnessF a v Source #

(KnownNat p, Symbolic c) => AdditiveSemigroup (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

(+) :: FFA p c -> FFA p c -> FFA p c Source #

AdditiveSemigroup a => AdditiveSemigroup (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(+) :: (p -> a) -> (p -> a) -> p -> a Source #

Polynomial c i j => AdditiveSemigroup (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

(+) :: Poly c i j -> Poly c i j -> Poly c i j Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => AdditiveSemigroup (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(+) :: UInt n r c -> UInt n r c -> UInt n r c Source #

class (AdditiveSemigroup a, Scale Natural a) => AdditiveMonoid a where Source #

A class of types with a binary associative, commutative operation and with an identity element.

While scaling by a natural is specified as a constraint, a default implementation is provided as a natScale function.

Methods

zero :: a Source #

An identity with respect to addition:

Identity
x + zero == x

Instances

Instances details
AdditiveMonoid Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: Rational Source #

AdditiveMonoid Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: Integer Source #

AdditiveMonoid Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: Natural Source #

AdditiveMonoid Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: Bool Source #

KnownNat p => AdditiveMonoid (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

zero :: Zp p Source #

(Ring c, Eq c) => AdditiveMonoid (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

zero :: Poly c Source #

AdditiveMonoid (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Methods

zero :: MerkleHash n Source #

Symbolic c => AdditiveMonoid (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

AdditiveMonoid a => AdditiveMonoid (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: Maybe a Source #

AdditiveMonoid a => AdditiveMonoid [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: [a] Source #

Field f => AdditiveMonoid (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

zero :: Ext2 f e Source #

Field f => AdditiveMonoid (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

zero :: Ext3 f e Source #

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

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

zero :: Point curve Source #

(Ring c, KnownNat size) => AdditiveMonoid (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

zero :: PolyVec c size Source #

(KnownNat size, AdditiveMonoid a, Eq a) => AdditiveMonoid (SVector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Sparse.Vector

Methods

zero :: SVector size a Source #

(AdditiveMonoid a, KnownNat n) => AdditiveMonoid (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

zero :: Vector n a Source #

AdditiveMonoid (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

zero :: EuclideanF a v Source #

AdditiveMonoid (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

zero :: WitnessF a v Source #

(KnownNat p, Symbolic c) => AdditiveMonoid (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

zero :: FFA p c Source #

AdditiveMonoid a => AdditiveMonoid (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

zero :: p -> a Source #

Polynomial c i j => AdditiveMonoid (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

zero :: Poly c i j Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => AdditiveMonoid (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

zero :: UInt n r c Source #

natScale :: AdditiveMonoid a => Natural -> a -> a Source #

A default implementation for natural scaling. Uses only (AdditiveSemigroup) and zero so doesn't loop via a Scale Natural a instance.

sum :: (Foldable t, AdditiveMonoid a) => t a -> a Source #

class (AdditiveMonoid a, Scale Integer a) => AdditiveGroup a where Source #

A class of abelian groups.

While scaling by an integer is specified in a constraint, a default implementation is provided as an intScale function.

Minimal complete definition

(negate | (-))

Methods

(-) :: a -> a -> a infixl 6 Source #

Subtraction in an abelian group. The following should hold:

Subtraction
x - x == zero
Agreement
x - y == x + negate y

negate :: a -> a Source #

Inverse in an abelian group. The following should hold:

Negative
x + negate x == zero
Agreement
negate x == zero - x

Instances

Instances details
AdditiveGroup Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

AdditiveGroup Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

AdditiveGroup Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(-) :: Bool -> Bool -> Bool Source #

negate :: Bool -> Bool Source #

KnownNat p => AdditiveGroup (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(-) :: Zp p -> Zp p -> Zp p Source #

negate :: Zp p -> Zp p Source #

(Ring c, Eq c) => AdditiveGroup (Poly c) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(-) :: Poly c -> Poly c -> Poly c Source #

negate :: Poly c -> Poly c Source #

AdditiveGroup (MerkleHash ('Just n)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Symbolic c => AdditiveGroup (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

AdditiveGroup a => AdditiveGroup (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(-) :: Maybe a -> Maybe a -> Maybe a Source #

negate :: Maybe a -> Maybe a Source #

AdditiveGroup a => AdditiveGroup [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(-) :: [a] -> [a] -> [a] Source #

negate :: [a] -> [a] Source #

Field f => AdditiveGroup (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(-) :: Ext2 f e -> Ext2 f e -> Ext2 f e Source #

negate :: Ext2 f e -> Ext2 f e Source #

Field f => AdditiveGroup (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(-) :: Ext3 f e -> Ext3 f e -> Ext3 f e Source #

negate :: Ext3 f e -> Ext3 f e Source #

(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 #

(Ring c, KnownNat size) => AdditiveGroup (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Methods

(-) :: PolyVec c size -> PolyVec c size -> PolyVec c size Source #

negate :: PolyVec c size -> PolyVec c size Source #

(KnownNat size, AdditiveGroup a, Eq a) => AdditiveGroup (SVector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Sparse.Vector

Methods

(-) :: SVector size a -> SVector size a -> SVector size a Source #

negate :: SVector size a -> SVector size a Source #

(AdditiveGroup a, KnownNat n) => AdditiveGroup (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

(-) :: Vector n a -> Vector n a -> Vector n a Source #

negate :: Vector n a -> Vector n a Source #

AdditiveGroup (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(-) :: WitnessF a v -> WitnessF a v -> WitnessF a v Source #

negate :: WitnessF a v -> WitnessF a v Source #

(KnownNat p, Symbolic c) => AdditiveGroup (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

(-) :: FFA p c -> FFA p c -> FFA p c Source #

negate :: FFA p c -> FFA p c Source #

AdditiveGroup a => AdditiveGroup (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(-) :: (p -> a) -> (p -> a) -> p -> a Source #

negate :: (p -> a) -> p -> a Source #

Polynomial c i j => AdditiveGroup (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

Methods

(-) :: Poly c i j -> Poly c i j -> Poly c i j Source #

negate :: Poly c i j -> Poly c i j Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => AdditiveGroup (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(-) :: UInt n r c -> UInt n r c -> UInt n r c Source #

negate :: UInt n r c -> UInt n r c Source #

intScale :: AdditiveGroup a => Integer -> a -> a Source #

A default implementation for integer scaling. Uses only natural scaling and negate so doesn't loop via a Scale Integer a instance.

class (AdditiveMonoid a, MultiplicativeMonoid a, FromConstant Natural a) => Semiring a Source #

Class of semirings with both 0 and 1. The following should hold:

Left distributivity
a * (b + c) == a * b + a * c
Right distributivity
(a + b) * c == a * c + b * c

Instances

Instances details
Semiring Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Semiring Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Semiring Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Semiring Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

KnownNat p => Semiring (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Semiring (MerkleHash n) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Symbolic c => Semiring (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Semiring a => Semiring (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Semiring a => Semiring [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

(Field f, Eq f, IrreduciblePoly f e) => Semiring (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

(Field f, Eq f, IrreduciblePoly f e) => Semiring (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

(Field c, KnownNat size) => Semiring (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Semiring (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Semiring (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

(KnownNat p, Symbolic c) => Semiring (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Semiring a => Semiring (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Polynomial c i j => Semiring (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

(Symbolic c, KnownNat n, KnownRegisterSize r) => Semiring (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

class Semiring a => SemiEuclidean a where Source #

A semi-Euclidean-domain a is a semiring without zero divisors which can be endowed with at least one function f : a{0} -> R+ s.t. if x and y are in a and y is nonzero, then there exist q and r in a such that x = qy + r and either r = 0 or f(r) < f(y).

q and r are called respectively a quotient and a remainder of the division (or Euclidean division) of x by y.

The function divMod associated with this class produces q and r given a and b.

This is a generalization of a notion of Euclidean domains to semirings.

Minimal complete definition

divMod | div, mod

Methods

divMod :: a -> a -> (a, a) Source #

div :: a -> a -> a Source #

mod :: a -> a -> a Source #

Instances

Instances details
SemiEuclidean Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

SemiEuclidean Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

KnownNat p => SemiEuclidean (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

divMod :: Zp p -> Zp p -> (Zp p, Zp p) Source #

div :: Zp p -> Zp p -> Zp p Source #

mod :: Zp p -> Zp p -> Zp p Source #

SemiEuclidean (MerkleHash ('Nothing :: Maybe Natural)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

SemiEuclidean Natural => SemiEuclidean (Maybe Natural) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

SemiEuclidean (EuclideanF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

divMod :: EuclideanF a v -> EuclideanF a v -> (EuclideanF a v, EuclideanF a v) Source #

div :: EuclideanF a v -> EuclideanF a v -> EuclideanF a v Source #

mod :: EuclideanF a v -> EuclideanF a v -> EuclideanF a v Source #

(Symbolic c, KnownNat n, KnownNat r, KnownRegisterSize rs, r ~ NumberOfRegisters (BaseField c) n rs, KnownNat (Ceil (GetRegisterSize (BaseField c) n rs) OrdWord), NFData (c (Vector r))) => SemiEuclidean (UInt n rs c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

divMod :: UInt n rs c -> UInt n rs c -> (UInt n rs c, UInt n rs c) Source #

div :: UInt n rs c -> UInt n rs c -> UInt n rs c Source #

mod :: UInt n rs c -> UInt n rs c -> UInt n rs c Source #

class (Semiring a, AdditiveGroup a, FromConstant Integer a) => Ring a Source #

Class of rings with both 0, 1 and additive inverses. The following should hold:

Left distributivity
a * (b - c) == a * b - a * c
Right distributivity
(a - b) * c == a * c - b * c

Instances

Instances details
Ring Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Ring Integer Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Ring Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

KnownNat p => Ring (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Ring (MerkleHash ('Just n)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Symbolic c => Ring (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Ring a => Ring (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Ring a => Ring [a] Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

(Field f, Eq f, IrreduciblePoly f e) => Ring (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

(Field f, Eq f, IrreduciblePoly f e) => Ring (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

(Field c, KnownNat size) => Ring (PolyVec c size) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Univariate

Ring (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

(KnownNat p, Symbolic c) => Ring (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Ring a => Ring (p -> a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Polynomial c i j => Ring (Poly c i j) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Polynomial

(Symbolic c, KnownNat n, KnownRegisterSize r) => Ring (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

type Algebra b a = (Ring a, Scale b a, FromConstant b a) Source #

Type of modules/algebras over the base type of constants b. As all the required laws are implied by the constraints, this is simply an alias rather than a typeclass in its own right.

Note the following useful facts:

  • every Ring is an algebra over natural numbers and over integers;
  • every Ring is an algebra over itself. However, due to the possible overlapping instances of Scale a a and FromConstant a a you might need to defer the resolution of these constraints until a is specified.

class (Ring a, Exponent a Integer) => Field a where Source #

Class of fields. As a ring, each field is commutative, that is:

Commutativity
x * y == y * x

While exponentiation by an integer is specified in a constraint, a default implementation is provided as an intPowF function. You can provide a faster alternative yourself, but do not forget to check that your implementation computes the same results on all inputs.

Minimal complete definition

(finv | (//))

Methods

(//) :: a -> a -> a Source #

Division in a field. The following should hold:

Division
If x /= 0, x // x == one
Div by 0
x // zero == zero
Agreement
x // y == x * finv y

finv :: a -> a Source #

Inverse in a field. The following should hold:

Inverse
If x /= 0, x * inverse x == one
Inv of 0
inverse zero == zero
Agreement
finv x == one // x

rootOfUnity :: Natural -> Maybe a Source #

rootOfUnity n is an element of a characteristic 2^n, that is,

Root of 0
rootOfUnity 0 == Just one
Root property
If rootOfUnity n == Just x, x ^ (2 ^ n) == one
Smallest root
If rootOfUnity n == Just x and m < n, x ^ (2 ^ m) /= one
All roots
If rootOfUnity n == Just x and m < n, rootOfUnity m /= Nothing

Instances

Instances details
Field Rational Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Prime p => Field (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(//) :: Zp p -> Zp p -> Zp p Source #

finv :: Zp p -> Zp p Source #

rootOfUnity :: Natural -> Maybe (Zp p) Source #

Field (MerkleHash ('Just n)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Symbolic c => Field (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Field a => Field (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(//) :: Maybe a -> Maybe a -> Maybe a Source #

finv :: Maybe a -> Maybe a Source #

rootOfUnity :: Natural -> Maybe (Maybe a) Source #

(Field f, Eq f, IrreduciblePoly f e) => Field (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(//) :: Ext2 f e -> Ext2 f e -> Ext2 f e Source #

finv :: Ext2 f e -> Ext2 f e Source #

rootOfUnity :: Natural -> Maybe (Ext2 f e) Source #

(Field f, Eq f, IrreduciblePoly f e) => Field (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(//) :: Ext3 f e -> Ext3 f e -> Ext3 f e Source #

finv :: Ext3 f e -> Ext3 f e Source #

rootOfUnity :: Natural -> Maybe (Ext3 f e) Source #

Field (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Methods

(//) :: WitnessF a v -> WitnessF a v -> WitnessF a v Source #

finv :: WitnessF a v -> WitnessF a v Source #

rootOfUnity :: Natural -> Maybe (WitnessF a v) Source #

(Prime p, Symbolic c) => Field (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

(//) :: FFA p c -> FFA p c -> FFA p c Source #

finv :: FFA p c -> FFA p c Source #

rootOfUnity :: Natural -> Maybe (FFA p c) Source #

intPowF :: Field a => a -> Integer -> a Source #

A default implementation for integer exponentiation. Uses only natural exponentiation and finv so doesn't loop via an Exponent Integer a instance.

class (KnownNat (Order a), KnownNat (NumberOfBits a)) => Finite (a :: Type) Source #

Class of finite structures. Order a should be the actual number of elements in the type, identified up to the associated equality relation.

Associated Types

type Order a :: Natural Source #

Instances

Instances details
Finite BLS12_381_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

Associated Types

type Order BLS12_381_GT :: Natural Source #

Finite BN254_GT Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

Associated Types

type Order BN254_GT :: Natural Source #

(KnownNat (Order (NonZero a)), KnownNat (NumberOfBits (NonZero a))) => Finite (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Associated Types

type Order (NonZero a) :: Natural Source #

(KnownNat p, KnownNat (NumberOfBits (Zp p))) => Finite (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Associated Types

type Order (Zp p) :: Natural Source #

Finite (Zp n) => Finite (MerkleHash ('Just n)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MerkleHash

Associated Types

type Order (MerkleHash ('Just n)) :: Natural Source #

(KnownNat (Order (FieldElement c)), KnownNat (NumberOfBits (FieldElement c))) => Finite (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Associated Types

type Order (FieldElement c) :: Natural Source #

Finite a => Finite (Maybe a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Associated Types

type Order (Maybe a) :: Natural Source #

(KnownNat (Order (Ext2 f e)), KnownNat (NumberOfBits (Ext2 f e))) => Finite (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Associated Types

type Order (Ext2 f e) :: Natural Source #

(KnownNat (Order (Ext3 f e)), KnownNat (NumberOfBits (Ext3 f e))) => Finite (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Associated Types

type Order (Ext3 f e) :: Natural Source #

Finite a => Finite (WitnessF a v) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Witness

Associated Types

type Order (WitnessF a v) :: Natural Source #

Finite (Zp p) => Finite (FFA p b) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Associated Types

type Order (FFA p b) :: Natural Source #

order :: forall a. Finite a => Natural Source #

type NumberOfBits a = Log2 (Order a - 1) + 1 Source #

type FiniteField a = (Finite a, Field a) Source #

class Field a => DiscreteField' a where Source #

A field is a commutative ring in which an element is invertible if and only if it is nonzero. In a discrete field an element is invertible xor it equals zero. That is equivalent in classical logic but stronger in constructive logic. Every element is either 0 or invertible, and 0 ≠ 1.

We represent a discrete field as a field with an internal equality function which returns one for equal field elements and zero for distinct field elements.

Minimal complete definition

Nothing

Methods

equal :: a -> a -> a Source #

default equal :: Eq a => a -> a -> a Source #

Instances

Instances details
Prime p => DiscreteField' (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

equal :: Zp p -> Zp p -> Zp p Source #

class DiscreteField' a => TrichotomyField a where Source #

An ordering of a field is usually required to have compatibility laws with respect to addition and multiplication. However, we can drop that requirement and define a trichotomy field as one with an internal total ordering. We represent a trichotomy field as a discrete field with an internal comparison of field elements returning negate one for <, zero for =, and one for >. The law of trichotomy is that for any two field elements, exactly one of the relations =, or holds. Thus we require that -1, 0 and 1 are distinct field elements.

equal a b = one - (trichotomy a b)^2

Minimal complete definition

Nothing

Methods

trichotomy :: a -> a -> a Source #

default trichotomy :: Ord a => a -> a -> a Source #

Instances

Instances details
Prime p => TrichotomyField (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

trichotomy :: Zp p -> Zp p -> Zp p Source #

class Semiring a => BinaryExpansion a where Source #

Class of semirings where a binary expansion of elements can be computed. The methods store binary expansion of a as objects of type b. Note: numbers should convert to Little-endian bit representation.

The following should hold:

  • fromBinary . binaryExpansion == id
  • fromBinary xs == foldr (x y -> x + y + y) zero xs

Minimal complete definition

binaryExpansion

Associated Types

type Bits a :: Type Source #

Methods

binaryExpansion :: a -> Bits a Source #

fromBinary :: Bits a -> a Source #

default fromBinary :: Bits a ~ [a] => Bits a -> a Source #

Instances

Instances details
BinaryExpansion Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Associated Types

type Bits Natural Source #

BinaryExpansion Bool Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Associated Types

type Bits Bool Source #

Prime p => BinaryExpansion (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Associated Types

type Bits (Zp p) Source #

Methods

binaryExpansion :: Zp p -> Bits (Zp p) Source #

fromBinary :: Bits (Zp p) -> Zp p Source #

Symbolic c => BinaryExpansion (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Associated Types

type Bits (FieldElement c) Source #

padBits :: forall a. AdditiveMonoid a => Natural -> [a] -> [a] Source #

castBits :: (Semiring a, Eq a, Semiring b) => [a] -> [b] Source #

newtype NonZero a Source #

A multiplicative subgroup of nonzero elements of a field. TODO: hide constructor

Constructors

NonZero a 

Instances

Instances details
(KnownNat (Order (NonZero a)), KnownNat (NumberOfBits (NonZero a))) => Finite (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Associated Types

type Order (NonZero a) :: Natural Source #

Field a => MultiplicativeGroup (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(/) :: NonZero a -> NonZero a -> NonZero a Source #

invert :: NonZero a -> NonZero a Source #

MultiplicativeMonoid a => MultiplicativeMonoid (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

one :: NonZero a Source #

MultiplicativeSemigroup a => MultiplicativeSemigroup (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(*) :: NonZero a -> NonZero a -> NonZero a Source #

Exponent a b => Exponent (NonZero a) b Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

Methods

(^) :: NonZero a -> b -> NonZero a Source #

type Order (NonZero a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Class

type Order (NonZero a) = Order a - 1

(-!) :: Natural -> Natural -> Natural infixl 6 Source #