module Hydra.HeadLogic.Input where

import Hydra.Prelude

import Hydra.API.ClientInput (ClientInput)
import Hydra.Chain (ChainEvent, IsChainState)
import Hydra.Network.Message (Message)
import Hydra.Party (Party)

type TTL = Natural

-- | Inputs that are processed by the head logic (the "core"). Corresponding to
-- each of the "shell" layers, we distinguish between inputs from the client,
-- the network and the chain.
data Input tx
  = -- | Input received from clients via the "Hydra.API".
    ClientInput {forall tx. Input tx -> ClientInput tx
clientInput :: ClientInput tx}
  | -- | Input received from peers via a "Hydra.Network".
    --
    --  * `ttl` is a simple counter that's decreased every time the event is
    --    reenqueued due to a wait. It's default value is `defaultTTL`
    NetworkInput {forall tx. Input tx -> TTL
ttl :: TTL, forall tx. Input tx -> Party
party :: Party, forall tx. Input tx -> Message tx
message :: Message tx}
  | -- | Input received from the chain via a "Hydra.Chain".
    ChainInput {forall tx. Input tx -> ChainEvent tx
chainEvent :: ChainEvent tx}
  deriving stock ((forall x. Input tx -> Rep (Input tx) x)
-> (forall x. Rep (Input tx) x -> Input tx) -> Generic (Input tx)
forall x. Rep (Input tx) x -> Input tx
forall x. Input tx -> Rep (Input tx) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall tx x. Rep (Input tx) x -> Input tx
forall tx x. Input tx -> Rep (Input tx) x
$cfrom :: forall tx x. Input tx -> Rep (Input tx) x
from :: forall x. Input tx -> Rep (Input tx) x
$cto :: forall tx x. Rep (Input tx) x -> Input tx
to :: forall x. Rep (Input tx) x -> Input tx
Generic)

deriving stock instance IsChainState tx => Eq (Input tx)
deriving stock instance IsChainState tx => Show (Input tx)
deriving anyclass instance IsChainState tx => ToJSON (Input tx)
deriving anyclass instance IsChainState tx => FromJSON (Input tx)

instance IsChainState tx => Arbitrary (Input tx) where
  arbitrary :: Gen (Input tx)
arbitrary = Gen (Input tx)
forall a.
(Generic a, GA UnsizedOpts (Rep a),
 UniformWeight (Weights_ (Rep a))) =>
Gen a
genericArbitrary
  shrink :: Input tx -> [Input tx]
shrink = Input tx -> [Input tx]
forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink