{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Cardano.Ledger.Shelley.Rules.Delpl
( DELPL,
DelplEnv (..),
DelplPredicateFailure (..),
DelplEvent,
PredicateFailure,
)
where
import Cardano.Binary
( FromCBOR (..),
ToCBOR (..),
encodeListLen,
)
import Cardano.Ledger.BaseTypes (ProtVer, ShelleyBase, invalidKey)
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Era (Crypto, Era)
import Cardano.Ledger.Serialization (decodeRecordSum)
import Cardano.Ledger.Shelley.LedgerState
( AccountState,
DPState,
DState,
PState,
dpsDState,
dpsPState,
)
import Cardano.Ledger.Shelley.Rules.Deleg (DELEG, DelegEnv (..), DelegPredicateFailure)
import Cardano.Ledger.Shelley.Rules.Pool (POOL, PoolEnv (..), PoolPredicateFailure)
import Cardano.Ledger.Shelley.TxBody
( DCert (..),
DelegCert (..),
GenesisDelegCert (..),
PoolCert (..),
Ptr,
)
import Cardano.Ledger.Slot (SlotNo)
import Control.State.Transition
import Data.Typeable (Typeable)
import Data.Word (Word8)
import GHC.Generics (Generic)
import GHC.Records (HasField)
import NoThunks.Class (NoThunks (..))
data DELPL era
data DelplEnv era = DelplEnv
{ DelplEnv era -> SlotNo
delplSlotNo :: SlotNo,
DelplEnv era -> Ptr
delPlPtr :: Ptr,
DelplEnv era -> PParams era
delPlPp :: Core.PParams era,
DelplEnv era -> AccountState
delPlAcnt :: AccountState
}
data DelplPredicateFailure era
= PoolFailure (PredicateFailure (Core.EraRule "POOL" era))
| DelegFailure (PredicateFailure (Core.EraRule "DELEG" era))
deriving ((forall x.
DelplPredicateFailure era -> Rep (DelplPredicateFailure era) x)
-> (forall x.
Rep (DelplPredicateFailure era) x -> DelplPredicateFailure era)
-> Generic (DelplPredicateFailure era)
forall x.
Rep (DelplPredicateFailure era) x -> DelplPredicateFailure era
forall x.
DelplPredicateFailure era -> Rep (DelplPredicateFailure era) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x.
Rep (DelplPredicateFailure era) x -> DelplPredicateFailure era
forall era x.
DelplPredicateFailure era -> Rep (DelplPredicateFailure era) x
$cto :: forall era x.
Rep (DelplPredicateFailure era) x -> DelplPredicateFailure era
$cfrom :: forall era x.
DelplPredicateFailure era -> Rep (DelplPredicateFailure era) x
Generic)
data DelplEvent era
= PoolEvent (Event (POOL era))
| DelegEvent (Event (DELEG era))
deriving stock instance
( Eq (PredicateFailure (Core.EraRule "DELEG" era)),
Eq (PredicateFailure (Core.EraRule "POOL" era))
) =>
Eq (DelplPredicateFailure era)
deriving stock instance
( Show (PredicateFailure (Core.EraRule "DELEG" era)),
Show (PredicateFailure (Core.EraRule "POOL" era))
) =>
Show (DelplPredicateFailure era)
instance
( NoThunks (PredicateFailure (Core.EraRule "DELEG" era)),
NoThunks (PredicateFailure (Core.EraRule "POOL" era))
) =>
NoThunks (DelplPredicateFailure era)
instance
( Era era,
Embed (Core.EraRule "DELEG" era) (DELPL era),
Environment (Core.EraRule "DELEG" era) ~ DelegEnv era,
State (Core.EraRule "DELEG" era) ~ DState (Crypto era),
Signal (Core.EraRule "DELEG" era) ~ DCert (Crypto era),
Embed (Core.EraRule "POOL" era) (DELPL era),
Environment (Core.EraRule "POOL" era) ~ PoolEnv era,
State (Core.EraRule "POOL" era) ~ PState (Crypto era),
Signal (Core.EraRule "POOL" era) ~ DCert (Crypto era)
) =>
STS (DELPL era)
where
type State (DELPL era) = DPState (Crypto era)
type Signal (DELPL era) = DCert (Crypto era)
type Environment (DELPL era) = DelplEnv era
type BaseM (DELPL era) = ShelleyBase
type PredicateFailure (DELPL era) = DelplPredicateFailure era
type Event (DELPL era) = DelplEvent era
transitionRules :: [TransitionRule (DELPL era)]
transitionRules = [TransitionRule (DELPL era)
forall era.
(Embed (EraRule "DELEG" era) (DELPL era),
Environment (EraRule "DELEG" era) ~ DelegEnv era,
State (EraRule "DELEG" era) ~ DState (Crypto era),
Signal (EraRule "DELEG" era) ~ DCert (Crypto era),
Embed (EraRule "POOL" era) (DELPL era),
Environment (EraRule "POOL" era) ~ PoolEnv era,
State (EraRule "POOL" era) ~ PState (Crypto era),
Signal (EraRule "POOL" era) ~ DCert (Crypto era)) =>
TransitionRule (DELPL era)
delplTransition]
instance
( Era era,
ToCBOR (PredicateFailure (Core.EraRule "POOL" era)),
ToCBOR (PredicateFailure (Core.EraRule "DELEG" era)),
Typeable (Core.Script era)
) =>
ToCBOR (DelplPredicateFailure era)
where
toCBOR :: DelplPredicateFailure era -> Encoding
toCBOR = \case
(PoolFailure PredicateFailure (EraRule "POOL" era)
a) ->
Word -> Encoding
encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
0 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> PredicateFailure (EraRule "POOL" era) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR PredicateFailure (EraRule "POOL" era)
a
(DelegFailure PredicateFailure (EraRule "DELEG" era)
a) ->
Word -> Encoding
encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (Word8
1 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> PredicateFailure (EraRule "DELEG" era) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR PredicateFailure (EraRule "DELEG" era)
a
instance
( Era era,
FromCBOR (PredicateFailure (Core.EraRule "POOL" era)),
FromCBOR (PredicateFailure (Core.EraRule "DELEG" era)),
Typeable (Core.Script era)
) =>
FromCBOR (DelplPredicateFailure era)
where
fromCBOR :: Decoder s (DelplPredicateFailure era)
fromCBOR =
String
-> (Word -> Decoder s (Int, DelplPredicateFailure era))
-> Decoder s (DelplPredicateFailure era)
forall s a. String -> (Word -> Decoder s (Int, a)) -> Decoder s a
decodeRecordSum
String
"PredicateFailure (DELPL era)"
( \case
Word
0 -> do
PredicateFailure (EraRule "POOL" era)
a <- Decoder s (PredicateFailure (EraRule "POOL" era))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int, DelplPredicateFailure era)
-> Decoder s (Int, DelplPredicateFailure era)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
2, PredicateFailure (EraRule "POOL" era) -> DelplPredicateFailure era
forall era.
PredicateFailure (EraRule "POOL" era) -> DelplPredicateFailure era
PoolFailure PredicateFailure (EraRule "POOL" era)
a)
Word
1 -> do
PredicateFailure (EraRule "DELEG" era)
a <- Decoder s (PredicateFailure (EraRule "DELEG" era))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int, DelplPredicateFailure era)
-> Decoder s (Int, DelplPredicateFailure era)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
2, PredicateFailure (EraRule "DELEG" era) -> DelplPredicateFailure era
forall era.
PredicateFailure (EraRule "DELEG" era) -> DelplPredicateFailure era
DelegFailure PredicateFailure (EraRule "DELEG" era)
a)
Word
k -> Word -> Decoder s (Int, DelplPredicateFailure era)
forall s a. Word -> Decoder s a
invalidKey Word
k
)
delplTransition ::
forall era.
( Embed (Core.EraRule "DELEG" era) (DELPL era),
Environment (Core.EraRule "DELEG" era) ~ DelegEnv era,
State (Core.EraRule "DELEG" era) ~ DState (Crypto era),
Signal (Core.EraRule "DELEG" era) ~ DCert (Crypto era),
Embed (Core.EraRule "POOL" era) (DELPL era),
Environment (Core.EraRule "POOL" era) ~ PoolEnv era,
State (Core.EraRule "POOL" era) ~ PState (Crypto era),
Signal (Core.EraRule "POOL" era) ~ DCert (Crypto era)
) =>
TransitionRule (DELPL era)
delplTransition :: TransitionRule (DELPL era)
delplTransition = do
TRC (DelplEnv slot ptr pp acnt, State (DELPL era)
d, Signal (DELPL era)
c) <- F (Clause (DELPL era) 'Transition) (TRC (DELPL era))
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
case Signal (DELPL era)
c of
DCertPool (RegPool _) -> do
PState (Crypto era)
ps <-
forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "POOL" era) super =>
RuleContext rtype (EraRule "POOL" era)
-> Rule super rtype (State (EraRule "POOL" era))
trans @(Core.EraRule "POOL" era) (RuleContext 'Transition (EraRule "POOL" era)
-> Rule (DELPL era) 'Transition (State (EraRule "POOL" era)))
-> RuleContext 'Transition (EraRule "POOL" era)
-> Rule (DELPL era) 'Transition (State (EraRule "POOL" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "POOL" era), State (EraRule "POOL" era),
Signal (EraRule "POOL" era))
-> TRC (EraRule "POOL" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> PParams era -> PoolEnv era
forall era. SlotNo -> PParams era -> PoolEnv era
PoolEnv SlotNo
slot PParams era
pp, DPState (Crypto era) -> PState (Crypto era)
forall crypto. DPState crypto -> PState crypto
dpsPState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "POOL" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsPState :: PState (Crypto era)
dpsPState = PState (Crypto era)
ps}
DCertPool (RetirePool _ _) -> do
PState (Crypto era)
ps <-
forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "POOL" era) super =>
RuleContext rtype (EraRule "POOL" era)
-> Rule super rtype (State (EraRule "POOL" era))
trans @(Core.EraRule "POOL" era) (RuleContext 'Transition (EraRule "POOL" era)
-> Rule (DELPL era) 'Transition (State (EraRule "POOL" era)))
-> RuleContext 'Transition (EraRule "POOL" era)
-> Rule (DELPL era) 'Transition (State (EraRule "POOL" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "POOL" era), State (EraRule "POOL" era),
Signal (EraRule "POOL" era))
-> TRC (EraRule "POOL" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> PParams era -> PoolEnv era
forall era. SlotNo -> PParams era -> PoolEnv era
PoolEnv SlotNo
slot PParams era
pp, DPState (Crypto era) -> PState (Crypto era)
forall crypto. DPState crypto -> PState crypto
dpsPState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "POOL" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsPState :: PState (Crypto era)
dpsPState = PState (Crypto era)
ps}
DCertGenesis GenesisDelegCert {} -> do
DState (Crypto era)
ds <-
forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "DELEG" era) super =>
RuleContext rtype (EraRule "DELEG" era)
-> Rule super rtype (State (EraRule "DELEG" era))
trans @(Core.EraRule "DELEG" era) (RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era)))
-> RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "DELEG" era), State (EraRule "DELEG" era),
Signal (EraRule "DELEG" era))
-> TRC (EraRule "DELEG" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
forall era.
SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
DelegEnv SlotNo
slot Ptr
ptr AccountState
acnt PParams era
pp, DPState (Crypto era) -> DState (Crypto era)
forall crypto. DPState crypto -> DState crypto
dpsDState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "DELEG" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsDState :: DState (Crypto era)
dpsDState = DState (Crypto era)
ds}
DCertDeleg (RegKey _) -> do
DState (Crypto era)
ds <-
forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "DELEG" era) super =>
RuleContext rtype (EraRule "DELEG" era)
-> Rule super rtype (State (EraRule "DELEG" era))
trans @(Core.EraRule "DELEG" era) (RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era)))
-> RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "DELEG" era), State (EraRule "DELEG" era),
Signal (EraRule "DELEG" era))
-> TRC (EraRule "DELEG" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
forall era.
SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
DelegEnv SlotNo
slot Ptr
ptr AccountState
acnt PParams era
pp, DPState (Crypto era) -> DState (Crypto era)
forall crypto. DPState crypto -> DState crypto
dpsDState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "DELEG" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsDState :: DState (Crypto era)
dpsDState = DState (Crypto era)
ds}
DCertDeleg (DeRegKey _) -> do
DState (Crypto era)
ds <-
forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "DELEG" era) super =>
RuleContext rtype (EraRule "DELEG" era)
-> Rule super rtype (State (EraRule "DELEG" era))
trans @(Core.EraRule "DELEG" era) (RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era)))
-> RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "DELEG" era), State (EraRule "DELEG" era),
Signal (EraRule "DELEG" era))
-> TRC (EraRule "DELEG" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
forall era.
SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
DelegEnv SlotNo
slot Ptr
ptr AccountState
acnt PParams era
pp, DPState (Crypto era) -> DState (Crypto era)
forall crypto. DPState crypto -> DState crypto
dpsDState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "DELEG" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsDState :: DState (Crypto era)
dpsDState = DState (Crypto era)
ds}
DCertDeleg (Delegate _) -> do
DState (Crypto era)
ds <-
forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "DELEG" era) super =>
RuleContext rtype (EraRule "DELEG" era)
-> Rule super rtype (State (EraRule "DELEG" era))
trans @(Core.EraRule "DELEG" era) (RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era)))
-> RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "DELEG" era), State (EraRule "DELEG" era),
Signal (EraRule "DELEG" era))
-> TRC (EraRule "DELEG" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
forall era.
SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
DelegEnv SlotNo
slot Ptr
ptr AccountState
acnt PParams era
pp, DPState (Crypto era) -> DState (Crypto era)
forall crypto. DPState crypto -> DState crypto
dpsDState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "DELEG" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsDState :: DState (Crypto era)
dpsDState = DState (Crypto era)
ds}
DCertMir _ -> do
DState (Crypto era)
ds <- forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "DELEG" era) super =>
RuleContext rtype (EraRule "DELEG" era)
-> Rule super rtype (State (EraRule "DELEG" era))
trans @(Core.EraRule "DELEG" era) (RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era)))
-> RuleContext 'Transition (EraRule "DELEG" era)
-> Rule (DELPL era) 'Transition (State (EraRule "DELEG" era))
forall a b. (a -> b) -> a -> b
$ (Environment (EraRule "DELEG" era), State (EraRule "DELEG" era),
Signal (EraRule "DELEG" era))
-> TRC (EraRule "DELEG" era)
forall sts. (Environment sts, State sts, Signal sts) -> TRC sts
TRC (SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
forall era.
SlotNo -> Ptr -> AccountState -> PParams era -> DelegEnv era
DelegEnv SlotNo
slot Ptr
ptr AccountState
acnt PParams era
pp, DPState (Crypto era) -> DState (Crypto era)
forall crypto. DPState crypto -> DState crypto
dpsDState State (DELPL era)
DPState (Crypto era)
d, Signal (EraRule "DELEG" era)
Signal (DELPL era)
c)
DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era)))
-> DPState (Crypto era)
-> F (Clause (DELPL era) 'Transition) (DPState (Crypto era))
forall a b. (a -> b) -> a -> b
$ State (DELPL era)
DPState (Crypto era)
d {dpsDState :: DState (Crypto era)
dpsDState = DState (Crypto era)
ds}
instance
( Era era,
STS (POOL era),
PredicateFailure (Core.EraRule "POOL" era) ~ PoolPredicateFailure era
) =>
Embed (POOL era) (DELPL era)
where
wrapFailed :: PredicateFailure (POOL era) -> PredicateFailure (DELPL era)
wrapFailed = PredicateFailure (POOL era) -> PredicateFailure (DELPL era)
forall era.
PredicateFailure (EraRule "POOL" era) -> DelplPredicateFailure era
PoolFailure
wrapEvent :: Event (POOL era) -> Event (DELPL era)
wrapEvent = Event (POOL era) -> Event (DELPL era)
forall era. Event (POOL era) -> DelplEvent era
PoolEvent
instance
( Era era,
HasField "_protocolVersion" (Core.PParams era) ProtVer,
PredicateFailure (Core.EraRule "DELEG" era) ~ DelegPredicateFailure era
) =>
Embed (DELEG era) (DELPL era)
where
wrapFailed :: PredicateFailure (DELEG era) -> PredicateFailure (DELPL era)
wrapFailed = PredicateFailure (DELEG era) -> PredicateFailure (DELPL era)
forall era.
PredicateFailure (EraRule "DELEG" era) -> DelplPredicateFailure era
DelegFailure
wrapEvent :: Event (DELEG era) -> Event (DELPL era)
wrapEvent = Event (DELEG era) -> Event (DELPL era)
forall era. Event (DELEG era) -> DelplEvent era
DelegEvent