| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Bulletproofs.ArithmeticCircuit.Internal
Synopsis
- data ArithCircuitProofError
- data ArithCircuitProof f = ArithCircuitProof {}
- data ArithCircuit f = ArithCircuit {
- weights :: GateWeights f
- commitmentWeights :: [[f]]
- cs :: [f]
- data GateWeights f = GateWeights {}
- data ArithWitness f = ArithWitness {
- assignment :: Assignment f
- commitments :: [Point]
- commitBlinders :: [f]
- data Assignment f = Assignment {}
- padCircuit :: Num f => ArithCircuit f -> ArithCircuit f
- padAssignment :: Num f => Assignment f -> Assignment f
- delta :: KnownNat p => Integer -> PrimeField p -> [PrimeField p] -> [PrimeField p] -> PrimeField p
- commitBitVector :: KnownNat p => PrimeField p -> [PrimeField p] -> [PrimeField p] -> Point
- shamirGxGxG :: (Show f, Num f) => Point -> Point -> Point -> f
- shamirGs :: (Show f, Num f) => [Point] -> f
- shamirZ :: (Show f, Num f) => f -> f
- 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 :: KnownNat p => GateWeights (PrimeField p) -> [[PrimeField p]] -> Assignment (PrimeField p) -> [PrimeField p] -> [PrimeField p]
- gaussianReduce :: KnownNat p => [[PrimeField p]] -> [[PrimeField p]]
- substituteMatrix :: KnownNat p => [[PrimeField p]] -> [PrimeField p]
- solveLinearSystem :: KnownNat p => [[PrimeField p]] -> [PrimeField p]
- arithCircuitGen :: forall p. KnownNat p => Integer -> Integer -> Gen (ArithCircuit (PrimeField p))
- arithAssignmentGen :: KnownNat p => Integer -> Gen (Assignment (PrimeField p))
- arithWitnessGen :: KnownNat p => Assignment (PrimeField p) -> ArithCircuit (PrimeField p) -> Integer -> Gen (ArithWitness (PrimeField p))
Documentation
data ArithCircuitProofError Source #
Constructors
| 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 Methods (==) :: ArithCircuitProofError -> ArithCircuitProofError -> Bool # (/=) :: ArithCircuitProofError -> ArithCircuitProofError -> Bool # | |
| Show ArithCircuitProofError Source # | |
Defined in Bulletproofs.ArithmeticCircuit.Internal Methods showsPrec :: Int -> ArithCircuitProofError -> ShowS # show :: ArithCircuitProofError -> String # showList :: [ArithCircuitProofError] -> ShowS # | |
data ArithCircuitProof f Source #
Constructors
| ArithCircuitProof | |
Fields
| |
Instances
data ArithCircuit f Source #
Constructors
| ArithCircuit | |
Fields
| |
Instances
data GateWeights f Source #
Constructors
| GateWeights | |
Instances
data ArithWitness f Source #
Constructors
| ArithWitness | |
Fields
| |
Instances
data Assignment f Source #
Constructors
| Assignment | |
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
delta :: KnownNat p => Integer -> PrimeField p -> [PrimeField p] -> [PrimeField p] -> PrimeField p Source #
commitBitVector :: KnownNat p => PrimeField p -> [PrimeField p] -> [PrimeField p] -> Point Source #
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 :: KnownNat p => GateWeights (PrimeField p) -> [[PrimeField p]] -> Assignment (PrimeField p) -> [PrimeField p] -> [PrimeField p] Source #
gaussianReduce :: KnownNat p => [[PrimeField p]] -> [[PrimeField p]] Source #
substituteMatrix :: KnownNat p => [[PrimeField p]] -> [PrimeField p] Source #
solveLinearSystem :: KnownNat p => [[PrimeField p]] -> [PrimeField p] Source #
arithCircuitGen :: forall p. KnownNat p => Integer -> Integer -> Gen (ArithCircuit (PrimeField p)) Source #
arithAssignmentGen :: KnownNat p => Integer -> Gen (Assignment (PrimeField p)) Source #
arithWitnessGen :: KnownNat p => Assignment (PrimeField p) -> ArithCircuit (PrimeField p) -> Integer -> Gen (ArithWitness (PrimeField p)) Source #