{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE UndecidableInstances #-} module ZkFold.Base.Protocol.Plonkup.Prover.Secret where import Data.Aeson.Types (FromJSON (..), ToJSON (..)) import GHC.Generics (Generic) import Prelude hiding (Num (..), drop, length, sum, take, (!!), (/), (^)) import Test.QuickCheck (Arbitrary (..)) import ZkFold.Base.Algebra.EllipticCurve.BLS12_381 (BLS12_381_G1) import ZkFold.Base.Algebra.EllipticCurve.Class (EllipticCurve (..)) import ZkFold.Base.Data.Vector (Vector (..)) newtype PlonkupProverSecret c = PlonkupProverSecret (Vector 19 (ScalarField c)) deriving stock (forall x. PlonkupProverSecret c -> Rep (PlonkupProverSecret c) x) -> (forall x. Rep (PlonkupProverSecret c) x -> PlonkupProverSecret c) -> Generic (PlonkupProverSecret c) forall x. Rep (PlonkupProverSecret c) x -> PlonkupProverSecret c forall x. PlonkupProverSecret c -> Rep (PlonkupProverSecret c) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall c x. Rep (PlonkupProverSecret c) x -> PlonkupProverSecret c forall c x. PlonkupProverSecret c -> Rep (PlonkupProverSecret c) x $cfrom :: forall c x. PlonkupProverSecret c -> Rep (PlonkupProverSecret c) x from :: forall x. PlonkupProverSecret c -> Rep (PlonkupProverSecret c) x $cto :: forall c x. Rep (PlonkupProverSecret c) x -> PlonkupProverSecret c to :: forall x. Rep (PlonkupProverSecret c) x -> PlonkupProverSecret c Generic deriving anyclass instance ToJSON (PlonkupProverSecret BLS12_381_G1) deriving anyclass instance FromJSON (PlonkupProverSecret BLS12_381_G1) instance Show (ScalarField c) => Show (PlonkupProverSecret c) where show :: PlonkupProverSecret c -> String show (PlonkupProverSecret Vector 19 (ScalarField c) v) = String "PlonkupProverSecret: " String -> ShowS forall a. [a] -> [a] -> [a] ++ Vector 19 (ScalarField c) -> String forall a. Show a => a -> String show Vector 19 (ScalarField c) v instance Arbitrary (ScalarField c) => Arbitrary (PlonkupProverSecret c) where arbitrary :: Gen (PlonkupProverSecret c) arbitrary = Vector 19 (ScalarField c) -> PlonkupProverSecret c forall c. Vector 19 (ScalarField c) -> PlonkupProverSecret c PlonkupProverSecret (Vector 19 (ScalarField c) -> PlonkupProverSecret c) -> Gen (Vector 19 (ScalarField c)) -> Gen (PlonkupProverSecret c) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b <$> Gen (Vector 19 (ScalarField c)) forall a. Arbitrary a => Gen a arbitrary