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

ZkFold.Base.Algebra.Basic.Field

Documentation

data Zp (p :: Natural) Source #

Instances

Instances details
IrreduciblePoly Fq IP1 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

IrreduciblePoly Fq2 IP2 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

IrreduciblePoly Fq6 IP3 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

(KnownNat p, 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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Integer -> Zp p Source #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Natural -> Zp p 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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

scale :: Natural -> Zp p -> Zp p 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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

arbitrary :: Gen (Zp p) #

shrink :: Zp p -> [Zp p] #

FromJSON (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

ToJSON (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

toJSON :: Zp p -> Value #

toEncoding :: Zp p -> Encoding #

toJSONList :: [Zp p] -> Value #

toEncodingList :: [Zp p] -> Encoding #

omitField :: Zp p -> Bool #

Generic (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Associated Types

type Rep (Zp p) :: Type -> Type #

Methods

from :: Zp p -> Rep (Zp p) x #

to :: Rep (Zp p) x -> Zp p #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

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

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

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

negate :: Zp p -> Zp p #

abs :: Zp p -> Zp p #

signum :: Zp p -> Zp p #

fromInteger :: Integer -> Zp p #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

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

recip :: Zp p -> Zp p #

fromRational :: Rational -> Zp p #

Show (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

showsPrec :: Int -> Zp p -> ShowS #

show :: Zp p -> String #

showList :: [Zp p] -> ShowS #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

put :: Zp p -> Put #

get :: Get (Zp p) #

putList :: [Zp p] -> Put #

NFData (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

rnf :: Zp p -> () #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(==) :: Zp p -> Zp p -> Bool #

(/=) :: Zp p -> Zp p -> Bool #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

compare :: Zp p -> Zp p -> Ordering #

(<) :: Zp p -> Zp p -> Bool #

(<=) :: Zp p -> Zp p -> Bool #

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

(>=) :: Zp p -> Zp p -> Bool #

max :: Zp p -> Zp p -> Zp p #

min :: Zp p -> Zp p -> Zp p #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

randomR :: RandomGen g => (Zp p, Zp p) -> g -> (Zp p, g) #

random :: RandomGen g => g -> (Zp p, g) #

randomRs :: RandomGen g => (Zp p, Zp p) -> g -> [Zp p] #

randoms :: RandomGen g => g -> [Zp p] #

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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

zero :: Zp p Source #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

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

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

binaryExpansion :: Zp p -> [Zp p] Source #

fromBinary :: [Zp p] -> Zp p Source #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

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

KnownNat p => EuclideanDomain (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 #

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 #

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

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

one :: Zp p Source #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

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

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

Defined in ZkFold.Base.Algebra.Basic.Field

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

Defined in ZkFold.Base.Algebra.Basic.Field

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

trichotomy :: Zp p -> Zp p -> Zp p 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 #

ToConstant (Zp p) Natural Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

toConstant :: Zp p -> Natural Source #

(Prime p, Field x, Eq x) => DiscreteField (Bool (Zp p)) x Source # 
Instance details

Defined in ZkFold.Symbolic.Data.DiscreteField

Methods

isZero :: x -> Bool (Zp p) Source #

(Prime p, Ord x) => Ord (Bool (Zp p)) x Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

Methods

(<=) :: x -> x -> Bool (Zp p) Source #

(<) :: x -> x -> Bool (Zp p) Source #

(>=) :: x -> x -> Bool (Zp p) Source #

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

max :: x -> x -> x Source #

min :: x -> x -> x Source #

(Finite (Zp p), KnownNat n) => Eq (Bool (Zp p)) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(==) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(/=) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(Finite (Zp p), KnownNat n) => Ord (Bool (Zp p)) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(<=) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(<) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(>=) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(>) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

max :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

min :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => StrictConv (Zp p) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

strictConv :: Zp p -> UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => Arbitrary (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

arbitrary :: Gen (ByteString n (Zp p)) #

shrink :: ByteString n (Zp p) -> [ByteString n (Zp p)] #

(Finite (Zp p), KnownNat n) => Arbitrary (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

arbitrary :: Gen (UInt n (Zp p)) #

shrink :: UInt n (Zp p) -> [UInt n (Zp p)] #

(Finite (Zp p), KnownNat n) => AdditiveGroup (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

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

negate :: UInt n (Zp p) -> UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => AdditiveMonoid (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

zero :: UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => AdditiveSemigroup (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

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

(Finite (Zp p), KnownNat n) => EuclideanDomain (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

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

div :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

mod :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => MultiplicativeMonoid (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

one :: UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => MultiplicativeSemigroup (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

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

(Finite (Zp p), KnownNat n) => Ring (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

(Finite (Zp p), KnownNat n) => Semiring (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

(Finite (Zp p), KnownNat n) => BoolType (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

true :: ByteString n (Zp p) Source #

false :: ByteString n (Zp p) Source #

not :: ByteString n (Zp p) -> ByteString n (Zp p) Source #

(&&) :: ByteString n (Zp p) -> ByteString n (Zp p) -> ByteString n (Zp p) Source #

(||) :: ByteString n (Zp p) -> ByteString n (Zp p) -> ByteString n (Zp p) Source #

xor :: ByteString n (Zp p) -> ByteString n (Zp p) -> ByteString n (Zp p) Source #

(Finite (Zp p), KnownNat n) => ShiftBits (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Finite (Zp p), KnownNat n) => StrictNum (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

strictAdd :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

strictSub :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

strictMul :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => ToConstant (UInt n (Zp p)) Integer Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

toConstant :: UInt n (Zp p) -> Integer Source #

(Finite (Zp p), KnownNat n) => ToConstant (UInt n (Zp p)) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

toConstant :: UInt n (Zp p) -> Natural Source #

Substitution (Vector n b) (Zp n) b Source # 
Instance details

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

Methods

subs :: Vector n b -> Zp n -> b Source #

(KnownNat n, KnownNat m, m <= n, Mod n m ~ 0, Finite (Zp p)) => Concat (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Unfortunately, Haskell does not support dependent types yet, so we have no possibility to infer the exact type of the result (the list can contain an arbitrary number of words). We can only impose some restrictions on n and m.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

concat :: [ByteString m (Zp p)] -> ByteString n (Zp p) Source #

(KnownNat wordSize, KnownNat n, Finite (Zp p), wordSize <= n, 1 <= wordSize, 1 <= n, Mod n wordSize ~ 0) => ToWords (ByteString n (Zp p)) (ByteString wordSize (Zp p)) Source #

A ByteString of length n can only be split into words of length wordSize if all of the following conditions are met: 1. wordSize is not greater than n; 2. wordSize is not zero; 3. The bytestring is not empty; 4. wordSize divides n.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

toWords :: ByteString n (Zp p) -> [ByteString wordSize (Zp p)] Source #

(KnownNat m, KnownNat n, n <= m, Finite (Zp p)) => Truncate (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Only a bigger ByteString can be truncated into a smaller one.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

truncate :: ByteString m (Zp p) -> ByteString n (Zp p) Source #

(KnownNat n, m <= n, Finite (Zp p)) => Extend (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Only a smaller ByteString can be extended into a bigger one.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

extend :: ByteString m (Zp p) -> ByteString n (Zp p) Source #

(Finite (Zp p), KnownNat n, KnownNat m, n <= m) => Extend (UInt n (Zp p)) (UInt m (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

extend :: UInt n (Zp p) -> UInt m (Zp p) Source #

(Finite (Zp p), KnownNat n) => Iso (ByteString n (Zp p)) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

from :: ByteString n (Zp p) -> UInt n (Zp p) Source #

(Finite (Zp p), KnownNat n) => Iso (UInt n (Zp p)) (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

from :: UInt n (Zp p) -> ByteString n (Zp p) Source #

(Finite (Zp p), KnownNat n, KnownNat m, m <= n) => Shrink (UInt n (Zp p)) (UInt m (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

shrink :: UInt n (Zp p) -> UInt m (Zp p) Source #

type BaseField (Ed25519 (Zp p) :: Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

type BaseField (Ed25519 (Zp p) :: Type) = UInt 256 (Zp p)
type ScalarField (Ed25519 (Zp p) :: Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

type ScalarField (Ed25519 (Zp p) :: Type) = UInt 256 (Zp p)
type Rep (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Rep (Zp p) = D1 ('MetaData "Zp" "ZkFold.Base.Algebra.Basic.Field" "zkfold-base-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Zp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
type Order (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Order (Zp p) = p

toZp :: forall p. KnownNat p => Integer -> Zp p Source #

data Ext2 f (e :: Symbol) Source #

Constructors

Ext2 f f 

Instances

Instances details
IrreduciblePoly Fq2 IP2 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

IrreduciblePoly Fq6 IP3 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

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

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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

arbitrary :: Gen (Ext2 f e) #

shrink :: Ext2 f e -> [Ext2 f e] #

Show f => Show (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

showsPrec :: Int -> Ext2 f e -> ShowS #

show :: Ext2 f e -> String #

showList :: [Ext2 f e] -> ShowS #

Binary f => Binary (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

put :: Ext2 f e -> Put #

get :: Get (Ext2 f e) #

putList :: [Ext2 f e] -> Put #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(==) :: Ext2 f e -> Ext2 f e -> Bool #

(/=) :: Ext2 f e -> Ext2 f e -> Bool #

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 => AdditiveMonoid (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

zero :: Ext2 f e 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, 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 #

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

(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) => 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) => Ring (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

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

Defined in ZkFold.Base.Algebra.Basic.Field

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 #

type Order (Ext2 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Order (Ext2 f e) = Order f ^ 2

data Ext3 f (e :: Symbol) Source #

Constructors

Ext3 f f f 

Instances

Instances details
IrreduciblePoly Fq6 IP3 Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BLS12_381

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

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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

arbitrary :: Gen (Ext3 f e) #

shrink :: Ext3 f e -> [Ext3 f e] #

Show f => Show (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

showsPrec :: Int -> Ext3 f e -> ShowS #

show :: Ext3 f e -> String #

showList :: [Ext3 f e] -> ShowS #

Binary f => Binary (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

put :: Ext3 f e -> Put #

get :: Get (Ext3 f e) #

putList :: [Ext3 f e] -> Put #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

(==) :: Ext3 f e -> Ext3 f e -> Bool #

(/=) :: Ext3 f e -> Ext3 f e -> Bool #

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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

zero :: Ext3 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 #

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

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

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

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

(Field f, Eq f, IrreduciblePoly f e) => Ring (Ext3 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 (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 #

type Order (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Order (Ext3 f e) = Order f ^ 3