{-# LANGUAGE NoStarIsType #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module ZkFold.Base.Protocol.Plonkup.Relation where
import Data.Bool (bool)
import Data.Constraint (withDict)
import Data.Constraint.Nat (timesNat)
import Data.Foldable (toList)
import Data.Functor.Rep (Rep, Representable, tabulate)
import Data.Map (elems)
import qualified Data.Map.Monoidal as M
import Data.Maybe (fromJust)
import qualified Data.Set as S
import GHC.IsList (fromList)
import Prelude hiding (Num (..), drop, length, replicate, sum,
take, (!!), (/), (^))
import Test.QuickCheck (Arbitrary (..))
import ZkFold.Base.Algebra.Basic.Class
import ZkFold.Base.Algebra.Basic.Number
import ZkFold.Base.Algebra.Basic.Permutations (Permutation, fromCycles, mkIndexPartition)
import ZkFold.Base.Algebra.Polynomials.Multivariate (evalMonomial, evalPolynomial, var)
import ZkFold.Base.Algebra.Polynomials.Univariate (PolyVec, toPolyVec)
import ZkFold.Base.Protocol.Plonkup.Internal (PlonkupPermutationSize)
import ZkFold.Base.Protocol.Plonkup.LookupConstraint (LookupConstraint (..))
import ZkFold.Base.Protocol.Plonkup.PlonkConstraint (PlonkConstraint (..), toPlonkConstraint)
import ZkFold.Base.Protocol.Plonkup.PlonkupConstraint
import ZkFold.Prelude (length, replicate)
import ZkFold.Symbolic.Compiler
import ZkFold.Symbolic.Compiler.ArithmeticCircuit.Internal
data PlonkupRelation p i n l a = PlonkupRelation
{ forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qM :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qL :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qR :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qO :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qC :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qK :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
t :: PolyVec a n
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> Permutation (3 * n)
sigma :: Permutation (3 * n)
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a
-> p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
witness :: p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
, forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> p a -> i a -> l a
pubInput :: p a -> i a -> l a
}
instance Show a => Show (PlonkupRelation p i n l a) where
show :: PlonkupRelation p i n l a -> String
show PlonkupRelation {PolyVec a n
Permutation (3 * n)
p a -> i a -> l a
p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
qM :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qL :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qR :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qO :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qC :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
qK :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
t :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> PolyVec a n
sigma :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> Permutation (3 * n)
witness :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a
-> p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
pubInput :: forall (p :: Type -> Type) (i :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
PlonkupRelation p i n l a -> p a -> i a -> l a
qM :: PolyVec a n
qL :: PolyVec a n
qR :: PolyVec a n
qO :: PolyVec a n
qC :: PolyVec a n
qK :: PolyVec a n
t :: PolyVec a n
sigma :: Permutation (3 * n)
witness :: p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
pubInput :: p a -> i a -> l a
..} =
String
"Plonkup Relation: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
qM String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
qL String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
qR String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
qO String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
qC String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
qK String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PolyVec a n -> String
forall a. Show a => a -> String
show PolyVec a n
t String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Permutation (3 * n) -> String
forall a. Show a => a -> String
show Permutation (3 * n)
sigma
instance
( KnownNat n
, KnownNat (PlonkupPermutationSize n)
, Representable p
, Representable i
, Representable l
, Foldable l
, Ord (Rep i)
, Arithmetic a
, Arbitrary (ArithmeticCircuit a p i l)
) => Arbitrary (PlonkupRelation p i n l a) where
arbitrary :: Gen (PlonkupRelation p i n l a)
arbitrary = Maybe (PlonkupRelation p i n l a) -> PlonkupRelation p i n l a
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (PlonkupRelation p i n l a) -> PlonkupRelation p i n l a)
-> (ArithmeticCircuit a p i l -> Maybe (PlonkupRelation p i n l a))
-> ArithmeticCircuit a p i l
-> PlonkupRelation p i n l a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArithmeticCircuit a p i l -> Maybe (PlonkupRelation p i n l a)
forall (i :: Type -> Type) (p :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
(KnownNat n, Arithmetic a, Ord (Rep i), Representable p,
Representable i, Representable l, Foldable l) =>
ArithmeticCircuit a p i l -> Maybe (PlonkupRelation p i n l a)
toPlonkupRelation (ArithmeticCircuit a p i l -> PlonkupRelation p i n l a)
-> Gen (ArithmeticCircuit a p i l)
-> Gen (PlonkupRelation p i n l a)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (ArithmeticCircuit a p i l)
forall a. Arbitrary a => Gen a
arbitrary
toPlonkupRelation ::
forall i p n l a .
( KnownNat n, Arithmetic a, Ord (Rep i)
, Representable p, Representable i, Representable l, Foldable l
) => ArithmeticCircuit a p i l -> Maybe (PlonkupRelation p i n l a)
toPlonkupRelation :: forall (i :: Type -> Type) (p :: Type -> Type) (n :: Natural)
(l :: Type -> Type) a.
(KnownNat n, Arithmetic a, Ord (Rep i), Representable p,
Representable i, Representable l, Foldable l) =>
ArithmeticCircuit a p i l -> Maybe (PlonkupRelation p i n l a)
toPlonkupRelation ArithmeticCircuit a p i l
ac =
let xPub :: l (Var a i)
xPub = ArithmeticCircuit a p i l -> l (Var a i)
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
ArithmeticCircuit a p i o -> o (Var a i)
acOutput ArithmeticCircuit a p i l
ac
pubInputConstraints :: [Poly a (Var a i) Natural]
pubInputConstraints = (Var a i -> Poly a (Var a i) Natural)
-> [Var a i] -> [Poly a (Var a i) Natural]
forall a b. (a -> b) -> [a] -> [b]
map Var a i -> Poly a (Var a i) Natural
forall c i j. Polynomial c i j => i -> Poly c i j
var (l (Var a i) -> [Var a i]
forall a. l a -> [a]
forall (t :: Type -> Type) a. Foldable t => t a -> [a]
toList l (Var a i)
xPub)
plonkConstraints :: [Poly a (Var a i) Natural]
plonkConstraints = (Poly a (SysVar i) Natural -> Poly a (Var a i) Natural)
-> [Poly a (SysVar i) Natural] -> [Poly a (Var a i) Natural]
forall a b. (a -> b) -> [a] -> [b]
map (((SysVar i -> Poly a (Var a i) Natural)
-> Mono (SysVar i) Natural -> Poly a (Var a i) Natural)
-> (SysVar i -> Poly a (Var a i) Natural)
-> Poly a (SysVar i) Natural
-> Poly a (Var a i) Natural
forall c i j b.
(AdditiveMonoid b, Scale c b) =>
((i -> b) -> Mono i j -> b) -> (i -> b) -> Poly c i j -> b
evalPolynomial (SysVar i -> Poly a (Var a i) Natural)
-> Mono (SysVar i) Natural -> Poly a (Var a i) Natural
forall i j b.
(MultiplicativeMonoid b, Exponent b j) =>
(i -> b) -> Mono i j -> b
evalMonomial (Var a i -> Poly a (Var a i) Natural
forall c i j. Polynomial c i j => i -> Poly c i j
var (Var a i -> Poly a (Var a i) Natural)
-> (SysVar i -> Var a i) -> SysVar i -> Poly a (Var a i) Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SysVar i -> Var a i
forall a (i :: Type -> Type). SysVar i -> Var a i
SysVar)) (Map ByteString (Poly a (SysVar i) Natural)
-> [Poly a (SysVar i) Natural]
forall k a. Map k a -> [a]
elems (ArithmeticCircuit a p i l
-> Map ByteString (Poly a (SysVar i) Natural)
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
ArithmeticCircuit a p i o -> Map ByteString (Constraint a i)
acSystem ArithmeticCircuit a p i l
ac))
rs :: [Natural]
rs = (a -> Natural) -> [a] -> [Natural]
forall a b. (a -> b) -> [a] -> [b]
map a -> Natural
a -> Const a
forall a. ToConstant a => a -> Const a
toConstant ([a] -> [Natural]) -> [a] -> [Natural]
forall a b. (a -> b) -> a -> b
$ MonoidalMap a (Set (SysVar i)) -> [a]
forall k a. MonoidalMap k a -> [k]
M.keys (MonoidalMap a (Set (SysVar i)) -> [a])
-> MonoidalMap a (Set (SysVar i)) -> [a]
forall a b. (a -> b) -> a -> b
$ ArithmeticCircuit a p i l -> MonoidalMap a (Set (SysVar i))
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
ArithmeticCircuit a p i o -> MonoidalMap a (Set (SysVar i))
acRange ArithmeticCircuit a p i l
ac
t :: PolyVec a n
t = Vector a -> PolyVec a n
forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (Natural -> Item (Vector a)) -> [Natural] -> [Item (Vector a)]
forall a b. (a -> b) -> [a] -> [b]
map Natural -> a
Natural -> Item (Vector a)
forall a b. FromConstant a b => a -> b
fromConstant ([Natural] -> [Item (Vector a)]) -> [Natural] -> [Item (Vector a)]
forall a b. (a -> b) -> a -> b
$ [Natural] -> [Natural] -> Bool -> [Natural]
forall a. a -> a -> Bool -> a
bool [] (Natural -> Natural -> [Natural]
forall a. Natural -> a -> [a]
replicate (forall (n :: Natural). KnownNat n => Natural
value @n Natural -> Natural -> Natural
-! [Natural] -> Natural
forall (t :: Type -> Type) a. Foldable t => t a -> Natural
length [Natural]
rs Natural -> Natural -> Natural
forall a. AdditiveSemigroup a => a -> a -> a
+ Natural
1) Natural
0 [Natural] -> [Natural] -> [Natural]
forall a. [a] -> [a] -> [a]
++ [ Natural
0 .. [Natural] -> Natural
forall a. HasCallStack => [a] -> a
head [Natural]
rs ]) (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Natural] -> Bool
forall a. [a] -> Bool
forall (t :: Type -> Type) a. Foldable t => t a -> Bool
null [Natural]
rs)
nLookup :: Natural
nLookup = Natural -> Natural -> Bool -> Natural
forall a. a -> a -> Bool -> a
bool Natural
0 ([Natural] -> Natural
forall a. HasCallStack => [a] -> a
head [Natural]
rs Natural -> Natural -> Natural
forall a. AdditiveSemigroup a => a -> a -> a
+ Natural
1) (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Natural] -> Bool
forall a. [a] -> Bool
forall (t :: Type -> Type) a. Foldable t => t a -> Bool
null [Natural]
rs)
xLookup :: [SysVar i]
xLookup = (Set (SysVar i) -> [SysVar i]) -> [Set (SysVar i)] -> [SysVar i]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> [b]) -> t a -> [b]
concatMap Set (SysVar i) -> [SysVar i]
forall a. Set a -> [a]
S.toList ([Set (SysVar i)] -> [SysVar i]) -> [Set (SysVar i)] -> [SysVar i]
forall a b. (a -> b) -> a -> b
$ MonoidalMap a (Set (SysVar i)) -> [Set (SysVar i)]
forall k a. MonoidalMap k a -> [a]
M.elems (ArithmeticCircuit a p i l -> MonoidalMap a (Set (SysVar i))
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
ArithmeticCircuit a p i o -> MonoidalMap a (Set (SysVar i))
acRange ArithmeticCircuit a p i l
ac)
n' :: Natural
n' = ArithmeticCircuit a p i l -> Natural
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
ArithmeticCircuit a p i o -> Natural
acSizeN ArithmeticCircuit a p i l
ac Natural -> Natural -> Natural
forall a. AdditiveSemigroup a => a -> a -> a
+ l (Rep l) -> Natural
forall (t :: Type -> Type) a. Foldable t => t a -> Natural
length (forall (f :: Type -> Type) a.
Representable f =>
(Rep f -> a) -> f a
tabulate @l Rep l -> Rep l
forall a. a -> a
id) Natural -> Natural -> Natural
forall a. AdditiveSemigroup a => a -> a -> a
+ [SysVar i] -> Natural
forall (t :: Type -> Type) a. Foldable t => t a -> Natural
length [SysVar i]
xLookup
plonkupSystem :: [PlonkupConstraint i a]
plonkupSystem = [[PlonkupConstraint i a]] -> [PlonkupConstraint i a]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat
[ (Poly a (Var a i) Natural -> PlonkupConstraint i a)
-> [Poly a (Var a i) Natural] -> [PlonkupConstraint i a]
forall a b. (a -> b) -> [a] -> [b]
map (PlonkConstraint i a -> PlonkupConstraint i a
forall (i :: Type -> Type) a.
PlonkConstraint i a -> PlonkupConstraint i a
ConsPlonk (PlonkConstraint i a -> PlonkupConstraint i a)
-> (Poly a (Var a i) Natural -> PlonkConstraint i a)
-> Poly a (Var a i) Natural
-> PlonkupConstraint i a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Poly a (Var a i) Natural -> PlonkConstraint i a
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
Poly a (Var a i) Natural -> PlonkConstraint i a
toPlonkConstraint) ([Poly a (Var a i) Natural]
pubInputConstraints [Poly a (Var a i) Natural]
-> [Poly a (Var a i) Natural] -> [Poly a (Var a i) Natural]
forall a. [a] -> [a] -> [a]
++ [Poly a (Var a i) Natural]
plonkConstraints)
, LookupConstraint i a -> PlonkupConstraint i a
forall (i :: Type -> Type) a.
LookupConstraint i a -> PlonkupConstraint i a
ConsLookup (LookupConstraint i a -> PlonkupConstraint i a)
-> (SysVar i -> LookupConstraint i a)
-> SysVar i
-> PlonkupConstraint i a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SysVar i -> LookupConstraint i a
forall {k} (i :: Type -> Type) (a :: k).
SysVar i -> LookupConstraint i a
LookupConstraint (SysVar i -> PlonkupConstraint i a)
-> [SysVar i] -> [PlonkupConstraint i a]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> [SysVar i]
xLookup
, Natural -> PlonkupConstraint i a -> [PlonkupConstraint i a]
forall a. Natural -> a -> [a]
replicate (forall (n :: Natural). KnownNat n => Natural
value @n Natural -> Natural -> Natural
-! Natural
n') PlonkupConstraint i a
forall (i :: Type -> Type) a. PlonkupConstraint i a
ConsExtra
]
qM :: PolyVec a n
qM = forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec @a @n (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (PlonkupConstraint i a -> a) -> [PlonkupConstraint i a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (PlonkConstraint i a -> a
forall (i :: Type -> Type) a. PlonkConstraint i a -> a
qm (PlonkConstraint i a -> a)
-> (PlonkupConstraint i a -> PlonkConstraint i a)
-> PlonkupConstraint i a
-> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlonkupConstraint i a -> PlonkConstraint i a
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> PlonkConstraint i a
getPlonkConstraint) [PlonkupConstraint i a]
plonkupSystem
qL :: PolyVec a n
qL = forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec @a @n (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (PlonkupConstraint i a -> a) -> [PlonkupConstraint i a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (PlonkConstraint i a -> a
forall (i :: Type -> Type) a. PlonkConstraint i a -> a
ql (PlonkConstraint i a -> a)
-> (PlonkupConstraint i a -> PlonkConstraint i a)
-> PlonkupConstraint i a
-> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlonkupConstraint i a -> PlonkConstraint i a
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> PlonkConstraint i a
getPlonkConstraint) [PlonkupConstraint i a]
plonkupSystem
qR :: PolyVec a n
qR = forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec @a @n (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (PlonkupConstraint i a -> a) -> [PlonkupConstraint i a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (PlonkConstraint i a -> a
forall (i :: Type -> Type) a. PlonkConstraint i a -> a
qr (PlonkConstraint i a -> a)
-> (PlonkupConstraint i a -> PlonkConstraint i a)
-> PlonkupConstraint i a
-> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlonkupConstraint i a -> PlonkConstraint i a
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> PlonkConstraint i a
getPlonkConstraint) [PlonkupConstraint i a]
plonkupSystem
qO :: PolyVec a n
qO = forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec @a @n (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (PlonkupConstraint i a -> a) -> [PlonkupConstraint i a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (PlonkConstraint i a -> a
forall (i :: Type -> Type) a. PlonkConstraint i a -> a
qo (PlonkConstraint i a -> a)
-> (PlonkupConstraint i a -> PlonkConstraint i a)
-> PlonkupConstraint i a
-> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlonkupConstraint i a -> PlonkConstraint i a
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> PlonkConstraint i a
getPlonkConstraint) [PlonkupConstraint i a]
plonkupSystem
qC :: PolyVec a n
qC = forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec @a @n (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (PlonkupConstraint i a -> a) -> [PlonkupConstraint i a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (PlonkConstraint i a -> a
forall (i :: Type -> Type) a. PlonkConstraint i a -> a
qc (PlonkConstraint i a -> a)
-> (PlonkupConstraint i a -> PlonkConstraint i a)
-> PlonkupConstraint i a
-> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlonkupConstraint i a -> PlonkConstraint i a
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> PlonkConstraint i a
getPlonkConstraint) [PlonkupConstraint i a]
plonkupSystem
qK :: PolyVec a n
qK = forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec @a @n (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (PlonkupConstraint i a -> a) -> [PlonkupConstraint i a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map PlonkupConstraint i a -> a
forall a (i :: Type -> Type).
FiniteField a =>
PlonkupConstraint i a -> a
isLookupConstraint [PlonkupConstraint i a]
plonkupSystem
a :: [Var a i]
a = (PlonkupConstraint i a -> Var a i)
-> [PlonkupConstraint i a] -> [Var a i]
forall a b. (a -> b) -> [a] -> [b]
map PlonkupConstraint i a -> Var a i
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> Var a i
getA [PlonkupConstraint i a]
plonkupSystem
b :: [Var a i]
b = (PlonkupConstraint i a -> Var a i)
-> [PlonkupConstraint i a] -> [Var a i]
forall a b. (a -> b) -> [a] -> [b]
map PlonkupConstraint i a -> Var a i
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> Var a i
getB [PlonkupConstraint i a]
plonkupSystem
c :: [Var a i]
c = (PlonkupConstraint i a -> Var a i)
-> [PlonkupConstraint i a] -> [Var a i]
forall a b. (a -> b) -> [a] -> [b]
map PlonkupConstraint i a -> Var a i
forall a (i :: Type -> Type).
(Ord a, FiniteField a, Ord (Rep i)) =>
PlonkupConstraint i a -> Var a i
getC [PlonkupConstraint i a]
plonkupSystem
sigma :: Permutation (3 * n)
sigma = ((KnownNat 3, KnownNat n) :- KnownNat (3 * n))
-> (KnownNat (3 * n) => Permutation (3 * n)) -> Permutation (3 * n)
forall (c :: Constraint) e r. HasDict c e => e -> (c => r) -> r
withDict (forall (n :: Natural) (m :: Natural).
(KnownNat n, KnownNat m) :- KnownNat (n * m)
timesNat @3 @n) (forall (n :: Natural) a.
KnownNat n =>
IndexPartition a -> Permutation n
fromCycles @(3*n) (IndexPartition (Var a i) -> Permutation (3 * n))
-> IndexPartition (Var a i) -> Permutation (3 * n)
forall a b. (a -> b) -> a -> b
$ Vector (Var a i) -> IndexPartition (Var a i)
forall a. Ord a => Vector a -> IndexPartition a
mkIndexPartition (Vector (Var a i) -> IndexPartition (Var a i))
-> Vector (Var a i) -> IndexPartition (Var a i)
forall a b. (a -> b) -> a -> b
$ [Item (Vector (Var a i))] -> Vector (Var a i)
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector (Var a i))] -> Vector (Var a i))
-> [Item (Vector (Var a i))] -> Vector (Var a i)
forall a b. (a -> b) -> a -> b
$ [Var a i]
a [Var a i] -> [Var a i] -> [Var a i]
forall a. [a] -> [a] -> [a]
++ [Var a i]
b [Var a i] -> [Var a i] -> [Var a i]
forall a. [a] -> [a] -> [a]
++ [Var a i]
c)
w1 :: p a -> i a -> PolyVec a n
w1 p a
e i a
i = Vector a -> PolyVec a n
forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (Var a i -> a) -> [Var a i] -> [a]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (ArithmeticCircuit a p i l -> p a -> i a -> Var a i -> a
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
(Arithmetic a, Representable p, Representable i) =>
ArithmeticCircuit a p i o -> p a -> i a -> Var a i -> a
indexW ArithmeticCircuit a p i l
ac p a
e i a
i) [Var a i]
a
w2 :: p a -> i a -> PolyVec a n
w2 p a
e i a
i = Vector a -> PolyVec a n
forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (Var a i -> a) -> [Var a i] -> [a]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (ArithmeticCircuit a p i l -> p a -> i a -> Var a i -> a
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
(Arithmetic a, Representable p, Representable i) =>
ArithmeticCircuit a p i o -> p a -> i a -> Var a i -> a
indexW ArithmeticCircuit a p i l
ac p a
e i a
i) [Var a i]
b
w3 :: p a -> i a -> PolyVec a n
w3 p a
e i a
i = Vector a -> PolyVec a n
forall c (size :: Natural).
(Ring c, KnownNat size) =>
Vector c -> PolyVec c size
toPolyVec (Vector a -> PolyVec a n) -> Vector a -> PolyVec a n
forall a b. (a -> b) -> a -> b
$ [Item (Vector a)] -> Vector a
forall l. IsList l => [Item l] -> l
fromList ([Item (Vector a)] -> Vector a) -> [Item (Vector a)] -> Vector a
forall a b. (a -> b) -> a -> b
$ (Var a i -> a) -> [Var a i] -> [a]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (ArithmeticCircuit a p i l -> p a -> i a -> Var a i -> a
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
(Arithmetic a, Representable p, Representable i) =>
ArithmeticCircuit a p i o -> p a -> i a -> Var a i -> a
indexW ArithmeticCircuit a p i l
ac p a
e i a
i) [Var a i]
c
witness :: p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
witness p a
e i a
i = (p a -> i a -> PolyVec a n
w1 p a
e i a
i, p a -> i a -> PolyVec a n
w2 p a
e i a
i, p a -> i a -> PolyVec a n
w3 p a
e i a
i)
pubInput :: p a -> i a -> l a
pubInput p a
e i a
i = (Var a i -> a) -> l (Var a i) -> l a
forall a b. (a -> b) -> l a -> l b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (ArithmeticCircuit a p i l -> p a -> i a -> Var a i -> a
forall a (p :: Type -> Type) (i :: Type -> Type)
(o :: Type -> Type).
(Arithmetic a, Representable p, Representable i) =>
ArithmeticCircuit a p i o -> p a -> i a -> Var a i -> a
indexW ArithmeticCircuit a p i l
ac p a
e i a
i) l (Var a i)
xPub
in if Natural -> Natural -> Natural
forall a. Ord a => a -> a -> a
max Natural
n' Natural
nLookup Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
<= forall (n :: Natural). KnownNat n => Natural
value @n
then PlonkupRelation p i n l a -> Maybe (PlonkupRelation p i n l a)
forall a. a -> Maybe a
Just (PlonkupRelation p i n l a -> Maybe (PlonkupRelation p i n l a))
-> PlonkupRelation p i n l a -> Maybe (PlonkupRelation p i n l a)
forall a b. (a -> b) -> a -> b
$ PlonkupRelation {PolyVec a n
Permutation (3 * n)
p a -> i a -> l a
p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
qM :: PolyVec a n
qL :: PolyVec a n
qR :: PolyVec a n
qO :: PolyVec a n
qC :: PolyVec a n
qK :: PolyVec a n
t :: PolyVec a n
sigma :: Permutation (3 * n)
witness :: p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
pubInput :: p a -> i a -> l a
t :: PolyVec a n
qM :: PolyVec a n
qL :: PolyVec a n
qR :: PolyVec a n
qO :: PolyVec a n
qC :: PolyVec a n
qK :: PolyVec a n
sigma :: Permutation (3 * n)
witness :: p a -> i a -> (PolyVec a n, PolyVec a n, PolyVec a n)
pubInput :: p a -> i a -> l a
..}
else Maybe (PlonkupRelation p i n l a)
forall a. Maybe a
Nothing