Skip to content

Commit

Permalink
Update to galois-field-0.4.0. Remove overlapping instances (#17)
Browse files Browse the repository at this point in the history
  • Loading branch information
Acentelles authored and sdiehl committed Aug 11, 2019
1 parent 95450b3 commit ca31452
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 55 deletions.
52 changes: 1 addition & 51 deletions Bulletproofs/Fq.hs
Original file line number Diff line number Diff line change
@@ -1,68 +1,18 @@
{-# LANGUAGE TypeFamilies #-}
-- | Prime field with characteristic _q, over which the elliptic curve
-- is defined and the other finite field extensions.
--
-- * Fq
-- * Fq2 := Fq[u]/u^2 + 1
-- * Fq6 := Fq2[v]/v^3 - (9 + u)
-- * Fq12 := Fq6[w]/w^2 - v

module Bulletproofs.Fq
( Fq
, PF
, fqRandom
, fqPow
, fqSqrt
, toInt
) where

import Protolude

import Crypto.Random (MonadRandom)
import Crypto.Number.Generate (generateMax)
import Math.NumberTheory.Moduli.Class (powMod)
import PrimeField (PrimeField(..), toInt)
import Pairing.Modular
import PrimeField (PrimeField(..))
import Bulletproofs.Curve


-------------------------------------------------------------------------------
-- Types
-------------------------------------------------------------------------------

-- | Prime field @Fq@ with characteristic @_q@
type Fq = PrimeField 0xfffffffffffffffffffffffffffffffebaaedce6af48a03bbfd25e8cd0364141

-- | Type family to extract the characteristic of the prime field
type family PF a where
PF (PrimeField k) = k

-------------------------------------------------------------------------------
-- Instances
-------------------------------------------------------------------------------

instance Ord Fq where
compare = on compare toInt

-------------------------------------------------------------------------------
-- Random
-------------------------------------------------------------------------------

fqRandom :: MonadRandom m => m Fq
fqRandom = fromInteger <$> generateMax _q

-------------------------------------------------------------------------------
-- Y for X
-------------------------------------------------------------------------------

fqPow :: Integral e => Fq -> e -> Fq
fqPow a b = fromInteger (withQ (modUnOp (toInt a) (flip powMod b)))
{-# INLINE fqPow #-}

fqSqrt :: Bool -> Fq -> Maybe Fq
fqSqrt largestY a = do
(y1, y2) <- withQM (modUnOpMTup (toInt a) bothSqrtOf)
return (fromInteger ((if largestY then max else min) y1 y2))

fqYforX :: Fq -> Bool -> Maybe Fq
fqYforX x largestY = fqSqrt largestY (x `fqPow` 3 + fromInteger _b)
3 changes: 1 addition & 2 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,7 @@ dependencies:
- random-shuffle
- MonadRandom
- QuickCheck
- galois-field > 0.2
- pairing > 0.4
- galois-field == 0.4.0

library:
source-dirs: .
Expand Down
5 changes: 3 additions & 2 deletions stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -5,5 +5,6 @@ packages:

extra-deps:
- criterion-1.5.2.0
- galois-field-0.2.1
- pairing-0.4.1
- galois-field-0.4.0
- poly-0.3.1.0
- semirings-0.4.2
1 change: 1 addition & 0 deletions tests/TestProtocol.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import qualified Crypto.PubKey.ECC.Generate as Crypto
import qualified Crypto.PubKey.ECC.Prim as Crypto
import qualified Crypto.PubKey.ECC.Types as Crypto
import GaloisField (GaloisField(..))
import PrimeField (toInt)

import Bulletproofs.Curve
import qualified Bulletproofs.RangeProof as RP
Expand Down

0 comments on commit ca31452

Please sign in to comment.