module Hydra.Node.Environment where
import Hydra.Prelude
import Hydra.Node.DepositPeriod (DepositPeriod)
import Hydra.Tx.ContestationPeriod (ContestationPeriod)
import Hydra.Tx.Crypto (HydraKey, SigningKey)
import Hydra.Tx.HeadParameters (HeadParameters (..))
import Hydra.Tx.OnChainId (OnChainId)
import Hydra.Tx.Party (HasParty (..), Party)
data Environment = Environment
{ Environment -> Party
party :: Party
,
Environment -> SigningKey HydraKey
signingKey :: SigningKey HydraKey
, Environment -> [Party]
otherParties :: [Party]
,
Environment -> [OnChainId]
participants :: [OnChainId]
, Environment -> ContestationPeriod
contestationPeriod :: ContestationPeriod
, Environment -> DepositPeriod
depositPeriod :: DepositPeriod
, Environment -> Text
configuredPeers :: Text
}
deriving stock ((forall x. Environment -> Rep Environment x)
-> (forall x. Rep Environment x -> Environment)
-> Generic Environment
forall x. Rep Environment x -> Environment
forall x. Environment -> Rep Environment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Environment -> Rep Environment x
from :: forall x. Environment -> Rep Environment x
$cto :: forall x. Rep Environment x -> Environment
to :: forall x. Rep Environment x -> Environment
Generic, Int -> Environment -> ShowS
[Environment] -> ShowS
Environment -> String
(Int -> Environment -> ShowS)
-> (Environment -> String)
-> ([Environment] -> ShowS)
-> Show Environment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Environment -> ShowS
showsPrec :: Int -> Environment -> ShowS
$cshow :: Environment -> String
show :: Environment -> String
$cshowList :: [Environment] -> ShowS
showList :: [Environment] -> ShowS
Show, Environment -> Environment -> Bool
(Environment -> Environment -> Bool)
-> (Environment -> Environment -> Bool) -> Eq Environment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Environment -> Environment -> Bool
== :: Environment -> Environment -> Bool
$c/= :: Environment -> Environment -> Bool
/= :: Environment -> Environment -> Bool
Eq)
instance Arbitrary Environment where
arbitrary :: Gen Environment
arbitrary = Gen Environment
forall a.
(Generic a, GA UnsizedOpts (Rep a),
UniformWeight (Weights_ (Rep a))) =>
Gen a
genericArbitrary
shrink :: Environment -> [Environment]
shrink = Environment -> [Environment]
forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance HasParty Environment where
getParty :: Environment -> Party
getParty = Environment -> Party
party
mkHeadParameters :: Environment -> HeadParameters
mkHeadParameters :: Environment -> HeadParameters
mkHeadParameters Environment{Party
$sel:party:Environment :: Environment -> Party
party :: Party
party, [Party]
$sel:otherParties:Environment :: Environment -> [Party]
otherParties :: [Party]
otherParties, ContestationPeriod
$sel:contestationPeriod:Environment :: Environment -> ContestationPeriod
contestationPeriod :: ContestationPeriod
contestationPeriod} =
HeadParameters{ContestationPeriod
contestationPeriod :: ContestationPeriod
$sel:contestationPeriod:HeadParameters :: ContestationPeriod
contestationPeriod, $sel:parties:HeadParameters :: [Party]
parties = Party
party Party -> [Party] -> [Party]
forall a. a -> [a] -> [a]
: [Party]
otherParties}