Skip to content

Commit

Permalink
[1215] Remove all redundant STS HasTrace instances
Browse files Browse the repository at this point in the history
  • Loading branch information
uroboros committed Feb 21, 2020
1 parent a5b77cd commit 98eebc2
Show file tree
Hide file tree
Showing 7 changed files with 3 additions and 102 deletions.
14 changes: 1 addition & 13 deletions shelley/chain-and-ledger/executable-spec/src/STS/Deleg.hs
Expand Up @@ -17,17 +17,14 @@ import Cardano.Binary (FromCBOR (..), ToCBOR (..), decodeWord)
import Cardano.Ledger.Shelley.Crypto
import Cardano.Prelude (NoUnexpectedThunks (..))
import Coin (Coin (..))
import Control.Monad.Trans.Reader (asks, runReaderT)
import Control.Monad.Trans.Reader (asks)
import Control.State.Transition
import Control.State.Transition.Generator
import Data.Functor.Identity (runIdentity)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Delegation.Certificates
import GHC.Generics (Generic)
import Hedgehog (Gen)
import Keys
import Ledger.Core (dom, range, singleton, (∈), (∉), (∪), (⋪), (⋫), (⨃))
import LedgerState (DState, emptyDState, _delegations, _fGenDelegs, _genDelegs, _irwd,
Expand Down Expand Up @@ -166,12 +163,3 @@ delegationTransition = do
_ -> do
failBecause WrongCertificateTypeDELEG -- this always fails
pure ds


instance Crypto crypto
=> HasTrace (DELEG crypto) where
envGen _ = undefined :: Gen DelegEnv
sigGen _ _ = undefined :: Gen (DCert crypto)

type BaseEnv (DELEG crypto) = Globals
interpretSTS globals act = runIdentity $ runReaderT act globals
13 changes: 0 additions & 13 deletions shelley/chain-and-ledger/executable-spec/src/STS/Delegs.hs
Expand Up @@ -21,17 +21,13 @@ import Cardano.Binary (FromCBOR (..), ToCBOR (..), decodeListLen, deco
import Cardano.Ledger.Shelley.Crypto
import Cardano.Prelude (NoUnexpectedThunks (..))
import Coin (Coin)
import Control.Monad.Trans.Reader (runReaderT)
import Control.State.Transition
import Control.State.Transition.Generator
import Data.Functor.Identity (runIdentity)
import Data.Sequence (Seq (..))
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Delegation.Certificates
import GHC.Generics (Generic)
import Hedgehog (Gen)
import Ledger.Core (dom, (∈), (⊆), (⨃))
import LedgerState (DPState (..), emptyDelegation, _dstate, _rewards, _stPools)
import PParams
Expand Down Expand Up @@ -137,12 +133,3 @@ instance
=> Embed (DELPL crypto) (DELEGS crypto)
where
wrapFailed = DelplFailure


instance Crypto crypto
=> HasTrace (DELEGS crypto) where
envGen _ = undefined :: Gen (DelegsEnv crypto)
sigGen _ _ = undefined :: Gen (Seq (DCert crypto))

type BaseEnv (DELEGS crypto) = Globals
interpretSTS globals act = runIdentity $ runReaderT act globals
17 changes: 0 additions & 17 deletions shelley/chain-and-ledger/executable-spec/src/STS/NewEpoch.hs
Expand Up @@ -16,16 +16,12 @@ import BaseTypes
import Cardano.Ledger.Shelley.Crypto
import Cardano.Prelude (NoUnexpectedThunks (..))
import Coin
import Control.Monad.Trans.Reader (runReaderT)
import Control.State.Transition
import Control.State.Transition.Generator
import Data.Functor.Identity (runIdentity)
import qualified Data.Map.Strict as Map
import Data.Maybe (catMaybes)
import Delegation.Certificates
import EpochBoundary
import GHC.Generics (Generic)
import Hedgehog (Gen)
import LedgerState
import Slot
import STS.Epoch
Expand Down Expand Up @@ -128,16 +124,3 @@ instance
Embed (MIR crypto) (NEWEPOCH crypto)
where
wrapFailed = MirFailure

instance
Crypto crypto =>
HasTrace (NEWEPOCH crypto)
where

envGen _ = undefined :: Gen (NewEpochEnv crypto)

sigGen _ _ = undefined :: Gen EpochNo

type BaseEnv (NEWEPOCH crypto) = Globals

interpretSTS globals act = runIdentity $ runReaderT act globals
18 changes: 1 addition & 17 deletions shelley/chain-and-ledger/executable-spec/src/STS/Pool.hs
Expand Up @@ -15,18 +15,15 @@ import BaseTypes
import Cardano.Binary (FromCBOR (..), ToCBOR (..), decodeWord)
import Cardano.Ledger.Shelley.Crypto
import Cardano.Prelude (NoUnexpectedThunks (..))
import Control.Monad.Trans.Reader (asks, runReaderT)
import Control.Monad.Trans.Reader (asks)
import Control.State.Transition
import Control.State.Transition.Generator
import Data.Functor.Identity (runIdentity)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Delegation.Certificates
import GHC.Generics (Generic)
import Hedgehog (Gen)
import Keys
import Ledger.Core (dom, (∈), (∉), (⋪))
import LedgerState
Expand Down Expand Up @@ -133,16 +130,3 @@ m ⨃ (k, v) = Map.union (Map.singleton k v) m
(KeyHash crypto, a) ->
Map (KeyHash crypto) a
m (k, v) = Map.union m (Map.singleton k v)

instance
Crypto crypto =>
HasTrace (POOL crypto)
where

envGen _ = undefined :: Gen PoolEnv

sigGen _ _ = undefined :: Gen (DCert crypto)

type BaseEnv (POOL crypto) = Globals

interpretSTS globals act = runIdentity $ runReaderT act globals
11 changes: 0 additions & 11 deletions shelley/chain-and-ledger/executable-spec/src/STS/PoolReap.hs
Expand Up @@ -11,17 +11,13 @@ where

import BaseTypes
import Cardano.Prelude (NoUnexpectedThunks (..))
import Control.Monad.Trans.Reader (runReaderT)
import Control.Monad.Trans.Reader (asks)
import Control.State.Transition
import Control.State.Transition.Generator (HasTrace (..), envGen, sigGen)
import Data.Functor.Identity (runIdentity)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Delegation.Certificates
import EpochBoundary (poolRefunds)
import GHC.Generics (Generic)
import Hedgehog (Gen)
import Ledger.Core (dom, (∈), (∪+), (⋪), (⋫), (▷), (◁))
import LedgerState
import Lens.Micro ((^.))
Expand Down Expand Up @@ -77,10 +73,3 @@ poolReapTransition = do
, _pParams = retired _pParams ps
, _retiring = retired _retiring ps
}

instance HasTrace (POOLREAP crypto) where
envGen _ = undefined :: Gen PParams
sigGen _ _ = undefined :: Gen EpochNo

type BaseEnv (POOLREAP crypto) = Globals
interpretSTS globals act = runIdentity $ runReaderT act globals
15 changes: 0 additions & 15 deletions shelley/chain-and-ledger/executable-spec/src/STS/Utxo.hs
Expand Up @@ -23,18 +23,14 @@ import Cardano.Binary (FromCBOR (..), ToCBOR (..), decodeListLen, deco
import Cardano.Ledger.Shelley.Crypto
import Cardano.Prelude (NoUnexpectedThunks (..))
import Coin
import Control.Monad.Trans.Reader (runReaderT)
import Control.State.Transition
import Control.State.Transition.Generator
import Data.Foldable (toList)
import Data.Functor.Identity (runIdentity)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Delegation.Certificates
import GHC.Generics (Generic)
import Hedgehog (Gen)
import Keys
import Ledger.Core (dom, range, (∪), (⊆), (⋪))
import LedgerState (UTxOState (..), consumed, decayedTx, keyRefunds, minfee, produced,
Expand Down Expand Up @@ -190,14 +186,3 @@ instance Crypto crypto
=> Embed (UP crypto) (UTXO crypto)
where
wrapFailed = UpdateFailure

instance
( Crypto crypto
, Signable (DSIGN crypto) (TxBody crypto)
)
=> HasTrace (UTXO crypto) where
envGen _ = undefined :: Gen (UtxoEnv crypto)
sigGen _ _ = undefined :: Gen (Tx crypto)

type BaseEnv (UTXO crypto) = Globals
interpretSTS globals act = runIdentity $ runReaderT act globals
17 changes: 1 addition & 16 deletions shelley/chain-and-ledger/executable-spec/src/STS/Utxow.hs
Expand Up @@ -16,23 +16,19 @@ module STS.Utxow
)
where

import BaseTypes (Globals, ShelleyBase, intervalValue, invalidKey, quorum, (==>))
import BaseTypes (ShelleyBase, intervalValue, invalidKey, quorum, (==>))
import Cardano.Binary (FromCBOR (..), ToCBOR (..), decodeListLen, decodeWord,
encodeListLen, matchSize)
import Cardano.Ledger.Shelley.Crypto
import Cardano.Prelude (NoUnexpectedThunks (..), asks)
import Control.Monad.Trans.Reader (runReaderT)
import Control.State.Transition
import Control.State.Transition.Generator (HasTrace (..), envGen, sigGen)
import Data.Functor.Identity (runIdentity)
import qualified Data.Map.Strict as Map
import qualified Data.Sequence as Seq (filter)
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Delegation.Certificates (isInstantaneousRewards)
import GHC.Generics (Generic)
import Hedgehog (Gen)
import Keys
import Ledger.Core (dom, (∩))
import LedgerState (UTxOState (..), verifiedWits, witsVKeyNeeded)
Expand Down Expand Up @@ -178,14 +174,3 @@ instance
=> Embed (UTXO crypto) (UTXOW crypto)
where
wrapFailed = UtxoFailure

instance
( Crypto crypto
, Signable (DSIGN crypto) (TxBody crypto)
)
=> HasTrace (UTXOW crypto) where
envGen _ = undefined :: Gen (UtxoEnv crypto)
sigGen _ _ = undefined :: Gen (Tx crypto)

type BaseEnv (UTXOW crypto) = Globals
interpretSTS globals act = runIdentity $ runReaderT act globals

0 comments on commit 98eebc2

Please sign in to comment.