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

ZkFold.Symbolic.Data.Eq

Documentation

class BoolType b => Eq b a where Source #

Methods

(==) :: a -> a -> b infix 4 Source #

(/=) :: a -> a -> b infix 4 Source #

Instances

Instances details
(BoolType b, Eq x) => Eq b x Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: x -> x -> b Source #

(/=) :: x -> x -> b Source #

Arithmetic a => Eq (Bool (ArithmeticCircuit a)) (ArithmeticCircuit a) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Instance

SymbolicData a x => Eq (Bool (ArithmeticCircuit a)) (Structural x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq.Structural

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

(Arithmetic a, KnownNat n) => Eq (Bool (ArithmeticCircuit a)) (UInt n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

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

Defined in ZkFold.Symbolic.Data.Ed25519

Methods

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

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

Ord i => Eq (Bool (Sources a i)) (Sources a i) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MonadBlueprint

Methods

(==) :: Sources a i -> Sources a i -> Bool (Sources a i) Source #

(/=) :: Sources a i -> Sources a i -> Bool (Sources a i) Source #

(Arithmetic a, KnownNat tokens) => Eq (Bool (ArithmeticCircuit a)) (Output tokens datum (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Cardano.Types

Methods

(==) :: Output tokens datum (ArithmeticCircuit a) -> Output tokens datum (ArithmeticCircuit a) -> Bool (ArithmeticCircuit a) Source #

(/=) :: Output tokens datum (ArithmeticCircuit a) -> Output tokens datum (ArithmeticCircuit a) -> Bool (ArithmeticCircuit a) Source #

elem :: (Eq b a, Foldable t) => a -> t a -> b Source #