| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Bulletproofs.RangeProof.Internal
Synopsis
- data RangeProof f = RangeProof {}
- data RangeProofError
- data LRPolys f = LRPolys {}
- data TPoly f = TPoly {}
- encodeBit :: (AsInteger f, Num f) => Integer -> f -> [f]
- reversedEncodeBit :: (AsInteger f, Num f) => Integer -> f -> [f]
- reversedEncodeBitMulti :: (AsInteger f, Num f) => Integer -> [f] -> [f]
- complementaryVector :: Num a => [a] -> [a]
- fillWithZeros :: Num f => Integer -> [f] -> [f]
- obfuscateEncodedBits :: (Eq f, Field f) => Integer -> [f] -> [f] -> f -> f -> f
- obfuscateEncodedBitsSingle :: (Eq f, Field f) => Integer -> [f] -> [f] -> f -> f -> f
- commitBitVectors :: (MonadRandom m, AsInteger f) => f -> f -> [f] -> [f] -> [f] -> [f] -> m (Point, Point)
- delta :: (Eq f, Field f) => Integer -> Integer -> f -> f -> f
- checkRange :: Integer -> Integer -> Bool
- checkRanges :: Integer -> [Integer] -> Bool
- computeLRCommitment :: (AsInteger f, Eq f, Num f, Show f) => Integer -> Integer -> Point -> Point -> f -> f -> f -> f -> f -> f -> [Point] -> Point
Documentation
data RangeProof f Source #
Constructors
| RangeProof | |
Fields
| |
Instances
| Eq f => Eq (RangeProof f) Source # | |
Defined in Bulletproofs.RangeProof.Internal | |
| Show f => Show (RangeProof f) Source # | |
Defined in Bulletproofs.RangeProof.Internal Methods showsPrec :: Int -> RangeProof f -> ShowS # show :: RangeProof f -> String # showList :: [RangeProof f] -> ShowS # | |
data RangeProofError Source #
Constructors
| UpperBoundTooLarge Integer | The upper bound of the range is too large |
| ValueNotInRange Integer | Value is not within the range required |
| ValuesNotInRange [Integer] | Values are not within the range required |
| NNotPowerOf2 Integer | Dimension n is required to be a power of 2 |
Instances
| Eq RangeProofError Source # | |
Defined in Bulletproofs.RangeProof.Internal Methods (==) :: RangeProofError -> RangeProofError -> Bool # (/=) :: RangeProofError -> RangeProofError -> Bool # | |
| Show RangeProofError Source # | |
Defined in Bulletproofs.RangeProof.Internal Methods showsPrec :: Int -> RangeProofError -> ShowS # show :: RangeProofError -> String # showList :: [RangeProofError] -> ShowS # | |
encodeBit :: (AsInteger f, Num f) => Integer -> f -> [f] Source #
Encode the value v into a bit representation. Let aL be a vector of bits such that 2^n = v (put more simply, the components of a L are the binary digits of v).
reversedEncodeBit :: (AsInteger f, Num f) => Integer -> f -> [f] Source #
Bits of v reversed. v = 2^n = a_0 * 2^0 + ... + a_n-1 * 2^(n-1)
complementaryVector :: Num a => [a] -> [a] Source #
In order to prove that v is in range, each element of aL is either 0 or 1. We construct a “complementary” vector aR = aL − 1^n and require that aL ◦ aR = 0 hold.
fillWithZeros :: Num f => Integer -> [f] -> [f] Source #
Add non-relevant zeros to a vector to match the size of the other vectors used in the protocol
obfuscateEncodedBits :: (Eq f, Field f) => Integer -> [f] -> [f] -> f -> f -> f Source #
Obfuscate encoded bits with challenges y and z. z^2 * 2^n + z * − 1^n − aR, y^n + aR · y^n = (z^2) * v The property holds because − 1^n − aR, y^n = 0 and · aR, y^n = 0
commitBitVectors :: (MonadRandom m, AsInteger f) => f -> f -> [f] -> [f] -> [f] -> [f] -> m (Point, Point) Source #
We need to blind the vectors aL, aR to make the proof zero knowledge. The Prover creates randomly vectors sL and sR. On creating these, the Prover can send commitments to these vectors; these are properly blinded vector Pedersen commitments: