Skip to content

Commit

Permalink
Format. [skip ci]
Browse files Browse the repository at this point in the history
  • Loading branch information
dnadales committed Jan 14, 2021
1 parent 8be06b4 commit 5b804fd
Show file tree
Hide file tree
Showing 8 changed files with 27 additions and 22 deletions.
@@ -1,3 +1,4 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
Expand All @@ -6,7 +7,6 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ConstraintKinds #-}

module Cardano.Ledger.Pretty where

Expand All @@ -27,6 +27,7 @@ import Cardano.Ledger.Era (Era)
import Codec.Binary.Bech32
import Control.Monad.Identity (Identity)
import Control.SetAlgebra (forwards)
import Control.State.Transition (STS (State))
import qualified Data.ByteString as Long (ByteString)
import qualified Data.ByteString.Lazy as Lazy (ByteString, toStrict)
import Data.IP (IPv4, IPv6)
Expand Down Expand Up @@ -143,7 +144,6 @@ import Shelley.Spec.Ledger.TxBody
WitVKey (..),
)
import Shelley.Spec.Ledger.UTxO (UTxO (..))
import Control.State.Transition (STS (State))

-- =====================================================================================================
-- HELPER FUNCTIONS
Expand Down Expand Up @@ -404,7 +404,8 @@ ppRewardUpdate (RewardUpdate dt dr rss df nonmyop) =
("nonMyopic", ppNonMyopic nonmyop)
]

ppUTxOState :: CanPrettyPrintLedgerState era =>
ppUTxOState ::
CanPrettyPrintLedgerState era =>
UTxOState era ->
PDoc
ppUTxOState (UTxOState u dep fee ppup) =
Expand All @@ -429,8 +430,9 @@ ppEpochState (EpochState acnt snap ls prev pp non) =
]

ppLedgerState ::
CanPrettyPrintLedgerState era
=> LedgerState era -> PDoc
CanPrettyPrintLedgerState era =>
LedgerState era ->
PDoc
ppLedgerState (LedgerState u d) =
ppRecord
"LedgerState"
Expand Down
Expand Up @@ -114,6 +114,7 @@ import Control.DeepSeq (NFData)
import Control.Monad.Trans.Reader (asks)
import Control.Provenance (ProvM, lift, modifyWithBlackBox, runOtherProv)
import Control.SetAlgebra (Bimap, biMapEmpty, dom, eval, forwards, range, (∈), (∪+), (▷), (◁))
import Control.State.Transition (STS (State))
import qualified Data.ByteString.Lazy as BSL (length)
import Data.Coerce (coerce)
import Data.Constraint (Constraint)
Expand Down Expand Up @@ -238,8 +239,6 @@ import Shelley.Spec.Ledger.UTxO
txup,
verifyWitVKey,
)
import Control.State.Transition (STS (State))


