symbolic-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

IrreduciblePoly Fp "IP1" Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

IrreduciblePoly Fp2 "IP2" Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

IrreduciblePoly Fp6 "IP3" Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

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

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

Methods

parseJSON :: Value -> Parser (Zp p) #

parseJSONList :: Value -> Parser [Zp p] #

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 #

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

Associated Types

type Bits (Zp p) Source #

Methods

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

fromBinary :: Bits (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 #

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

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

Defined in ZkFold.Base.Algebra.Basic.Field

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 #

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 #

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

Defined in ZkFold.Symbolic.Data.UInt

Methods

strictConv :: Zp p -> UInt n r c Source #

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

Defined in ZkFold.Symbolic.Data.ByteString

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 #

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 #

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

Defined in ZkFold.Symbolic.Data.UInt

Methods

toJSON :: UInt n r (Interpreter (Zp p)) -> Value #

toEncoding :: UInt n r (Interpreter (Zp p)) -> Encoding #

toJSONList :: [UInt n r (Interpreter (Zp p))] -> Value #

toEncodingList :: [UInt n r (Interpreter (Zp p))] -> Encoding #

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

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" "symbolic-base-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Zp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
type Bits (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Bits (Zp p) = [Zp p]
type Const (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Const (Zp p) = Natural
type Order (Zp p) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

type Order (Zp p) = p
type Const (ByteString n (Interpreter (Zp p))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

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

Defined in ZkFold.Symbolic.Data.UInt

type Const (UInt n r (Interpreter (Zp p))) = Natural

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

IrreduciblePoly Fp2 "IP2" Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

IrreduciblePoly Fp6 "IP3" Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

(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) => 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, 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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

compare :: Ext2 f e -> Ext2 f e -> Ordering #

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

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

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

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

max :: Ext2 f e -> Ext2 f e -> Ext2 f e #

min :: Ext2 f e -> Ext2 f e -> Ext2 f e #

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 #

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 #

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

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

IrreduciblePoly Fp6 "IP3" Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.BN254

(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) => FromConstant (Poly f) (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

fromConstant :: Poly f -> 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 #

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

Defined in ZkFold.Base.Algebra.Basic.Field

Methods

compare :: Ext3 f e -> Ext3 f e -> Ordering #

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

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

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

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

max :: Ext3 f e -> Ext3 f e -> Ext3 f e #

min :: Ext3 f e -> Ext3 f e -> Ext3 f e #

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 #

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 #

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

type Order (Ext3 f e) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.Field

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