{-# 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_Point) import ZkFold.Base.Algebra.EllipticCurve.Class (CyclicGroup (..)) import ZkFold.Base.Data.Vector (Vector (..)) newtype PlonkupProverSecret g = PlonkupProverSecret (Vector 19 (ScalarFieldOf g)) deriving stock (forall x. PlonkupProverSecret g -> Rep (PlonkupProverSecret g) x) -> (forall x. Rep (PlonkupProverSecret g) x -> PlonkupProverSecret g) -> Generic (PlonkupProverSecret g) forall x. Rep (PlonkupProverSecret g) x -> PlonkupProverSecret g forall x. PlonkupProverSecret g -> Rep (PlonkupProverSecret g) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall g x. Rep (PlonkupProverSecret g) x -> PlonkupProverSecret g forall g x. PlonkupProverSecret g -> Rep (PlonkupProverSecret g) x $cfrom :: forall g x. PlonkupProverSecret g -> Rep (PlonkupProverSecret g) x from :: forall x. PlonkupProverSecret g -> Rep (PlonkupProverSecret g) x $cto :: forall g x. Rep (PlonkupProverSecret g) x -> PlonkupProverSecret g to :: forall x. Rep (PlonkupProverSecret g) x -> PlonkupProverSecret g Generic deriving anyclass instance ToJSON (PlonkupProverSecret BLS12_381_G1_Point) deriving anyclass instance FromJSON (PlonkupProverSecret BLS12_381_G1_Point) instance Show (ScalarFieldOf g) => Show (PlonkupProverSecret g) where show :: PlonkupProverSecret g -> String show (PlonkupProverSecret Vector 19 (ScalarFieldOf g) v) = String "PlonkupProverSecret: " String -> ShowS forall a. [a] -> [a] -> [a] ++ Vector 19 (ScalarFieldOf g) -> String forall a. Show a => a -> String show Vector 19 (ScalarFieldOf g) v instance Arbitrary (ScalarFieldOf g) => Arbitrary (PlonkupProverSecret g) where arbitrary :: Gen (PlonkupProverSecret g) arbitrary = Vector 19 (ScalarFieldOf g) -> PlonkupProverSecret g forall g. Vector 19 (ScalarFieldOf g) -> PlonkupProverSecret g PlonkupProverSecret (Vector 19 (ScalarFieldOf g) -> PlonkupProverSecret g) -> Gen (Vector 19 (ScalarFieldOf g)) -> Gen (PlonkupProverSecret g) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b <$> Gen (Vector 19 (ScalarFieldOf g)) forall a. Arbitrary a => Gen a arbitrary