Skip to content

Commit

Permalink
stylish-haskell auto-commit
Browse files Browse the repository at this point in the history
  • Loading branch information
vks4git authored and actions-user committed Jul 26, 2024
1 parent c7a4a8c commit 54410d2
Show file tree
Hide file tree
Showing 6 changed files with 20 additions and 18 deletions.
9 changes: 5 additions & 4 deletions bench/BenchDiv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ import Control.DeepSeq (force)
import Control.Exception (evaluate)
import qualified Data.Map as M
import Data.Time.Clock (getCurrentTime)
import Prelude hiding (not, sum, (&&), (*), (+), (-), (/), (^), (||), divMod)
import Prelude hiding (divMod, not, sum, (&&), (*), (+), (-), (/), (^),
(||))
import System.Random (randomIO)
import Test.Tasty.Bench

Expand All @@ -22,15 +23,15 @@ import ZkFold.Base.Algebra.Basic.Number
import ZkFold.Base.Algebra.EllipticCurve.BLS12_381
import ZkFold.Base.Data.Vector
import ZkFold.Symbolic.Compiler
import ZkFold.Symbolic.Data.UInt
import ZkFold.Symbolic.Data.Combinators
import ZkFold.Symbolic.Data.UInt

evalUInt :: forall a n . UInt n ArithmeticCircuit a -> Vector (NumberOfRegisters a n) a
evalUInt (UInt xs) = eval xs M.empty

-- | Generate random addition circuit of given size
--
divisionCircuit
divisionCircuit
:: forall n p r
. KnownNat n
=> PrimeField (Zp p)
Expand All @@ -47,7 +48,7 @@ divisionCircuit = do
let acX = fromConstant (x :: Integer) :: UInt n ArithmeticCircuit (Zp p)
acY = fromConstant (y :: Integer) :: UInt n ArithmeticCircuit (Zp p)

acZ = acX `divMod` acY
acZ = acX `divMod` acY

evaluate . force $ acZ

Expand Down
2 changes: 1 addition & 1 deletion src/ZkFold/Base/Algebra/Basic/Number.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

module ZkFold.Base.Algebra.Basic.Number
module ZkFold.Base.Algebra.Basic.Number
( Natural
, KnownNat
, Prime
Expand Down
10 changes: 5 additions & 5 deletions src/ZkFold/Base/Algebra/Polynomials/Multivariate/Polynomial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,13 +38,13 @@ newtype Poly c i j = P [(c, Mono i j)]
polynomial :: Polynomial c i j => [(c, Mono i j)] -> Poly c i j
polynomial = foldr (\(c, m) x -> if c == zero then x else P [(c, m)] + x) zero

evalPolynomial
:: forall c i j b
evalPolynomial
:: forall c i j b
. AdditiveMonoid b
=> Scale c b
=> ((i -> b) -> Mono i j -> b)
-> (i -> b)
-> Poly c i j
=> ((i -> b) -> Mono i j -> b)
-> (i -> b)
-> Poly c i j
-> b
evalPolynomial e f (P p) = foldr (\(c, m) x -> x + scale c (e f m)) zero p

Expand Down
3 changes: 2 additions & 1 deletion src/ZkFold/Base/Protocol/ARK/Protostar/Lookup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ import ZkFold.Base.Algebra.Basic.Field (Zp)
import ZkFold.Base.Algebra.Basic.Number
import ZkFold.Base.Data.Sparse.Vector (SVector (..))
import ZkFold.Base.Data.Vector (Vector)
import ZkFold.Base.Protocol.ARK.Protostar.SpecialSound (SpecialSoundProtocol (..), SpecialSoundTranscript, LMap)
import ZkFold.Base.Protocol.ARK.Protostar.SpecialSound (LMap, SpecialSoundProtocol (..),
SpecialSoundTranscript)
import ZkFold.Symbolic.Compiler (Arithmetic)

data ProtostarLookup (l :: Natural) (sizeT :: Natural)
Expand Down
2 changes: 1 addition & 1 deletion src/ZkFold/Base/Protocol/ARK/Protostar/Permutation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ import ZkFold.Base.Algebra.Basic.Class
import ZkFold.Base.Algebra.Basic.Number
import ZkFold.Base.Algebra.Basic.Permutations (Permutation, applyPermutation)
import ZkFold.Base.Algebra.Polynomials.Multivariate (var)
import ZkFold.Base.Data.Vector as V
import ZkFold.Base.Data.Vector as V
import ZkFold.Base.Protocol.ARK.Protostar.SpecialSound (LMap, SpecialSoundProtocol (..),
SpecialSoundTranscript)
import ZkFold.Symbolic.Compiler (Arithmetic)
Expand Down
12 changes: 6 additions & 6 deletions src/ZkFold/Base/Protocol/ARK/Protostar/SpecialSound.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,13 +40,13 @@ class Arithmetic f => SpecialSoundProtocol f a where

prover :: a -> Witness f a -> Input f a -> SpecialSoundTranscript f a -> ProverMessage f a

algebraicMap
:: a
-> Input f a
-> [ProverMessage Natural a]
-> [VerifierMessage Natural a]
algebraicMap
:: a
-> Input f a
-> [ProverMessage Natural a]
-> [VerifierMessage Natural a]
-> LMap f
-- ^ the algebraic map V_sps computed by the verifier.
-- ^ the algebraic map V_sps computed by the verifier.
-- The j-th element of the vector is a homogeneous degree-j algebraic map that outputs a vector of @Dimension a@ field elements.
-- Variables have natural indices from @0@ to @2k@:
-- Variable @0@ is public input
Expand Down

0 comments on commit 54410d2

Please sign in to comment.