-- | Representation of a list of pairs of key pairs, e.g., pay and stake keys
type KeyPairs crypto = [(KeyPair 'Payment crypto, KeyPair 'Staking crypto)]
Expand Down
Expand Up @@ -48,7 +48,7 @@ import Control.State.Transition
liftSTS,
trans,
)
import Data.Default.Class (def, Default)
import Data.Default.Class (Default, def)
import Data.Foldable (fold)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
Expand Down
Expand Up @@ -31,6 +31,7 @@ import Control.State.Transition
judgmentContext,
trans,
)
import Data.Default.Class (Default)
import qualified Data.Map.Strict as Map
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
Expand All @@ -39,9 +40,9 @@ import Shelley.Spec.Ledger.Coin (Coin (..))
import Shelley.Spec.Ledger.EpochBoundary (SnapShots, obligation)
import Shelley.Spec.Ledger.LedgerState
( EpochState,
UpecState (..),
LedgerState,
PState (..),
UpecState (..),
esAccountState,
esLState,
esNonMyopic,
Expand All @@ -63,7 +64,6 @@ import Shelley.Spec.Ledger.STS.PoolReap (POOLREAP, PoolreapPredicateFailure, Poo
import Shelley.Spec.Ledger.STS.Snap (SNAP, SnapPredicateFailure)
import Shelley.Spec.Ledger.STS.Upec (UPEC, UpecPredicateFailure)
import Shelley.Spec.Ledger.Slot (EpochNo)
import Data.Default.Class (Default)

data EPOCH era

Expand Down Expand Up @@ -203,7 +203,7 @@ instance

instance
( Era era,
-- Default (State (Core.EraRule "PPUP" era)),
-- Default (State (Core.EraRule "PPUP" era)),
Default (PoolreapState era),
PredicateFailure (Core.EraRule "POOLREAP" era) ~ PoolreapPredicateFailure era
) =>
Expand Down
Expand Up @@ -32,6 +32,7 @@ import Control.State.Transition
judgmentContext,
trans,
)
import Data.Default.Class (Default)
import Data.Foldable (toList)
import Data.Sequence (Seq)
import GHC.Generics (Generic)
Expand All @@ -51,7 +52,6 @@ import Shelley.Spec.Ledger.STS.Ledger (LEDGER, LedgerEnv (..), LedgerPredicateFa
import Shelley.Spec.Ledger.Slot (SlotNo)
import Shelley.Spec.Ledger.Tx (Tx)
import Shelley.Spec.Ledger.TxBody (EraIndependentTxBody)
import Data.Default.Class (Default)

data LEDGERS era

Expand Down
@@ -1,13 +1,13 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE EmptyDataDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}

module Shelley.Spec.Ledger.STS.Mir
Expand All @@ -28,6 +28,7 @@ import Control.State.Transition
TransitionRule,
judgmentContext,
)
import Data.Default.Class (Default)
import Data.Foldable (fold)
import qualified Data.Map.Strict as Map
import Data.Typeable (Typeable)
Expand All @@ -51,7 +52,6 @@ import Shelley.Spec.Ledger.LedgerState
_rewards,
pattern EpochState,
)
import Data.Default.Class (Default)

data MIR era

Expand Down
Expand Up @@ -25,7 +25,7 @@ import Cardano.Ledger.Era (Crypto, Era)
import Cardano.Ledger.Shelley.Constraints (UsesTxOut, UsesValue)
import qualified Cardano.Ledger.Val as Val
import Control.State.Transition
import Data.Default.Class (def)
import Data.Default.Class (Default, def)
import Data.Foldable (fold)
import qualified Data.Map.Strict as Map
import Data.Maybe (catMaybes)
Expand All @@ -40,7 +40,6 @@ import Shelley.Spec.Ledger.STS.Epoch
import Shelley.Spec.Ledger.STS.Mir
import Shelley.Spec.Ledger.Slot
import Shelley.Spec.Ledger.TxBody
import Data.Default.Class (Default)

data NEWEPOCH era

Expand Down
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
Expand All @@ -8,7 +9,6 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}

-- | Epoch change registration.
--
Expand All @@ -18,8 +18,14 @@
-- todo: explain that this rule is Shelley specific.
module Shelley.Spec.Ledger.STS.Upec where

import Cardano.Ledger.Shelley.Constraints (
ShelleyBased, UsesAuxiliary, UsesScript, UsesTxBody, UsesValue)
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Shelley.Constraints
( ShelleyBased,
UsesAuxiliary,
UsesScript,
UsesTxBody,
UsesValue,
)
import Control.Monad.Trans.Reader (asks)
import Control.State.Transition
( Embed (..),
Expand All @@ -36,8 +42,8 @@ import NoThunks.Class (NoThunks (..))
import Shelley.Spec.Ledger.BaseTypes (Globals (..), ShelleyBase)
import Shelley.Spec.Ledger.LedgerState
( EpochState,
UpecState (..),
PPUPState (..),
UpecState (..),
esAccountState,
esLState,
_delegationState,
Expand All @@ -48,7 +54,6 @@ import Shelley.Spec.Ledger.LedgerState
)
import Shelley.Spec.Ledger.PParams (PParams, PParamsUpdate, ProposedPPUpdates (..), updatePParams)
import Shelley.Spec.Ledger.STS.Newpp (NEWPP, NewppEnv (..), NewppState (..))
import qualified Cardano.Ledger.Core as Core

-- | Update epoch change
data UPEC era
Expand All @@ -65,7 +70,7 @@ instance
UsesScript era,
UsesValue era,
State (Core.EraRule "PPUP" era)
~ PPUPState era
~ PPUPState era
) =>
STS (UPEC era)
where
Expand Down

0 comments on commit 5b804fd

Please sign in to comment.