{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
module Bulletproofs.Utils where
import Protolude hiding (hash, fromStrict)
import Control.Monad.Random (getRandomR, MonadRandom)
import Data.Field.Galois (PrimeField(..), sr)
import Data.Curve.Weierstrass.SECP256K1 (PA, Fr, Point(..), _r, def, mul, gen)
import Data.Digest.Pure.SHA (integerDigest, sha256)
import Data.ByteString.Lazy (fromStrict)
h :: PA
h = generateH ""
gs :: [PA]
gs = mul gen . oracle . (<> pointToBS gen) . show <$> [1..]
hs :: [PA]
hs = mul gen . oracle . (<> pointToBS h) . show <$> [1..]
oracle :: PrimeField f => ByteString -> f
oracle = fromInteger . integerDigest . sha256 . fromStrict
pointToBS :: PA -> ByteString
pointToBS = show
generateH :: [Char] -> PA
generateH extra =
case yM of
Nothing -> generateH (toS $ '1':extra)
Just y -> if def (A x y :: PA)
then A x y
else generateH (toS $ '1':extra)
where
x = oracle (pointToBS gen <> toS extra)
yM = sr (x ^ 3 + 7)
powerVector :: (Eq f, Num f) => f -> Integer -> [f]
powerVector a x
= (\i -> if i == 0 && a == 0 then 0 else a ^ i) <$> [0..x-1]
hadamard :: Num a => [a] -> [a] -> [a]
hadamard a b | length a == length b = zipWith (*) a b
| otherwise = panic "Vector sizes must match"
dot :: Num a => [a] -> [a] -> a
dot xs ys = sum $ hadamard xs ys
(^+^) :: Num a => [a] -> [a] -> [a]
(^+^) = zipWith (+)
(^-^) :: Num a => [a] -> [a] -> [a]
(^-^) = zipWith (-)
addTwoMulP :: Fr -> PA -> Fr -> PA -> PA
addTwoMulP exp0 pt0 exp1 pt1 = (pt0 `mul` exp0) <> (pt1 `mul` exp1)
sumExps :: [Fr] -> [PA] -> PA
sumExps (exp0:exp1:exps) (pt0:pt1:pts)
= addTwoMulP exp0 pt0 exp1 pt1 <> sumExps exps pts
sumExps (exp:_) (pt:_) = pt `mul` exp
sumExps _ _ = mempty
commit :: Fr -> Fr -> PA
commit x r = addTwoMulP x gen r h
isLogBase2 :: Integer -> Bool
isLogBase2 x
| x == 1 = True
| x == 0 || (x `mod` 2 /= 0) = False
| otherwise = isLogBase2 (x `div` 2)
logBase2 :: Integer -> Integer
logBase2 = floor . logBase 2.0 . fromIntegral
logBase2M :: Integer -> Maybe Integer
logBase2M x
= if isLogBase2 x
then Just (logBase2 x)
else Nothing
slice :: Integer -> Integer -> [a] -> [a]
slice n j vs = take (fromIntegral $ j * n - (j - 1)*n) (drop (fromIntegral $ (j - 1) * n) vs)
padToNearestPowerOfTwo
:: Num f => [f] -> [f]
padToNearestPowerOfTwo [] = []
padToNearestPowerOfTwo xs = padToNearestPowerOfTwoOf (length xs) xs
padToNearestPowerOfTwoOf
:: Num f
=> Int
-> [f]
-> [f]
padToNearestPowerOfTwoOf i xs = xs ++ replicate padLength 0
where
padLength = nearestPowerOfTwo - length xs
nearestPowerOfTwo = 2 ^ log2Ceil i
log2Ceil :: Int -> Int
log2Ceil x = floorLog + correction
where
floorLog = finiteBitSize x - 1 - countLeadingZeros x
correction = if countTrailingZeros x < floorLog
then 1
else 0
randomN :: MonadRandom m => Integer -> m Integer
randomN n = getRandomR (1, 2^n - 1)
chooseBlindingVectors :: (Num f, MonadRandom m) => Integer -> m ([f], [f])
chooseBlindingVectors n = do
sL <- replicateM (fromInteger n) (fromInteger <$> getRandomR (1, 2^n - 1))
sR <- replicateM (fromInteger n) (fromInteger <$> getRandomR (1, 2^n - 1))
pure (sL, sR)
shamirY :: PA -> PA -> Fr
shamirY aCommit sCommit
= oracle $
show _r <> pointToBS aCommit <> pointToBS sCommit
shamirZ :: PA -> PA -> Fr -> Fr
shamirZ aCommit sCommit y
= oracle $
show _r <> pointToBS aCommit <> pointToBS sCommit <> show y
shamirX
:: PA
-> PA
-> PA
-> PA
-> Fr
-> Fr
-> Fr
shamirX aCommit sCommit t1Commit t2Commit y z
= oracle $
show _r <> pointToBS aCommit <> pointToBS sCommit <> pointToBS t1Commit <> pointToBS t2Commit <> show y <> show z
shamirX' :: PA -> PA -> PA -> Fr
shamirX' commitmentLR l' r'
= oracle $
show _r <> pointToBS l' <> pointToBS r' <> pointToBS commitmentLR
shamirU :: Fr -> Fr -> Fr -> Fr
shamirU tBlinding mu t
= oracle $ show _r <> show tBlinding <> show mu <> show t