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

ZkFold.Symbolic.Data.Eq

Documentation

class Eq b a where Source #

Minimal complete definition

Nothing

Methods

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

default (==) :: (Generic a, GEq b (Rep a)) => a -> a -> b Source #

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

default (/=) :: (Generic a, GEq b (Rep a)) => a -> a -> b Source #

Instances

Instances details
Eq Bool String Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Eq Bool Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Eq Bool Bool Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

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

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

KnownNat n => Eq Bool (Zp n) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

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

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

(EllipticCurve curve, bool ~ BooleanOf curve) => Eq bool (CompressedPoint curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

(==) :: CompressedPoint curve -> CompressedPoint curve -> bool Source #

(/=) :: CompressedPoint curve -> CompressedPoint curve -> bool Source #

(EllipticCurve curve, bool ~ BooleanOf curve) => Eq bool (Point curve) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Methods

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

(/=) :: Point curve -> Point curve -> bool Source #

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

Defined in ZkFold.Symbolic.Data.Eq

Methods

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

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

(BoolType b, Eq b x0, Eq b x1) => Eq b (x0, x1) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: (x0, x1) -> (x0, x1) -> b Source #

(/=) :: (x0, x1) -> (x0, x1) -> b Source #

(BoolType bool, Eq bool field) => Eq bool (Ext2 field i) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: Ext2 field i -> Ext2 field i -> bool Source #

(/=) :: Ext2 field i -> Ext2 field i -> bool Source #

(BoolType bool, Eq bool field) => Eq bool (Ext3 field i) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: Ext3 field i -> Ext3 field i -> bool Source #

(/=) :: Ext3 field i -> Ext3 field i -> bool Source #

(BoolType b, Eq b x0, Eq b x1, Eq b x2) => Eq b (x0, x1, x2) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: (x0, x1, x2) -> (x0, x1, x2) -> b Source #

(/=) :: (x0, x1, x2) -> (x0, x1, x2) -> b Source #

(BoolType b, Eq b x0, Eq b x1, Eq b x2, Eq b x3) => Eq b (x0, x1, x2, x3) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: (x0, x1, x2, x3) -> (x0, x1, x2, x3) -> b Source #

(/=) :: (x0, x1, x2, x3) -> (x0, x1, x2, x3) -> b Source #

Symbolic c => Eq (Bool c) (Bool c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

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

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

Symbolic c => Eq (Bool c) (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

(Symbolic c, Eq (BaseField c), Representable f, Traversable f) => Eq (Bool c) (c f) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

(==) :: c f -> c f -> Bool c Source #

(/=) :: c f -> c f -> Bool c Source #

(Symbolic c, KnownNat n) => Eq (Bool c) (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

(==) :: ByteString n c -> ByteString n c -> Bool c Source #

(/=) :: ByteString n c -> ByteString n c -> Bool c Source #

Symbolic c => Eq (Bool c) (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Methods

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

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

(SymbolicOutput x, Context x ~ c, Eq (Bool c) x) => Eq (Bool c) (Maybe c x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Maybe

Methods

(==) :: Maybe c x -> Maybe c x -> Bool c Source #

(/=) :: Maybe c x -> Maybe c x -> Bool c Source #

(KnownRegisters c n r, Symbolic c) => Eq (Bool c) (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

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

(/=) :: UInt n r c -> UInt n r c -> Bool c Source #

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

class GEq b u where Source #

Methods

geq :: u x -> u x -> b Source #

gneq :: u x -> u x -> b Source #

Instances

Instances details
Eq b x => GEq b (Rec0 x :: k -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

geq :: forall (x0 :: k0). Rec0 x x0 -> Rec0 x x0 -> b Source #

gneq :: forall (x0 :: k0). Rec0 x x0 -> Rec0 x x0 -> b Source #

(BoolType b, GEq b u, GEq b v) => GEq b (u :*: v :: k -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

geq :: forall (x :: k0). (u :*: v) x -> (u :*: v) x -> b Source #

gneq :: forall (x :: k0). (u :*: v) x -> (u :*: v) x -> b Source #

GEq b v => GEq b (M1 i c v :: k -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq

Methods

geq :: forall (x :: k0). M1 i c v x -> M1 i c v x -> b Source #

gneq :: forall (x :: k0). M1 i c v x -> M1 i c v x -> b Source #