Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ArithCircuitProofError
- data ArithCircuitProof f p = ArithCircuitProof {
- tBlinding :: f
- mu :: f
- t :: f
- aiCommit :: p
- aoCommit :: p
- sCommit :: p
- tCommits :: [p]
- productProof :: InnerProductProof f p
- data ArithCircuit f = ArithCircuit {
- weights :: GateWeights f
- commitmentWeights :: [[f]]
- cs :: [f]
- data GateWeights f = GateWeights {}
- data ArithWitness f p = ArithWitness {
- assignment :: Assignment f
- commitments :: [p]
- commitBlinders :: [f]
- data Assignment f = Assignment {}
- padCircuit :: Num f => ArithCircuit f -> ArithCircuit f
- padAssignment :: Num f => Assignment f -> Assignment f
- delta :: Integer -> Fr -> [Fr] -> [Fr] -> Fr
- commitBitVector :: Fr -> [Fr] -> [Fr] -> PA
- shamirGxGxG :: PA -> PA -> PA -> Fr
- shamirGs :: [PA] -> Fr
- shamirZ :: Fr -> Fr
- evaluatePolynomial :: Num f => Integer -> [[f]] -> f -> [f]
- multiplyPoly :: Num n => [[n]] -> [[n]] -> [n]
- vectorMatrixProduct :: Num f => [f] -> [[f]] -> [f]
- vectorMatrixProductT :: Num f => [f] -> [[f]] -> [f]
- matrixVectorProduct :: Num f => [[f]] -> [f] -> [f]
- powerMatrix :: Num f => [[f]] -> Integer -> [[f]]
- matrixProduct :: Num a => [[a]] -> [[a]] -> [[a]]
- insertAt :: Int -> a -> [a] -> [a]
- genIdenMatrix :: Num f => Integer -> [[f]]
- genZeroMatrix :: Num f => Integer -> Integer -> [[f]]
- computeInputValues :: GateWeights Fr -> [[Fr]] -> Assignment Fr -> [Fr] -> [Fr]
- gaussianReduce :: [[Fr]] -> [[Fr]]
- substituteMatrix :: [[Fr]] -> [Fr]
- solveLinearSystem :: [[Fr]] -> [Fr]
- arithCircuitGen :: Integer -> Integer -> Gen (ArithCircuit Fr)
- arithAssignmentGen :: Integer -> Gen (Assignment Fr)
- arithWitnessGen :: Assignment Fr -> ArithCircuit Fr -> Integer -> Gen (ArithWitness Fr PA)
Documentation
data ArithCircuitProofError Source #
TooManyGates Integer | The number of gates is too high |
NNotPowerOf2 Integer | The number of gates is not a power of 2 |
Instances
Eq ArithCircuitProofError Source # | |
Defined in Bulletproofs.ArithmeticCircuit.Internal | |
Show ArithCircuitProofError Source # | |
Defined in Bulletproofs.ArithmeticCircuit.Internal showsPrec :: Int -> ArithCircuitProofError -> ShowS # show :: ArithCircuitProofError -> String # showList :: [ArithCircuitProofError] -> ShowS # |
data ArithCircuitProof f p Source #
ArithCircuitProof | |
|
Instances
data ArithCircuit f Source #
ArithCircuit | |
|
Instances
data GateWeights f Source #
Instances
data ArithWitness f p Source #
ArithWitness | |
|
Instances
data Assignment f Source #
Instances
padCircuit :: Num f => ArithCircuit f -> ArithCircuit f Source #
Pad circuit weights to make n be a power of 2, which is required to compute the inner product proof
padAssignment :: Num f => Assignment f -> Assignment f Source #
Pad assignment vectors to make their length n be a power of 2, which is required to compute the inner product proof
evaluatePolynomial :: Num f => Integer -> [[f]] -> f -> [f] Source #
multiplyPoly :: Num n => [[n]] -> [[n]] -> [n] Source #
vectorMatrixProduct :: Num f => [f] -> [[f]] -> [f] Source #
vectorMatrixProductT :: Num f => [f] -> [[f]] -> [f] Source #
matrixVectorProduct :: Num f => [[f]] -> [f] -> [f] Source #
powerMatrix :: Num f => [[f]] -> Integer -> [[f]] Source #
matrixProduct :: Num a => [[a]] -> [[a]] -> [[a]] Source #
genIdenMatrix :: Num f => Integer -> [[f]] Source #
computeInputValues :: GateWeights Fr -> [[Fr]] -> Assignment Fr -> [Fr] -> [Fr] Source #
gaussianReduce :: [[Fr]] -> [[Fr]] Source #
substituteMatrix :: [[Fr]] -> [Fr] Source #
solveLinearSystem :: [[Fr]] -> [Fr] Source #
arithCircuitGen :: Integer -> Integer -> Gen (ArithCircuit Fr) Source #
arithAssignmentGen :: Integer -> Gen (Assignment Fr) Source #
arithWitnessGen :: Assignment Fr -> ArithCircuit Fr -> Integer -> Gen (ArithWitness Fr PA) Source #