diff --git a/hydra-cardano-api/hydra-cardano-api.cabal b/hydra-cardano-api/hydra-cardano-api.cabal index 23f617d7fd1..5adba6e72c3 100644 --- a/hydra-cardano-api/hydra-cardano-api.cabal +++ b/hydra-cardano-api/hydra-cardano-api.cabal @@ -33,7 +33,7 @@ common project-config ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -Wunused-packages - -fprint-potential-instances + -Wmissing-deriving-strategies -fprint-potential-instances library import: project-config diff --git a/hydra-cluster/src/CardanoClient.hs b/hydra-cluster/src/CardanoClient.hs index 24fca8e1c67..872e85212a1 100644 --- a/hydra-cluster/src/CardanoClient.hs +++ b/hydra-cluster/src/CardanoClient.hs @@ -64,7 +64,7 @@ data Sizes = Sizes , outputs :: Int , witnesses :: Int } - deriving (Eq, Show) + deriving stock (Eq, Show) defaultSizes :: Sizes defaultSizes = Sizes{inputs = 0, outputs = 0, witnesses = 0} diff --git a/hydra-cluster/src/CardanoNode.hs b/hydra-cluster/src/CardanoNode.hs index 1138b1789db..ba662ec915c 100644 --- a/hydra-cluster/src/CardanoNode.hs +++ b/hydra-cluster/src/CardanoNode.hs @@ -370,7 +370,7 @@ generateCardanoKey = do pure (getVerificationKey sk, sk) data ProcessHasExited = ProcessHasExited Text ExitCode - deriving (Show) + deriving stock (Show) instance Exception ProcessHasExited diff --git a/hydra-cluster/src/Hydra/Cluster/Faucet.hs b/hydra-cluster/src/Hydra/Cluster/Faucet.hs index 95f87280653..e0faa61a758 100644 --- a/hydra-cluster/src/Hydra/Cluster/Faucet.hs +++ b/hydra-cluster/src/Hydra/Cluster/Faucet.hs @@ -34,7 +34,7 @@ import Hydra.Ledger.Cardano () data FaucetException = FaucetHasNotEnoughFunds {faucetUTxO :: UTxO} | FaucetFailedToBuildTx {reason :: TxBodyErrorAutoBalance} - deriving (Show) + deriving stock (Show) instance Exception FaucetException diff --git a/hydra-cluster/src/Hydra/Cluster/Fixture.hs b/hydra-cluster/src/Hydra/Cluster/Fixture.hs index f34f8c2d9a5..6b70da02d37 100644 --- a/hydra-cluster/src/Hydra/Cluster/Fixture.hs +++ b/hydra-cluster/src/Hydra/Cluster/Fixture.hs @@ -48,7 +48,7 @@ data Actor | Bob | Carol | Faucet - deriving (Eq, Show) + deriving stock (Eq, Show) actorName :: Actor -> String actorName = \case @@ -63,4 +63,4 @@ data KnownNetwork = Preview | Preproduction | Mainnet - deriving (Show) + deriving stock (Show) diff --git a/hydra-cluster/src/Hydra/Cluster/Options.hs b/hydra-cluster/src/Hydra/Cluster/Options.hs index dc06fabf8db..7f079d35eb0 100644 --- a/hydra-cluster/src/Hydra/Cluster/Options.hs +++ b/hydra-cluster/src/Hydra/Cluster/Options.hs @@ -12,10 +12,10 @@ data Options = Options , stateDirectory :: Maybe FilePath , publishHydraScripts :: PublishOrReuse } - deriving (Show) + deriving stock (Show) data PublishOrReuse = Publish | Reuse TxId - deriving (Show) + deriving stock (Show) -- TODO: Provide an option to use mithril aggregated snapshots to bootstrap the testnet parseOptions :: Parser Options diff --git a/hydra-cluster/src/Hydra/Generator.hs b/hydra-cluster/src/Hydra/Generator.hs index aecc858bbf4..4ff3e32290b 100644 --- a/hydra-cluster/src/Hydra/Generator.hs +++ b/hydra-cluster/src/Hydra/Generator.hs @@ -26,7 +26,8 @@ data Dataset = Dataset , title :: Maybe Text , description :: Maybe Text } - deriving (Show, Generic, ToJSON, FromJSON) + deriving stock (Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance Arbitrary Dataset where arbitrary = sized $ \n -> do @@ -39,7 +40,7 @@ data ClientKeys = ClientKeys , externalSigningKey :: SigningKey PaymentKey -- ^ Key holding funds to commit. } - deriving (Show) + deriving stock (Show) instance ToJSON ClientKeys where toJSON ClientKeys{signingKey, externalSigningKey} = @@ -66,7 +67,8 @@ data ClientDataset = ClientDataset , initialUTxO :: UTxO , txSequence :: [Tx] } - deriving (Show, Generic, ToJSON, FromJSON) + deriving stock (Show, Generic) + deriving anyclass (ToJSON, FromJSON) defaultProtocolParameters :: ProtocolParameters defaultProtocolParameters = fromLedgerPParams ShelleyBasedEraShelley def diff --git a/hydra-cluster/src/Hydra/LogFilter.hs b/hydra-cluster/src/Hydra/LogFilter.hs index 14a262356ae..deafc902cd0 100644 --- a/hydra-cluster/src/Hydra/LogFilter.hs +++ b/hydra-cluster/src/Hydra/LogFilter.hs @@ -43,9 +43,9 @@ data Trace tx } deriving stock (Generic) -deriving instance (IsTx tx) => Eq (Trace tx) -deriving instance (IsTx tx) => Show (Trace tx) -deriving instance (IsTx tx) => ToJSON (Trace tx) +deriving stock instance (IsTx tx) => Eq (Trace tx) +deriving stock instance (IsTx tx) => Show (Trace tx) +deriving anyclass instance (IsTx tx) => ToJSON (Trace tx) data TraceKey = EventKey Word64 diff --git a/hydra-cluster/src/HydraNode.hs b/hydra-cluster/src/HydraNode.hs index ca818bf3858..b69ae0ec197 100644 --- a/hydra-cluster/src/HydraNode.hs +++ b/hydra-cluster/src/HydraNode.hs @@ -207,7 +207,8 @@ data EndToEndLog | PublishedHydraScriptsAt {hydraScriptsTxId :: TxId} | UsingHydraScriptsAt {hydraScriptsTxId :: TxId} | CreatedKey {keyPath :: FilePath} - deriving (Eq, Show, Generic, ToJSON, FromJSON, ToObject) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON, ToObject) -- XXX: The two lists need to be of same length. Also the verification keys can -- be derived from the signing keys. diff --git a/hydra-cluster/test/Test/DirectChainSpec.hs b/hydra-cluster/test/Test/DirectChainSpec.hs index 5dcbebea1bd..74887521fbc 100644 --- a/hydra-cluster/test/Test/DirectChainSpec.hs +++ b/hydra-cluster/test/Test/DirectChainSpec.hs @@ -422,7 +422,8 @@ data DirectChainTestLog = FromNode NodeLog | FromDirectChain Text DirectChainLog | FromFaucet FaucetLog - deriving (Show, Generic, ToJSON) + deriving stock (Show, Generic) + deriving anyclass (ToJSON) data DirectChainTest tx m = DirectChainTest { postTx :: PostChainTx tx -> m () diff --git a/hydra-node/exe/hydra-node/Main.hs b/hydra-node/exe/hydra-node/Main.hs index 9dba69249b7..4310d41202a 100644 --- a/hydra-node/exe/hydra-node/Main.hs +++ b/hydra-node/exe/hydra-node/Main.hs @@ -58,7 +58,7 @@ import Hydra.Persistence (createPersistenceIncremental) import Hydra.Utils (genHydraKeys) newtype ConfigurationParseException = ConfigurationParseException ProtocolParametersConversionError - deriving (Show) + deriving stock (Show) instance Exception ConfigurationParseException diff --git a/hydra-node/src/Hydra/API/APIServerLog.hs b/hydra-node/src/Hydra/API/APIServerLog.hs index 5561355f60f..06519d9c74a 100644 --- a/hydra-node/src/Hydra/API/APIServerLog.hs +++ b/hydra-node/src/Hydra/API/APIServerLog.hs @@ -36,7 +36,7 @@ instance Arbitrary APIServerLog where -- | New type wrapper to define JSON instances. newtype PathInfo = PathInfo ByteString - deriving (Eq, Show) + deriving stock (Eq, Show) instance Arbitrary PathInfo where arbitrary = @@ -55,7 +55,7 @@ instance FromJSON PathInfo where -- NOTE: We are not using http-types 'StdMethod' as we do not want to be -- constrained in terms of logging and accept any method in a 'Request'. newtype Method = Method ByteString - deriving (Eq, Show) + deriving stock (Eq, Show) instance Arbitrary Method where arbitrary = Method . renderStdMethod <$> chooseEnum (minBound, maxBound) diff --git a/hydra-node/src/Hydra/API/ClientInput.hs b/hydra-node/src/Hydra/API/ClientInput.hs index 09426b8ea75..ad872740c1a 100644 --- a/hydra-node/src/Hydra/API/ClientInput.hs +++ b/hydra-node/src/Hydra/API/ClientInput.hs @@ -14,12 +14,12 @@ data ClientInput tx | Close | Contest | Fanout - deriving (Generic) + deriving stock (Generic) -deriving instance IsTx tx => Eq (ClientInput tx) -deriving instance IsTx tx => Show (ClientInput tx) -deriving instance IsTx tx => ToJSON (ClientInput tx) -deriving instance IsTx tx => FromJSON (ClientInput tx) +deriving stock instance IsTx tx => Eq (ClientInput tx) +deriving stock instance IsTx tx => Show (ClientInput tx) +deriving anyclass instance IsTx tx => ToJSON (ClientInput tx) +deriving anyclass instance IsTx tx => FromJSON (ClientInput tx) instance Arbitrary tx => Arbitrary (ClientInput tx) where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/API/HTTPServer.hs b/hydra-node/src/Hydra/API/HTTPServer.hs index ce81fe301f3..5bacafe94d7 100644 --- a/hydra-node/src/Hydra/API/HTTPServer.hs +++ b/hydra-node/src/Hydra/API/HTTPServer.hs @@ -48,7 +48,7 @@ import Network.Wai ( newtype DraftCommitTxResponse = DraftCommitTxResponse { commitTx :: Tx } - deriving (Show, Generic) + deriving stock (Show, Generic) instance ToJSON DraftCommitTxResponse where toJSON (DraftCommitTxResponse tx) = diff --git a/hydra-node/src/Hydra/API/Server.hs b/hydra-node/src/Hydra/API/Server.hs index 63b8f2de74f..1c1ef2287f5 100644 --- a/hydra-node/src/Hydra/API/Server.hs +++ b/hydra-node/src/Hydra/API/Server.hs @@ -133,7 +133,7 @@ data RunServerException = RunServerException , host :: IP , port :: PortNumber } - deriving (Show) + deriving stock (Show) instance Exception RunServerException diff --git a/hydra-node/src/Hydra/API/ServerOutput.hs b/hydra-node/src/Hydra/API/ServerOutput.hs index c8c2afe5a0c..e7de232aa00 100644 --- a/hydra-node/src/Hydra/API/ServerOutput.hs +++ b/hydra-node/src/Hydra/API/ServerOutput.hs @@ -90,10 +90,10 @@ data ServerOutput tx Greetings {me :: Party, headStatus :: HeadStatus, snapshotUtxo :: Maybe (UTxOType tx), hydraNodeVersion :: String} | PostTxOnChainFailed {postChainTx :: PostChainTx tx, postTxError :: PostTxError tx} | IgnoredHeadInitializing {headId :: HeadId, participants :: [OnChainId]} - deriving (Generic) + deriving stock (Generic) -deriving instance (IsChainState tx) => Eq (ServerOutput tx) -deriving instance (IsChainState tx) => Show (ServerOutput tx) +deriving stock instance (IsChainState tx) => Eq (ServerOutput tx) +deriving stock instance (IsChainState tx) => Show (ServerOutput tx) instance (IsChainState tx) => ToJSON (ServerOutput tx) where toJSON = @@ -148,17 +148,17 @@ instance data OutputFormat = OutputCBOR | OutputJSON - deriving (Eq, Show) + deriving stock (Eq, Show) -- | Whether or not to include full UTxO in server outputs. data WithUTxO = WithUTxO | WithoutUTxO - deriving (Eq, Show) + deriving stock (Eq, Show) data ServerOutputConfig = ServerOutputConfig { txOutputFormat :: OutputFormat , utxoInSnapshot :: WithUTxO } - deriving (Eq, Show) + deriving stock (Eq, Show) -- | Replaces the json encoded tx field with it's cbor representation. -- @@ -236,7 +236,8 @@ data HeadStatus | Closed | FanoutPossible | Final - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance Arbitrary HeadStatus where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/Chain.hs b/hydra-node/src/Hydra/Chain.hs index 1a451f2812b..72b2908cb11 100644 --- a/hydra-node/src/Hydra/Chain.hs +++ b/hydra-node/src/Hydra/Chain.hs @@ -73,12 +73,12 @@ data PostChainTx tx | FanoutTx {utxo :: UTxOType tx, contestationDeadline :: UTCTime} deriving stock (Generic) -deriving instance IsTx tx => Eq (PostChainTx tx) -deriving instance IsTx tx => Show (PostChainTx tx) -deriving instance IsTx tx => ToJSON (PostChainTx tx) -deriving instance IsTx tx => FromJSON (PostChainTx tx) +deriving stock instance (IsTx tx) => Eq (PostChainTx tx) +deriving stock instance (IsTx tx) => Show (PostChainTx tx) +deriving anyclass instance (IsTx tx) => ToJSON (PostChainTx tx) +deriving anyclass instance (IsTx tx) => FromJSON (PostChainTx tx) -instance IsTx tx => Arbitrary (PostChainTx tx) where +instance (IsTx tx) => Arbitrary (PostChainTx tx) where arbitrary = genericArbitrary -- REVIEW(SN): There is a similarly named type in plutus-ledger, so we might @@ -86,7 +86,7 @@ instance IsTx tx => Arbitrary (PostChainTx tx) where -- | Uniquely identifies a Hydra Head. newtype HeadId = HeadId ByteString - deriving (Show, Eq, Ord, Generic) + deriving stock (Show, Eq, Ord, Generic) deriving (ToJSON, FromJSON) via (UsingRawBytesHex HeadId) instance SerialiseAsRawBytes HeadId where @@ -130,12 +130,12 @@ data OnChainTx tx } | OnContestTx {snapshotNumber :: SnapshotNumber} | OnFanoutTx - deriving (Generic) + deriving stock (Generic) -deriving instance IsTx tx => Eq (OnChainTx tx) -deriving instance IsTx tx => Show (OnChainTx tx) -deriving instance IsTx tx => ToJSON (OnChainTx tx) -deriving instance IsTx tx => FromJSON (OnChainTx tx) +deriving stock instance (IsTx tx) => Eq (OnChainTx tx) +deriving stock instance (IsTx tx) => Show (OnChainTx tx) +deriving anyclass instance (IsTx tx) => ToJSON (OnChainTx tx) +deriving anyclass instance (IsTx tx) => FromJSON (OnChainTx tx) instance (Arbitrary tx, Arbitrary (UTxOType tx)) => Arbitrary (OnChainTx tx) where arbitrary = genericArbitrary @@ -172,14 +172,14 @@ data PostTxError tx FailedToDraftTxNotInitializing | -- | Committing UTxO addressed to the internal wallet is forbidden. SpendingNodeUtxoForbidden - deriving (Generic) + deriving stock (Generic) -deriving instance IsChainState tx => Eq (PostTxError tx) -deriving instance IsChainState tx => Show (PostTxError tx) -deriving instance IsChainState tx => ToJSON (PostTxError tx) -deriving instance IsChainState tx => FromJSON (PostTxError tx) +deriving stock instance (IsChainState tx) => Eq (PostTxError tx) +deriving stock instance (IsChainState tx) => Show (PostTxError tx) +deriving anyclass instance (IsChainState tx) => ToJSON (PostTxError tx) +deriving anyclass instance (IsChainState tx) => FromJSON (PostTxError tx) -instance IsChainState tx => Exception (PostTxError tx) +instance (IsChainState tx) => Exception (PostTxError tx) instance Arbitrary Lovelace where arbitrary = Lovelace <$> scale (* 8) arbitrary `suchThat` (> 0) @@ -194,7 +194,7 @@ data ChainStateHistory tx = UnsafeChainStateHistory { history :: NonEmpty (ChainStateType tx) , defaultChainState :: ChainStateType tx } - deriving (Generic) + deriving stock (Generic) currentState :: ChainStateHistory tx -> ChainStateType tx currentState UnsafeChainStateHistory{history} = head history @@ -205,7 +205,7 @@ pushNewState cs h@UnsafeChainStateHistory{history} = h{history = cs <| history} initHistory :: ChainStateType tx -> ChainStateHistory tx initHistory cs = UnsafeChainStateHistory{history = cs :| [], defaultChainState = cs} -rollbackHistory :: IsChainState tx => ChainSlot -> ChainStateHistory tx -> ChainStateHistory tx +rollbackHistory :: (IsChainState tx) => ChainSlot -> ChainStateHistory tx -> ChainStateHistory tx rollbackHistory rollbackChainSlot h@UnsafeChainStateHistory{history, defaultChainState} = h{history = fromMaybe (defaultChainState :| []) (nonEmpty rolledBack)} where @@ -214,12 +214,12 @@ rollbackHistory rollbackChainSlot h@UnsafeChainStateHistory{history, defaultChai (\cs -> chainStateSlot cs > rollbackChainSlot) (toList history) -deriving instance Eq (ChainStateType tx) => Eq (ChainStateHistory tx) -deriving instance Show (ChainStateType tx) => Show (ChainStateHistory tx) -deriving anyclass instance ToJSON (ChainStateType tx) => ToJSON (ChainStateHistory tx) -deriving anyclass instance FromJSON (ChainStateType tx) => FromJSON (ChainStateHistory tx) +deriving stock instance (Eq (ChainStateType tx)) => Eq (ChainStateHistory tx) +deriving stock instance (Show (ChainStateType tx)) => Show (ChainStateHistory tx) +deriving anyclass instance (ToJSON (ChainStateType tx)) => ToJSON (ChainStateHistory tx) +deriving anyclass instance (FromJSON (ChainStateType tx)) => FromJSON (ChainStateHistory tx) -instance Arbitrary (ChainStateType tx) => Arbitrary (ChainStateHistory tx) where +instance (Arbitrary (ChainStateType tx)) => Arbitrary (ChainStateHistory tx) where arbitrary = genericArbitrary -- | Interface available from a chain state. Expected to be instantiated by all @@ -242,7 +242,7 @@ class -- | Handle to interface with the main chain network data Chain tx m = Chain - { postTx :: MonadThrow m => PostChainTx tx -> m () + { postTx :: (MonadThrow m) => PostChainTx tx -> m () -- ^ Construct and send a transaction to the main chain corresponding to the -- given 'PostChainTx' description. -- This function is not expected to block, so it is only responsible for @@ -251,12 +251,12 @@ data Chain tx m = Chain -- -- Does at least throw 'PostTxError'. , draftCommitTx :: - MonadThrow m => + (MonadThrow m) => UTxO' (TxOut CtxUTxO, Witness WitCtxTxIn) -> m (Either (PostTxError Tx) Tx) -- ^ Create a commit transaction using user provided utxos (zero or many) and -- information to spend from a script. Errors are handled at the call site. - , submitTx :: MonadThrow m => Tx -> m () + , submitTx :: (MonadThrow m) => Tx -> m () -- ^ Submit a cardano transaction. -- -- Throws at least 'PostTxError'. @@ -293,12 +293,12 @@ data ChainEvent tx { chainTime :: UTCTime , chainSlot :: ChainSlot } - deriving (Generic) + deriving stock (Generic) -deriving instance (IsTx tx, Eq (ChainStateType tx)) => Eq (ChainEvent tx) -deriving instance (IsTx tx, Show (ChainStateType tx)) => Show (ChainEvent tx) -deriving instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (ChainEvent tx) -deriving instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (ChainEvent tx) +deriving stock instance (IsTx tx, Eq (ChainStateType tx)) => Eq (ChainEvent tx) +deriving stock instance (IsTx tx, Show (ChainStateType tx)) => Show (ChainEvent tx) +deriving anyclass instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (ChainEvent tx) +deriving anyclass instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (ChainEvent tx) instance ( Arbitrary tx diff --git a/hydra-node/src/Hydra/Chain/CardanoClient.hs b/hydra-node/src/Hydra/Chain/CardanoClient.hs index 77e243114fa..0e964ffe1c2 100644 --- a/hydra-node/src/Hydra/Chain/CardanoClient.hs +++ b/hydra-node/src/Hydra/Chain/CardanoClient.hs @@ -18,7 +18,7 @@ data QueryException = QueryAcquireException AcquiringFailure | QueryEraMismatchException EraMismatch | QueryProtocolParamsConversionException ProtocolParametersConversionError - deriving (Show) + deriving stock (Show) instance Eq QueryException where a == b = case (a, b) of @@ -145,7 +145,7 @@ submitTransaction networkId socket tx = data SubmitTransactionException = SubmitEraMismatch EraMismatch | SubmitTxValidationError (TxValidationErrorInMode CardanoMode) - deriving (Show) + deriving stock (Show) instance Exception SubmitTransactionException @@ -176,9 +176,9 @@ awaitTransaction networkId socket tx = -- | Describes whether to query at the tip or at a specific point. data QueryPoint = QueryTip | QueryAt ChainPoint - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) -deriving instance ToJSON QueryPoint +deriving anyclass instance ToJSON QueryPoint instance Arbitrary QueryPoint where -- XXX: This is not complete as we lack an 'Arbitrary ChainPoint' and we have diff --git a/hydra-node/src/Hydra/Chain/Direct.hs b/hydra-node/src/Hydra/Chain/Direct.hs index 4f8539e330c..b4c82c0558d 100644 --- a/hydra-node/src/Hydra/Chain/Direct.hs +++ b/hydra-node/src/Hydra/Chain/Direct.hs @@ -247,7 +247,7 @@ data ConnectException = ConnectException , nodeSocket :: SocketPath , networkId :: NetworkId } - deriving (Show) + deriving stock (Show) instance Exception ConnectException @@ -259,7 +259,7 @@ instance Exception ConnectException newtype IntersectionNotFoundException = IntersectionNotFound { requestedPoint :: ChainPoint } - deriving (Show) + deriving stock (Show) instance Exception IntersectionNotFoundException diff --git a/hydra-node/src/Hydra/Chain/Direct/Handlers.hs b/hydra-node/src/Hydra/Chain/Direct/Handlers.hs index 38b3d06c4da..8bd6d304010 100644 --- a/hydra-node/src/Hydra/Chain/Direct/Handlers.hs +++ b/hydra-node/src/Hydra/Chain/Direct/Handlers.hs @@ -235,7 +235,8 @@ data TimeConversionException = TimeConversionException { slotNo :: SlotNo , reason :: Text } - deriving (Eq, Show, Exception) + deriving stock (Eq, Show) + deriving anyclass (Exception) -- | Creates a `ChainSyncHandler` that can notify the given `callback` of events happening -- on-chain. @@ -386,7 +387,7 @@ data DirectChainLog | RolledForward {point :: ChainPoint, receivedTxIds :: [TxId]} | RolledBackward {point :: ChainPoint} | Wallet TinyWalletLog - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) deriving anyclass (ToJSON, FromJSON) instance Arbitrary DirectChainLog where diff --git a/hydra-node/src/Hydra/Chain/Direct/ScriptRegistry.hs b/hydra-node/src/Hydra/Chain/Direct/ScriptRegistry.hs index a4a3aebc986..7bc89f5a2e8 100644 --- a/hydra-node/src/Hydra/Chain/Direct/ScriptRegistry.hs +++ b/hydra-node/src/Hydra/Chain/Direct/ScriptRegistry.hs @@ -59,7 +59,8 @@ data ScriptRegistry = ScriptRegistry , commitReference :: (TxIn, TxOut CtxUTxO) , headReference :: (TxIn, TxOut CtxUTxO) } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) genScriptRegistry :: Gen ScriptRegistry genScriptRegistry = do @@ -87,7 +88,7 @@ data NewScriptRegistryException = MissingScript , scriptHash :: ScriptHash , discoveredScripts :: Set ScriptHash } - deriving (Eq, Show) + deriving stock (Eq, Show) instance Exception NewScriptRegistryException diff --git a/hydra-node/src/Hydra/Chain/Direct/State.hs b/hydra-node/src/Hydra/Chain/Direct/State.hs index f83453c1332..035af649ecd 100644 --- a/hydra-node/src/Hydra/Chain/Direct/State.hs +++ b/hydra-node/src/Hydra/Chain/Direct/State.hs @@ -133,7 +133,8 @@ data ChainStateAt = ChainStateAt { chainState :: ChainState , recordedAt :: Maybe ChainPoint } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance Arbitrary ChainStateAt where arbitrary = genericArbitrary @@ -161,7 +162,7 @@ data ChainTransition | Close | Contest | Fanout - deriving (Eq, Show, Enum, Bounded) + deriving stock (Eq, Show, Enum, Bounded) -- | An enumeration of all possible on-chain states of a Hydra Head, where each -- case stores the relevant information to construct & observe transactions to @@ -173,7 +174,8 @@ data ChainState | Initial InitialState | Open OpenState | Closed ClosedState - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance Arbitrary ChainState where arbitrary = genChainState @@ -205,7 +207,8 @@ data ChainContext = ChainContext , scriptRegistry :: ScriptRegistry , contestationPeriod :: ContestationPeriod } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance HasKnownUTxO ChainContext where getKnownUTxO ChainContext{scriptRegistry} = registryUTxO scriptRegistry @@ -242,7 +245,8 @@ data InitialState = InitialState , headId :: HeadId , seedTxIn :: TxIn } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance HasKnownUTxO InitialState where getKnownUTxO st = @@ -264,7 +268,8 @@ data OpenState = OpenState , seedTxIn :: TxIn , openUtxoHash :: UTxOHash } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance HasKnownUTxO OpenState where getKnownUTxO st = @@ -279,7 +284,8 @@ data ClosedState = ClosedState , headId :: HeadId , seedTxIn :: TxIn } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance HasKnownUTxO ClosedState where getKnownUTxO st = @@ -828,7 +834,7 @@ data HydraContext = HydraContext , ctxContestationPeriod :: ContestationPeriod , ctxScriptRegistry :: ScriptRegistry } - deriving (Show) + deriving stock (Show) ctxParties :: HydraContext -> [Party] ctxParties = fmap deriveParty . ctxHydraSigningKeys diff --git a/hydra-node/src/Hydra/Chain/Direct/Tx.hs b/hydra-node/src/Hydra/Chain/Direct/Tx.hs index c594b2ab451..b293d43a067 100644 --- a/hydra-node/src/Hydra/Chain/Direct/Tx.hs +++ b/hydra-node/src/Hydra/Chain/Direct/Tx.hs @@ -58,7 +58,7 @@ import qualified PlutusLedgerApi.V2 as Plutus type UTxOWithScript = (TxIn, TxOut CtxUTxO, HashableScriptData) newtype UTxOHash = UTxOHash ByteString - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) instance ToJSON UTxOHash where toJSON (UTxOHash bytes) = @@ -76,7 +76,8 @@ data InitialThreadOutput = InitialThreadOutput , initialContestationPeriod :: OnChain.ContestationPeriod , initialParties :: [OnChain.Party] } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) -- | Representation of the Head output after a CollectCom transaction. data OpenThreadOutput = OpenThreadOutput @@ -84,7 +85,8 @@ data OpenThreadOutput = OpenThreadOutput , openContestationPeriod :: OnChain.ContestationPeriod , openParties :: [OnChain.Party] } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) data ClosedThreadOutput = ClosedThreadOutput { closedThreadUTxO :: UTxOWithScript @@ -92,7 +94,8 @@ data ClosedThreadOutput = ClosedThreadOutput , closedContestationDeadline :: Plutus.POSIXTime , closedContesters :: [Plutus.PubKeyHash] } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) hydraHeadV1AssetName :: AssetName hydraHeadV1AssetName = AssetName (fromBuiltin hydraHeadV1) @@ -520,7 +523,7 @@ fanoutTx scriptRegistry utxo (headInput, headOutput, ScriptDatumForTxIn -> headD toTxContext <$> toList utxo data AbortTxError = OverlappingInputs - deriving (Show) + deriving stock (Show) -- | Create transaction which aborts a head by spending the Head output and all -- other "initial" outputs. @@ -642,7 +645,7 @@ data InitObservation = InitObservation , contestationPeriod :: ContestationPeriod , parties :: [Party] } - deriving (Show, Eq) + deriving stock (Show, Eq) -- | An explanation for a failed tentative `InitTx` observation. data NotAnInit @@ -650,7 +653,7 @@ data NotAnInit NotAnInit NotAnInitReason | -- | The transaction /is/ a valid InitTx but does not match the configuration of our Head. NotAnInitForUs MismatchReason - deriving (Show, Eq) + deriving stock (Show, Eq) data NotAnInitReason = NoHeadOutput @@ -887,7 +890,7 @@ data CollectComObservation = CollectComObservation , headId :: HeadId , utxoHash :: UTxOHash } - deriving (Show, Eq) + deriving stock (Show, Eq) -- | Identify a collectCom tx by lookup up the input spending the Head output -- and decoding its redeemer. @@ -935,7 +938,7 @@ data CloseObservation = CloseObservation , headId :: HeadId , snapshotNumber :: SnapshotNumber } - deriving (Show, Eq) + deriving stock (Show, Eq) -- | Identify a close tx by lookup up the input spending the Head output and -- decoding its redeemer. @@ -983,7 +986,7 @@ data ContestObservation = ContestObservation , snapshotNumber :: SnapshotNumber , contesters :: [Plutus.PubKeyHash] } - deriving (Show, Eq) + deriving stock (Show, Eq) -- | Identify a close tx by lookup up the input spending the Head output and -- decoding its redeemer. diff --git a/hydra-node/src/Hydra/Chain/Direct/Wallet.hs b/hydra-node/src/Hydra/Chain/Direct/Wallet.hs index 3b02a6e83e9..25b764841b9 100644 --- a/hydra-node/src/Hydra/Chain/Direct/Wallet.hs +++ b/hydra-node/src/Hydra/Chain/Direct/Wallet.hs @@ -216,10 +216,10 @@ data ErrCoverFee | ErrUnknownInput {input :: TxIn} | ErrScriptExecutionFailed {scriptFailure :: (RdmrPtr, TransactionScriptFailure LedgerEra)} | ErrTranslationError (TranslationError StandardCrypto) - deriving (Show) + deriving stock (Show) data ChangeError = ChangeError {inputBalance :: Coin, outputBalance :: Coin} - deriving (Show) + deriving stock (Show) -- | Cover fee for a transaction body using the given UTXO set. This calculate -- necessary fees and augments inputs / outputs / collateral accordingly to @@ -406,10 +406,10 @@ data TinyWalletLog | BeginUpdate {point :: ChainPoint} | EndUpdate {newUTxO :: Api.UTxO} | SkipUpdate {point :: ChainPoint} - deriving (Eq, Generic, Show) + deriving stock (Eq, Generic, Show) -deriving instance ToJSON TinyWalletLog -deriving instance FromJSON TinyWalletLog +deriving anyclass instance ToJSON TinyWalletLog +deriving anyclass instance FromJSON TinyWalletLog instance Arbitrary TinyWalletLog where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/Crypto.hs b/hydra-node/src/Hydra/Crypto.hs index baea1fa66a7..c119a70eb8b 100644 --- a/hydra-node/src/Hydra/Crypto.hs +++ b/hydra-node/src/Hydra/Crypto.hs @@ -92,7 +92,7 @@ instance Key HydraKey where -- Hydra verification key, which can be used to 'verify' signed messages. newtype VerificationKey HydraKey = HydraVerificationKey (VerKeyDSIGN Ed25519DSIGN) - deriving (Eq, Show, Ord) + deriving stock (Eq, Show, Ord) deriving newtype (ToCBOR, FromCBOR) deriving anyclass (SerialiseAsCBOR) @@ -105,7 +105,7 @@ instance Key HydraKey where -- material as well. newtype SigningKey HydraKey = HydraSigningKey (SignKeyDSIGN Ed25519DSIGN) - deriving (Eq, Show) + deriving stock (Eq, Show) deriving newtype (ToCBOR, FromCBOR) deriving anyclass (SerialiseAsCBOR) @@ -191,7 +191,7 @@ generateSigningKey seed = -- | Signature of 'a', not containing the actual payload. newtype Signature a = HydraSignature (SigDSIGN Ed25519DSIGN) - deriving (Eq) + deriving stock (Eq) deriving newtype (ToCBOR, FromCBOR) instance Show (Signature a) where @@ -247,7 +247,7 @@ verify (HydraVerificationKey vk) (HydraSignature sig) a = -- | Naiively aggregated multi-signatures. newtype MultiSignature a = HydraMultiSignature {multiSignature :: [Signature a]} - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) deriving newtype (Semigroup, Monoid) deriving anyclass instance ToJSON a => ToJSON (MultiSignature a) diff --git a/hydra-node/src/Hydra/HeadLogic/Error.hs b/hydra-node/src/Hydra/HeadLogic/Error.hs index 0352df4847d..88520e5a8d6 100644 --- a/hydra-node/src/Hydra/HeadLogic/Error.hs +++ b/hydra-node/src/Hydra/HeadLogic/Error.hs @@ -25,10 +25,10 @@ instance (Typeable tx, Show (Event tx), Show (HeadState tx), Show (RequirementFa instance (Arbitrary (Event tx), Arbitrary (HeadState tx), Arbitrary (RequirementFailure tx)) => Arbitrary (LogicError tx) where arbitrary = genericArbitrary -deriving instance (Eq (HeadState tx), Eq (Event tx), Eq (RequirementFailure tx)) => Eq (LogicError tx) -deriving instance (Show (HeadState tx), Show (Event tx), Show (RequirementFailure tx)) => Show (LogicError tx) -deriving instance (ToJSON (HeadState tx), ToJSON (Event tx), ToJSON (RequirementFailure tx)) => ToJSON (LogicError tx) -deriving instance (FromJSON (HeadState tx), FromJSON (Event tx), FromJSON (RequirementFailure tx)) => FromJSON (LogicError tx) +deriving stock instance (Eq (HeadState tx), Eq (Event tx), Eq (RequirementFailure tx)) => Eq (LogicError tx) +deriving stock instance (Show (HeadState tx), Show (Event tx), Show (RequirementFailure tx)) => Show (LogicError tx) +deriving anyclass instance (ToJSON (HeadState tx), ToJSON (Event tx), ToJSON (RequirementFailure tx)) => ToJSON (LogicError tx) +deriving anyclass instance (FromJSON (HeadState tx), FromJSON (Event tx), FromJSON (RequirementFailure tx)) => FromJSON (LogicError tx) data RequirementFailure tx = ReqSnNumberInvalid {requestedSn :: SnapshotNumber, lastSeenSn :: SnapshotNumber} @@ -39,10 +39,10 @@ data RequirementFailure tx | SnapshotDoesNotApply {requestedSn :: SnapshotNumber, txid :: TxIdType tx, error :: ValidationError} deriving stock (Generic) -deriving instance (Eq (TxIdType tx)) => Eq (RequirementFailure tx) -deriving instance (Show (TxIdType tx)) => Show (RequirementFailure tx) -deriving instance (ToJSON (TxIdType tx)) => ToJSON (RequirementFailure tx) -deriving instance (FromJSON (TxIdType tx)) => FromJSON (RequirementFailure tx) +deriving stock instance (Eq (TxIdType tx)) => Eq (RequirementFailure tx) +deriving stock instance (Show (TxIdType tx)) => Show (RequirementFailure tx) +deriving anyclass instance (ToJSON (TxIdType tx)) => ToJSON (RequirementFailure tx) +deriving anyclass instance (FromJSON (TxIdType tx)) => FromJSON (RequirementFailure tx) instance Arbitrary (TxIdType tx) => Arbitrary (RequirementFailure tx) where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/HeadLogic/Event.hs b/hydra-node/src/Hydra/HeadLogic/Event.hs index 37745673766..18dc0282715 100644 --- a/hydra-node/src/Hydra/HeadLogic/Event.hs +++ b/hydra-node/src/Hydra/HeadLogic/Event.hs @@ -37,10 +37,10 @@ data Event tx PostTxError {postChainTx :: PostChainTx tx, postTxError :: PostTxError tx} deriving stock (Generic) -deriving instance (IsChainState tx) => Eq (Event tx) -deriving instance (IsChainState tx) => Show (Event tx) -deriving instance (IsChainState tx) => ToJSON (Event tx) -deriving instance (IsChainState tx) => FromJSON (Event tx) +deriving stock instance (IsChainState tx) => Eq (Event tx) +deriving stock instance (IsChainState tx) => Show (Event tx) +deriving anyclass instance (IsChainState tx) => ToJSON (Event tx) +deriving anyclass instance (IsChainState tx) => FromJSON (Event tx) instance ( IsTx tx diff --git a/hydra-node/src/Hydra/HeadLogic/Outcome.hs b/hydra-node/src/Hydra/HeadLogic/Outcome.hs index 36e8d44e3f5..29b4990e576 100644 --- a/hydra-node/src/Hydra/HeadLogic/Outcome.hs +++ b/hydra-node/src/Hydra/HeadLogic/Outcome.hs @@ -27,10 +27,10 @@ data Effect tx OnChainEffect {postChainTx :: PostChainTx tx} deriving stock (Generic) -deriving instance (IsChainState tx) => Eq (Effect tx) -deriving instance (IsChainState tx) => Show (Effect tx) -deriving instance (IsChainState tx) => ToJSON (Effect tx) -deriving instance (IsChainState tx) => FromJSON (Effect tx) +deriving stock instance (IsChainState tx) => Eq (Effect tx) +deriving stock instance (IsChainState tx) => Show (Effect tx) +deriving anyclass instance (IsChainState tx) => ToJSON (Effect tx) +deriving anyclass instance (IsChainState tx) => FromJSON (Effect tx) instance ( IsTx tx @@ -82,10 +82,10 @@ data StateChanged tx instance (IsTx tx, Arbitrary (HeadState tx), Arbitrary (ChainStateType tx)) => Arbitrary (StateChanged tx) where arbitrary = genericArbitrary -deriving instance (IsTx tx, Eq (HeadState tx), Eq (ChainStateType tx)) => Eq (StateChanged tx) -deriving instance (IsTx tx, Show (HeadState tx), Show (ChainStateType tx)) => Show (StateChanged tx) -deriving instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (StateChanged tx) -deriving instance (IsTx tx, FromJSON (HeadState tx), FromJSON (ChainStateType tx)) => FromJSON (StateChanged tx) +deriving stock instance (IsTx tx, Eq (HeadState tx), Eq (ChainStateType tx)) => Eq (StateChanged tx) +deriving stock instance (IsTx tx, Show (HeadState tx), Show (ChainStateType tx)) => Show (StateChanged tx) +deriving anyclass instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (StateChanged tx) +deriving anyclass instance (IsTx tx, FromJSON (HeadState tx), FromJSON (ChainStateType tx)) => FromJSON (StateChanged tx) data Outcome tx = Effects {effects :: [Effect tx]} @@ -98,10 +98,10 @@ data Outcome tx instance Semigroup (Outcome tx) where (<>) = Combined -deriving instance (IsChainState tx) => Eq (Outcome tx) -deriving instance (IsChainState tx) => Show (Outcome tx) -deriving instance (IsChainState tx) => ToJSON (Outcome tx) -deriving instance (IsChainState tx) => FromJSON (Outcome tx) +deriving stock instance (IsChainState tx) => Eq (Outcome tx) +deriving stock instance (IsChainState tx) => Show (Outcome tx) +deriving anyclass instance (IsChainState tx) => ToJSON (Outcome tx) +deriving anyclass instance (IsChainState tx) => FromJSON (Outcome tx) instance (IsTx tx, Arbitrary (ChainStateType tx)) => Arbitrary (Outcome tx) where arbitrary = genericArbitrary @@ -130,10 +130,10 @@ data WaitReason tx | WaitOnContestationDeadline deriving stock (Generic) -deriving instance (IsTx tx) => Eq (WaitReason tx) -deriving instance (IsTx tx) => Show (WaitReason tx) -deriving instance (IsTx tx) => ToJSON (WaitReason tx) -deriving instance (IsTx tx) => FromJSON (WaitReason tx) +deriving stock instance (IsTx tx) => Eq (WaitReason tx) +deriving stock instance (IsTx tx) => Show (WaitReason tx) +deriving anyclass instance (IsTx tx) => ToJSON (WaitReason tx) +deriving anyclass instance (IsTx tx) => FromJSON (WaitReason tx) instance IsTx tx => Arbitrary (WaitReason tx) where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/HeadLogic/SnapshotOutcome.hs b/hydra-node/src/Hydra/HeadLogic/SnapshotOutcome.hs index 2be3688ab4b..3dd3f3a281b 100644 --- a/hydra-node/src/Hydra/HeadLogic/SnapshotOutcome.hs +++ b/hydra-node/src/Hydra/HeadLogic/SnapshotOutcome.hs @@ -11,13 +11,13 @@ import Hydra.Snapshot (SnapshotNumber) data SnapshotOutcome tx = ShouldSnapshot SnapshotNumber [tx] -- TODO(AB) : should really be a Set (TxId tx) | ShouldNotSnapshot NoSnapshotReason - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) data NoSnapshotReason = NotLeader SnapshotNumber | SnapshotInFlight SnapshotNumber | NoTransactionsToSnapshot - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) isLeader :: HeadParameters -> Party -> SnapshotNumber -> Bool isLeader HeadParameters{parties} p sn = diff --git a/hydra-node/src/Hydra/HeadLogic/State.hs b/hydra-node/src/Hydra/HeadLogic/State.hs index 68a7d9f50db..a48cf4c2884 100644 --- a/hydra-node/src/Hydra/HeadLogic/State.hs +++ b/hydra-node/src/Hydra/HeadLogic/State.hs @@ -22,7 +22,7 @@ data Environment = Environment , otherParties :: [Party] , contestationPeriod :: ContestationPeriod } - deriving (Show) + deriving stock (Show) instance Arbitrary Environment where arbitrary = do @@ -51,10 +51,10 @@ data HeadState tx instance (IsTx tx, Arbitrary (ChainStateType tx)) => Arbitrary (HeadState tx) where arbitrary = genericArbitrary -deriving instance (IsTx tx, Eq (ChainStateType tx)) => Eq (HeadState tx) -deriving instance (IsTx tx, Show (ChainStateType tx)) => Show (HeadState tx) -deriving instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (HeadState tx) -deriving instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (HeadState tx) +deriving stock instance (IsTx tx, Eq (ChainStateType tx)) => Eq (HeadState tx) +deriving stock instance (IsTx tx, Show (ChainStateType tx)) => Show (HeadState tx) +deriving anyclass instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (HeadState tx) +deriving anyclass instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (HeadState tx) -- | Update the chain state in any 'HeadState'. setChainState :: ChainStateType tx -> HeadState tx -> HeadState tx @@ -76,10 +76,10 @@ getHeadParameters = \case -- | An 'Idle' head only having a chain state with things seen on chain so far. newtype IdleState tx = IdleState {chainState :: ChainStateType tx} - deriving (Generic) + deriving stock (Generic) -deriving instance Eq (ChainStateType tx) => Eq (IdleState tx) -deriving instance Show (ChainStateType tx) => Show (IdleState tx) +deriving stock instance Eq (ChainStateType tx) => Eq (IdleState tx) +deriving stock instance Show (ChainStateType tx) => Show (IdleState tx) deriving anyclass instance ToJSON (ChainStateType tx) => ToJSON (IdleState tx) deriving anyclass instance FromJSON (ChainStateType tx) => FromJSON (IdleState tx) @@ -96,12 +96,12 @@ data InitialState tx = InitialState , chainState :: ChainStateType tx , headId :: HeadId } - deriving (Generic) + deriving stock (Generic) -deriving instance (IsTx tx, Eq (ChainStateType tx)) => Eq (InitialState tx) -deriving instance (IsTx tx, Show (ChainStateType tx)) => Show (InitialState tx) -deriving instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (InitialState tx) -deriving instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (InitialState tx) +deriving stock instance (IsTx tx, Eq (ChainStateType tx)) => Eq (InitialState tx) +deriving stock instance (IsTx tx, Show (ChainStateType tx)) => Show (InitialState tx) +deriving anyclass instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (InitialState tx) +deriving anyclass instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (InitialState tx) instance (IsTx tx, Arbitrary (ChainStateType tx)) => Arbitrary (InitialState tx) where arbitrary = do @@ -127,12 +127,12 @@ data OpenState tx = OpenState , headId :: HeadId , currentSlot :: ChainSlot } - deriving (Generic) + deriving stock (Generic) -deriving instance (IsTx tx, Eq (ChainStateType tx)) => Eq (OpenState tx) -deriving instance (IsTx tx, Show (ChainStateType tx)) => Show (OpenState tx) -deriving instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (OpenState tx) -deriving instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (OpenState tx) +deriving stock instance (IsTx tx, Eq (ChainStateType tx)) => Eq (OpenState tx) +deriving stock instance (IsTx tx, Show (ChainStateType tx)) => Show (OpenState tx) +deriving anyclass instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (OpenState tx) +deriving anyclass instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (OpenState tx) instance (IsTx tx, Arbitrary (ChainStateType tx)) => Arbitrary (OpenState tx) where arbitrary = @@ -160,10 +160,10 @@ data CoordinatedHeadState tx = CoordinatedHeadState } deriving stock (Generic) -deriving instance IsTx tx => Eq (CoordinatedHeadState tx) -deriving instance IsTx tx => Show (CoordinatedHeadState tx) -deriving instance IsTx tx => ToJSON (CoordinatedHeadState tx) -deriving instance IsTx tx => FromJSON (CoordinatedHeadState tx) +deriving stock instance IsTx tx => Eq (CoordinatedHeadState tx) +deriving stock instance IsTx tx => Show (CoordinatedHeadState tx) +deriving anyclass instance IsTx tx => ToJSON (CoordinatedHeadState tx) +deriving anyclass instance IsTx tx => FromJSON (CoordinatedHeadState tx) instance IsTx tx => Arbitrary (CoordinatedHeadState tx) where arbitrary = genericArbitrary @@ -191,10 +191,10 @@ data SeenSnapshot tx instance IsTx tx => Arbitrary (SeenSnapshot tx) where arbitrary = genericArbitrary -deriving instance IsTx tx => Eq (SeenSnapshot tx) -deriving instance IsTx tx => Show (SeenSnapshot tx) -deriving instance IsTx tx => ToJSON (SeenSnapshot tx) -deriving instance IsTx tx => FromJSON (SeenSnapshot tx) +deriving stock instance IsTx tx => Eq (SeenSnapshot tx) +deriving stock instance IsTx tx => Show (SeenSnapshot tx) +deriving anyclass instance IsTx tx => ToJSON (SeenSnapshot tx) +deriving anyclass instance IsTx tx => FromJSON (SeenSnapshot tx) -- | Get the last seen snapshot number given a 'SeenSnapshot'. seenSnapshotNumber :: SeenSnapshot tx -> SnapshotNumber @@ -218,12 +218,12 @@ data ClosedState tx = ClosedState , chainState :: ChainStateType tx , headId :: HeadId } - deriving (Generic) + deriving stock (Generic) -deriving instance (IsTx tx, Eq (ChainStateType tx)) => Eq (ClosedState tx) -deriving instance (IsTx tx, Show (ChainStateType tx)) => Show (ClosedState tx) -deriving instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (ClosedState tx) -deriving instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (ClosedState tx) +deriving stock instance (IsTx tx, Eq (ChainStateType tx)) => Eq (ClosedState tx) +deriving stock instance (IsTx tx, Show (ChainStateType tx)) => Show (ClosedState tx) +deriving anyclass instance (IsTx tx, ToJSON (ChainStateType tx)) => ToJSON (ClosedState tx) +deriving anyclass instance (IsTx tx, FromJSON (ChainStateType tx)) => FromJSON (ClosedState tx) instance (IsTx tx, Arbitrary (ChainStateType tx)) => Arbitrary (ClosedState tx) where arbitrary = diff --git a/hydra-node/src/Hydra/Ledger.hs b/hydra-node/src/Hydra/Ledger.hs index b4a036a1b4f..d2ac62a3d8d 100644 --- a/hydra-node/src/Hydra/Ledger.hs +++ b/hydra-node/src/Hydra/Ledger.hs @@ -54,7 +54,7 @@ class -- | A generic description for a chain slot all implementions need to use. newtype ChainSlot = ChainSlot Natural - deriving (Ord, Eq, Show, Generic) + deriving stock (Ord, Eq, Show, Generic) deriving newtype (Num, ToJSON, FromJSON) instance Arbitrary ChainSlot where diff --git a/hydra-node/src/Hydra/Ledger/Cardano/Builder.hs b/hydra-node/src/Hydra/Ledger/Cardano/Builder.hs index cb5dd0d5d16..89ed068da89 100644 --- a/hydra-node/src/Hydra/Ledger/Cardano/Builder.hs +++ b/hydra-node/src/Hydra/Ledger/Cardano/Builder.hs @@ -30,7 +30,7 @@ data InvalidTransactionException = InvalidTransactionException { txBodyError :: TxBodyError , builder :: TxBodyContent BuildTx } - deriving (Show) + deriving stock (Show) instance Exception InvalidTransactionException diff --git a/hydra-node/src/Hydra/Ledger/Cardano/Configuration.hs b/hydra-node/src/Hydra/Ledger/Cardano/Configuration.hs index 97e5372c409..7f3139e7330 100644 --- a/hydra-node/src/Hydra/Ledger/Cardano/Configuration.hs +++ b/hydra-node/src/Hydra/Ledger/Cardano/Configuration.hs @@ -28,7 +28,8 @@ readJsonFileThrow parser filepath = do -- * Globals -data GlobalsTranslationException = GlobalsTranslationException deriving (Eq, Show) +data GlobalsTranslationException = GlobalsTranslationException + deriving stock (Eq, Show) instance Exception GlobalsTranslationException diff --git a/hydra-node/src/Hydra/Ledger/Cardano/Evaluate.hs b/hydra-node/src/Hydra/Ledger/Cardano/Evaluate.hs index 0458bc26954..9453113b5a3 100644 --- a/hydra-node/src/Hydra/Ledger/Cardano/Evaluate.hs +++ b/hydra-node/src/Hydra/Ledger/Cardano/Evaluate.hs @@ -145,7 +145,7 @@ data EvaluationError = TransactionBudgetOverspent {used :: ExecutionUnits, available :: ExecutionUnits} | TransactionInvalid TransactionValidityError | PParamsConversion ProtocolParametersConversionError - deriving (Show) + deriving stock (Show) -- | Evaluation result for each of the included scripts. Either they failed -- evaluation or used a number of 'ExecutionUnits'. diff --git a/hydra-node/src/Hydra/Ledger/Simple.hs b/hydra-node/src/Hydra/Ledger/Simple.hs index b7a52f25cb6..4881a557247 100644 --- a/hydra-node/src/Hydra/Ledger/Simple.hs +++ b/hydra-node/src/Hydra/Ledger/Simple.hs @@ -86,7 +86,7 @@ instance FromCBOR SimpleTx where -- * Simple chain state newtype SimpleChainState = SimpleChainState {slot :: ChainSlot} - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) deriving anyclass (ToJSON, FromJSON) instance Arbitrary SimpleChainState where diff --git a/hydra-node/src/Hydra/Logging.hs b/hydra-node/src/Hydra/Logging.hs index 3b48e495f67..97bbd69217b 100644 --- a/hydra-node/src/Hydra/Logging.hs +++ b/hydra-node/src/Hydra/Logging.hs @@ -51,7 +51,8 @@ import Test.QuickCheck.Instances.Text () import Test.QuickCheck.Instances.Time () data Verbosity = Quiet | Verbose Text - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) -- | Provides logging metadata for entries. data Envelope a = Envelope @@ -60,7 +61,8 @@ data Envelope a = Envelope , namespace :: Text , message :: a } - deriving (Eq, Show, Generic, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (FromJSON) instance ToJSON a => ToJSON (Envelope a) where toEncoding Envelope{timestamp, threadId, namespace, message} = diff --git a/hydra-node/src/Hydra/Logging/Messages.hs b/hydra-node/src/Hydra/Logging/Messages.hs index cbfa94b8a6c..c11ddd25132 100644 --- a/hydra-node/src/Hydra/Logging/Messages.hs +++ b/hydra-node/src/Hydra/Logging/Messages.hs @@ -25,12 +25,12 @@ data HydraLog tx net | NodeOptions {runOptions :: RunOptions} | Authentication {authentication :: AuthLog} | Reliability {reliability :: ReliabilityLog} - deriving (Generic) + deriving stock (Generic) -deriving instance (Eq net, Eq (HydraNodeLog tx)) => Eq (HydraLog tx net) -deriving instance (Show net, Show (HydraNodeLog tx)) => Show (HydraLog tx net) -deriving instance (ToJSON net, ToJSON (HydraNodeLog tx)) => ToJSON (HydraLog tx net) -deriving instance (FromJSON net, FromJSON (HydraNodeLog tx)) => FromJSON (HydraLog tx net) +deriving stock instance (Eq net, Eq (HydraNodeLog tx)) => Eq (HydraLog tx net) +deriving stock instance (Show net, Show (HydraNodeLog tx)) => Show (HydraLog tx net) +deriving anyclass instance (ToJSON net, ToJSON (HydraNodeLog tx)) => ToJSON (HydraLog tx net) +deriving anyclass instance (FromJSON net, FromJSON (HydraNodeLog tx)) => FromJSON (HydraLog tx net) instance (Arbitrary net, Arbitrary (HydraNodeLog tx)) => Arbitrary (HydraLog tx net) where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/Network.hs b/hydra-node/src/Hydra/Network.hs index 628e67022fe..fdf240ec002 100644 --- a/hydra-node/src/Hydra/Network.hs +++ b/hydra-node/src/Hydra/Network.hs @@ -36,8 +36,8 @@ import Test.QuickCheck (elements, listOf, suchThat) import Text.Read (Read (readsPrec)) import Text.Show (Show (show)) -deriving instance ToJSON IP -deriving instance FromJSON IP +deriving anyclass instance ToJSON IP +deriving anyclass instance FromJSON IP -- * Hydra network interface @@ -99,7 +99,8 @@ data Host = Host { hostname :: Text , port :: PortNumber } - deriving (Ord, Generic, Eq, ToJSON, FromJSON) + deriving stock (Ord, Generic, Eq) + deriving anyclass (ToJSON, FromJSON) instance Show Host where show = showHost diff --git a/hydra-node/src/Hydra/Network/Heartbeat.hs b/hydra-node/src/Hydra/Network/Heartbeat.hs index a6b65bc7378..b083e00eb05 100644 --- a/hydra-node/src/Hydra/Network/Heartbeat.hs +++ b/hydra-node/src/Hydra/Network/Heartbeat.hs @@ -35,7 +35,7 @@ data HeartbeatState = HeartbeatState -- ^ The set of known parties which might be 'Disconnected' -- This is updated after some time no message has been received from a node. } - deriving (Eq) + deriving stock (Eq) initialHeartbeatState :: HeartbeatState initialHeartbeatState = HeartbeatState{alive = mempty, suspected = mempty} diff --git a/hydra-node/src/Hydra/Network/Message.hs b/hydra-node/src/Hydra/Network/Message.hs index 0f206fd08e7..430be9eb0b5 100644 --- a/hydra-node/src/Hydra/Network/Message.hs +++ b/hydra-node/src/Hydra/Network/Message.hs @@ -31,10 +31,10 @@ data Message tx AckSn {signed :: Signature (Snapshot tx), snapshotNumber :: SnapshotNumber} deriving stock (Generic) -deriving instance (IsTx tx) => Eq (Message tx) -deriving instance (IsTx tx) => Show (Message tx) -deriving instance (IsTx tx) => ToJSON (Message tx) -deriving instance (IsTx tx) => FromJSON (Message tx) +deriving stock instance (IsTx tx) => Eq (Message tx) +deriving stock instance (IsTx tx) => Show (Message tx) +deriving anyclass instance (IsTx tx) => ToJSON (Message tx) +deriving anyclass instance (IsTx tx) => FromJSON (Message tx) instance IsTx tx => Arbitrary (Message tx) where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/Network/Ouroboros.hs b/hydra-node/src/Hydra/Network/Ouroboros.hs index f26e861b052..99276fd4906 100644 --- a/hydra-node/src/Hydra/Network/Ouroboros.hs +++ b/hydra-node/src/Hydra/Network/Ouroboros.hs @@ -282,12 +282,12 @@ data NetworkServerListenException = NetworkServerListenException { ioException :: IOException , localHost :: Host } - deriving (Show) + deriving stock (Show) instance Exception NetworkServerListenException data WithHost trace = WithHost Host trace - deriving (Show) + deriving stock (Show) instance ToJSON trace => ToJSON (WithHost trace) where toJSON (WithHost h tr) = diff --git a/hydra-node/src/Hydra/Node.hs b/hydra-node/src/Hydra/Node.hs index 749d599c151..23b9e026732 100644 --- a/hydra-node/src/Hydra/Node.hs +++ b/hydra-node/src/Hydra/Node.hs @@ -77,7 +77,7 @@ initEnvironment RunOptions{hydraSigningKey, hydraVerificationKeys, chainConfig = -- | Exception used to indicate command line options not matching the persisted -- state. newtype ParameterMismatch = ParameterMismatch [ParamMismatch] - deriving (Eq, Show) + deriving stock (Eq, Show) deriving anyclass (Exception) data ParamMismatch @@ -144,10 +144,10 @@ data HydraNodeLog tx | Misconfiguration {misconfigurationErrors :: [ParamMismatch]} deriving stock (Generic) -deriving instance (IsChainState tx) => Eq (HydraNodeLog tx) -deriving instance (IsChainState tx) => Show (HydraNodeLog tx) -deriving instance (IsChainState tx) => ToJSON (HydraNodeLog tx) -deriving instance (IsChainState tx) => FromJSON (HydraNodeLog tx) +deriving stock instance (IsChainState tx) => Eq (HydraNodeLog tx) +deriving stock instance (IsChainState tx) => Show (HydraNodeLog tx) +deriving anyclass instance (IsChainState tx) => ToJSON (HydraNodeLog tx) +deriving anyclass instance (IsChainState tx) => FromJSON (HydraNodeLog tx) instance (IsTx tx, Arbitrary (ChainStateType tx)) => Arbitrary (HydraNodeLog tx) where arbitrary = genericArbitrary diff --git a/hydra-node/src/Hydra/Options.hs b/hydra-node/src/Hydra/Options.hs index 515b3c69353..0bed79c8103 100644 --- a/hydra-node/src/Hydra/Options.hs +++ b/hydra-node/src/Hydra/Options.hs @@ -91,7 +91,7 @@ data Command = Run RunOptions | Publish PublishOptions | GenHydraKey GenerateKeyPair - deriving (Show, Eq) + deriving stock (Show, Eq) commandParser :: Parser Command commandParser = @@ -136,7 +136,7 @@ data PublishOptions = PublishOptions , publishNodeSocket :: SocketPath , publishSigningKey :: FilePath } - deriving (Show, Eq) + deriving stock (Show, Eq) publishOptionsParser :: Parser PublishOptions publishOptionsParser = @@ -162,7 +162,8 @@ data RunOptions = RunOptions , chainConfig :: ChainConfig , ledgerConfig :: LedgerConfig } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) instance Arbitrary RunOptions where arbitrary = do @@ -219,7 +220,7 @@ runOptionsParser = newtype GenerateKeyPair = GenerateKeyPair { outputFile :: FilePath } - deriving (Eq, Show) + deriving stock (Eq, Show) genHydraKeyParser :: Parser GenerateKeyPair genHydraKeyParser = @@ -288,7 +289,8 @@ data ChainConfig = DirectChainConfig -- ^ Point at which to start following the chain. , contestationPeriod :: ContestationPeriod } - deriving (Eq, Show, Generic, ToJSON, FromJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON, FromJSON) defaultChainConfig :: ChainConfig defaultChainConfig = @@ -632,7 +634,7 @@ contestationPeriodParser = data InvalidOptions = MaximumNumberOfPartiesExceeded | CardanoAndHydraKeysMissmatch - deriving (Eq, Show) + deriving stock (Eq, Show) explain :: InvalidOptions -> String explain = \case diff --git a/hydra-node/src/Hydra/Party.hs b/hydra-node/src/Hydra/Party.hs index a67513118d1..d989875b898 100644 --- a/hydra-node/src/Hydra/Party.hs +++ b/hydra-node/src/Hydra/Party.hs @@ -13,7 +13,7 @@ import qualified Hydra.Data.Party as OnChain -- | Identifies a party in a Hydra head by it's 'VerificationKey'. newtype Party = Party {vkey :: VerificationKey HydraKey} - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) deriving anyclass (ToJSON, FromJSON, FromJSONKey, ToJSONKey) -- REVIEW: Do we really want to define Ord or also use unordered-containers diff --git a/hydra-node/src/Hydra/Persistence.hs b/hydra-node/src/Hydra/Persistence.hs index a81bc3e23bb..d78d1da99f9 100644 --- a/hydra-node/src/Hydra/Persistence.hs +++ b/hydra-node/src/Hydra/Persistence.hs @@ -13,7 +13,7 @@ import UnliftIO.IO.File (withBinaryFile, writeBinaryFileDurableAtomic) newtype PersistenceException = PersistenceException String - deriving (Eq, Show) + deriving stock (Eq, Show) instance Exception PersistenceException diff --git a/hydra-node/src/Hydra/Snapshot.hs b/hydra-node/src/Hydra/Snapshot.hs index 1b695b27ffe..eb7e6ec8a79 100644 --- a/hydra-node/src/Hydra/Snapshot.hs +++ b/hydra-node/src/Hydra/Snapshot.hs @@ -17,7 +17,7 @@ import Test.QuickCheck.Instances.Natural () newtype SnapshotNumber = UnsafeSnapshotNumber Natural - deriving (Eq, Ord, Generic) + deriving stock (Eq, Ord, Generic) deriving newtype (Show, ToJSON, FromJSON, ToCBOR, FromCBOR, Real, Num, Enum, Integral) instance Arbitrary SnapshotNumber where @@ -29,10 +29,10 @@ data Snapshot tx = Snapshot , confirmed :: [TxIdType tx] -- ^ The set of transactions that lead to 'utxo' } - deriving (Generic) + deriving stock (Generic) -deriving instance IsTx tx => Eq (Snapshot tx) -deriving instance IsTx tx => Show (Snapshot tx) +deriving stock instance IsTx tx => Eq (Snapshot tx) +deriving stock instance IsTx tx => Show (Snapshot tx) instance (Arbitrary (TxIdType tx), Arbitrary (UTxOType tx)) => Arbitrary (Snapshot tx) where arbitrary = genericArbitrary @@ -81,7 +81,8 @@ data ConfirmedSnapshot tx { snapshot :: Snapshot tx , signatures :: MultiSignature (Snapshot tx) } - deriving (Generic, Eq, Show, ToJSON, FromJSON) + deriving stock (Generic, Eq, Show) + deriving anyclass (ToJSON, FromJSON) -- NOTE: While we could use 'snapshot' directly, this is a record-field accessor -- which may become partial (and lead to unnoticed runtime errors) if we ever diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Abort.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Abort.hs index d9b39b2aa36..9dacfe78196 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Abort.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Abort.hs @@ -164,9 +164,9 @@ data AbortMutation ExtractValue | -- | State token is not burned DoNotBurnST - | -- Here we want to check that the initial validator also fails on abort. + | -- | Here we want to check that the initial validator also fails on abort. DoNotBurnSTInitial - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genAbortMutation :: (Tx, UTxO) -> Gen SomeMutation genAbortMutation (tx, utxo) = diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs index 939a7e80efb..0ac98b12388 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs @@ -286,7 +286,7 @@ data CloseMutation MutateValueInOutput | -- | Invalidate the tx by changing the contestation period. MutateContestationPeriod - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genCloseMutation :: (Tx, UTxO) -> Gen SomeMutation genCloseMutation (tx, _utxo) = @@ -388,7 +388,7 @@ genCloseMutation (tx, _utxo) = data CloseInitialMutation = MutateCloseContestationDeadline' - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) -- | Mutations for the specific case of closing with the intial state. -- We should probably validate all the mutation to this initial state but at diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/CollectCom.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/CollectCom.hs index d243d2e53cf..a55ff169dd5 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/CollectCom.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/CollectCom.hs @@ -148,7 +148,7 @@ data HealthyCommit = HealthyCommit , txOut :: TxOut CtxUTxO , scriptData :: HashableScriptData } - deriving (Show) + deriving stock (Show) healthyCommitOutput :: Party -> @@ -201,7 +201,7 @@ data CollectComMutation MutateTokenMintingOrBurning | -- | νCommit validator checks the ST is in the output RemoveSTFromOutput - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genCollectComMutation :: (Tx, UTxO) -> Gen SomeMutation genCollectComMutation (tx, _utxo) = diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Commit.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Commit.hs index ade1d6237a9..a03abd4b75b 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Commit.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Commit.hs @@ -103,7 +103,7 @@ data CommitMutation UsePTFromDifferentHead | -- | Minting or burning of the tokens should not be possible in commit. MutateTokenMintingOrBurning - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genCommitMutation :: (Tx, UTxO) -> Gen SomeMutation genCommitMutation (tx, _utxo) = diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs index 16adff22699..6eedfd81f2c 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs @@ -256,7 +256,7 @@ data ContestMutation | -- | Ensures headId do not change between head input datum and head output -- datum. MutateHeadIdInOutput - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genContestMutation :: (Tx, UTxO) -> Gen SomeMutation genContestMutation (tx, _utxo) = diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/FanOut.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/FanOut.hs index a882e62131a..99de449d2fa 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/FanOut.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/FanOut.hs @@ -101,7 +101,7 @@ data FanoutMutation = MutateAddUnexpectedOutput | MutateChangeOutputValue | MutateValidityBeforeDeadline - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genFanoutMutation :: (Tx, UTxO) -> Gen SomeMutation genFanoutMutation (tx, _utxo) = diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Init.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Init.hs index 81a9fc6e622..9edb026bacc 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Init.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Init.hs @@ -78,11 +78,11 @@ data InitMutation | MutateHeadIdInDatum | MutateHeadIdInInitialDatum | MutateSeedInDatum - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) data ObserveInitMutation = MutateSomePT - deriving (Generic, Show, Enum, Bounded) + deriving stock (Generic, Show, Enum, Bounded) genInitMutation :: (Tx, UTxO) -> Gen SomeMutation genInitMutation (tx, _utxo) = diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Mutation.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Mutation.hs index 0f35249d292..54f6c6ef09f 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Mutation.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Mutation.hs @@ -254,7 +254,7 @@ data SomeMutation = forall lbl. , mutation :: Mutation } -deriving instance Show SomeMutation +deriving stock instance Show SomeMutation -- | Basic mutations data Mutation @@ -304,7 +304,7 @@ data Mutation -- change of more than one thing in the transaction and/or UTxO set, for -- example to change consistently the Head script's redeemer and datum. Changes [Mutation] - deriving (Show, Generic) + deriving stock (Show, Generic) -- | Apply a single 'Mutation' to the given (transaction, UTxO) pair. -- '''NOTE''': This function is partial, it can raise 'error' when some preconditions @@ -489,7 +489,7 @@ applyMutation mutation (tx@(Tx body wits), utxo) = case mutation of -- * Orphans -deriving instance Eq Head.Input +deriving stock instance Eq Head.Input instance Arbitrary Head.Input where arbitrary = genericArbitrary diff --git a/hydra-node/test/Hydra/Model.hs b/hydra-node/test/Hydra/Model.hs index b97c4475d5d..0c229ac5ff0 100644 --- a/hydra-node/test/Hydra/Model.hs +++ b/hydra-node/test/Hydra/Model.hs @@ -88,7 +88,7 @@ data WorldState = WorldState -- ^ Expected consensus state -- All nodes should be in the same state. } - deriving (Eq, Show) + deriving stock (Eq, Show) -- | Global state of the Head protocol. -- While each participant in the Hydra Head protocol has its own private @@ -322,8 +322,8 @@ instance HasVariables WorldState where instance HasVariables (Action WorldState a) where getAllVariables _ = mempty -deriving instance Show (Action WorldState a) -deriving instance Eq (Action WorldState a) +deriving stock instance Show (Action WorldState a) +deriving stock instance Eq (Action WorldState a) -- ** Generator Helper @@ -430,7 +430,7 @@ data RunException | UnexpectedParty Party | UnknownAddress AddressInEra [(AddressInEra, CardanoSigningKey)] | CannotFindSpendableUTxO Payment UTxO - deriving (Eq, Show) + deriving stock (Eq, Show) instance Exception RunException diff --git a/hydra-node/test/Hydra/Model/Payment.hs b/hydra-node/test/Hydra/Model/Payment.hs index 8b4866048ae..9084fcbd417 100644 --- a/hydra-node/test/Hydra/Model/Payment.hs +++ b/hydra-node/test/Hydra/Model/Payment.hs @@ -48,7 +48,8 @@ data Payment = Payment , to :: CardanoSigningKey , value :: Value } - deriving (Eq, Generic, ToJSON, FromJSON) + deriving stock (Eq, Generic) + deriving anyclass (ToJSON, FromJSON) instance Show Payment where -- NOTE: We display derived addresses instead of raw signing keys in order to help troubleshooting diff --git a/hydra-plutus/src/Hydra/Contract.hs b/hydra-plutus/src/Hydra/Contract.hs index b5f0156e617..061bce1483a 100644 --- a/hydra-plutus/src/Hydra/Contract.hs +++ b/hydra-plutus/src/Hydra/Contract.hs @@ -31,7 +31,8 @@ data ScriptInfo = ScriptInfo , headScriptHash :: ScriptHash , headScriptSize :: Int64 } - deriving (Eq, Show, Generic, ToJSON) + deriving stock (Eq, Show, Generic) + deriving anyclass (ToJSON) -- | Gather 'ScriptInfo' from the current Hydra scripts. This is useful to -- determine changes in between version of 'hydra-plutus'. diff --git a/hydra-plutus/src/Hydra/Contract/Commit.hs b/hydra-plutus/src/Hydra/Contract/Commit.hs index e5a43163d73..491ce6082ee 100644 --- a/hydra-plutus/src/Hydra/Contract/Commit.hs +++ b/hydra-plutus/src/Hydra/Contract/Commit.hs @@ -49,7 +49,7 @@ data Commit = Commit { input :: TxOutRef , preSerializedOutput :: BuiltinByteString } - deriving (Haskell.Eq, Haskell.Show, Haskell.Ord) + deriving stock (Haskell.Eq, Haskell.Show, Haskell.Ord) instance Eq Commit where (Commit i o) == (Commit i' o') = diff --git a/hydra-plutus/src/Hydra/Contract/CommitError.hs b/hydra-plutus/src/Hydra/Contract/CommitError.hs index ef5fdabaf3d..82ab0a1beeb 100644 --- a/hydra-plutus/src/Hydra/Contract/CommitError.hs +++ b/hydra-plutus/src/Hydra/Contract/CommitError.hs @@ -9,7 +9,7 @@ import Text.Show (Show) data CommitError = STNotBurnedError | STIsMissingInTheOutput - deriving (Show) + deriving stock (Show) instance ToErrorCode CommitError where toErrorCode = \case diff --git a/hydra-plutus/src/Hydra/Contract/Hash.hs b/hydra-plutus/src/Hydra/Contract/Hash.hs index 36f8469a063..6b25ef29019 100644 --- a/hydra-plutus/src/Hydra/Contract/Hash.hs +++ b/hydra-plutus/src/Hydra/Contract/Hash.hs @@ -32,7 +32,7 @@ data HashAlgorithm | SHA2 | SHA3 | Blake2b - deriving (Haskell.Show, Haskell.Generic, Haskell.Enum, Haskell.Bounded) + deriving stock (Haskell.Show, Haskell.Generic, Haskell.Enum, Haskell.Bounded) PlutusTx.unstableMakeIsData ''HashAlgorithm diff --git a/hydra-plutus/src/Hydra/Contract/HeadError.hs b/hydra-plutus/src/Hydra/Contract/HeadError.hs index 681fb3f5cc1..fd58dce99a7 100644 --- a/hydra-plutus/src/Hydra/Contract/HeadError.hs +++ b/hydra-plutus/src/Hydra/Contract/HeadError.hs @@ -45,7 +45,7 @@ data HeadError | PartySignatureVerificationFailed | NotPayingToHead | NotAllValueCollected - deriving (Show) + deriving stock (Show) instance ToErrorCode HeadError where toErrorCode = \case diff --git a/hydra-plutus/src/Hydra/Contract/HeadState.hs b/hydra-plutus/src/Hydra/Contract/HeadState.hs index 5ea70f3c475..821f7cc57b3 100644 --- a/hydra-plutus/src/Hydra/Contract/HeadState.hs +++ b/hydra-plutus/src/Hydra/Contract/HeadState.hs @@ -56,6 +56,6 @@ data Input } | Abort | Fanout {numberOfFanoutOutputs :: Integer} - deriving (Generic, Show) + deriving stock (Generic, Show) PlutusTx.unstableMakeIsData ''Input diff --git a/hydra-plutus/src/Hydra/Contract/HeadTokensError.hs b/hydra-plutus/src/Hydra/Contract/HeadTokensError.hs index 71ceff8865e..4985813bf80 100644 --- a/hydra-plutus/src/Hydra/Contract/HeadTokensError.hs +++ b/hydra-plutus/src/Hydra/Contract/HeadTokensError.hs @@ -19,7 +19,7 @@ data HeadTokensError | NoDatum | MultipleHeadOutput | WrongInitialDatum - deriving (Show) + deriving stock (Show) instance ToErrorCode HeadTokensError where toErrorCode = \case diff --git a/hydra-plutus/src/Hydra/Contract/InitialError.hs b/hydra-plutus/src/Hydra/Contract/InitialError.hs index fc93d7b2c68..40abe3bd066 100644 --- a/hydra-plutus/src/Hydra/Contract/InitialError.hs +++ b/hydra-plutus/src/Hydra/Contract/InitialError.hs @@ -23,7 +23,7 @@ data InitialError | WrongHeadIdInCommitDatum | MintingOrBurningIsForbidden | OutRefNotFound - deriving (Show) + deriving stock (Show) instance ToErrorCode InitialError where toErrorCode = \case diff --git a/hydra-plutus/src/Hydra/Contract/Util.hs b/hydra-plutus/src/Hydra/Contract/Util.hs index 34a782d70c0..8d93b45e69e 100644 --- a/hydra-plutus/src/Hydra/Contract/Util.hs +++ b/hydra-plutus/src/Hydra/Contract/Util.hs @@ -62,7 +62,7 @@ infix 4 === data UtilError = MintingOrBurningIsForbidden - deriving (Show) + deriving stock (Show) instance ToErrorCode UtilError where toErrorCode = \case diff --git a/hydra-prelude/hydra-prelude.cabal b/hydra-prelude/hydra-prelude.cabal index 7e6f18a1518..6279de3ce4e 100644 --- a/hydra-prelude/hydra-prelude.cabal +++ b/hydra-prelude/hydra-prelude.cabal @@ -36,8 +36,9 @@ library default-language: GHC2021 default-extensions: - NoImplicitPrelude DerivingStrategies LambdaCase + NoImplicitPrelude - ghc-options: -Wall -Wcompat -Wunused-packages + ghc-options: + -Wall -Wcompat -Wunused-packages -Wmissing-deriving-strategies diff --git a/hydra-test-utils/hydra-test-utils.cabal b/hydra-test-utils/hydra-test-utils.cabal index b2b1c659b66..ae60a8c2f78 100644 --- a/hydra-test-utils/hydra-test-utils.cabal +++ b/hydra-test-utils/hydra-test-utils.cabal @@ -26,6 +26,7 @@ common package-config ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -Wunused-packages + -Wmissing-deriving-strategies library import: package-config diff --git a/hydra-tui/src/Hydra/Client.hs b/hydra-tui/src/Hydra/Client.hs index 7370dfc5785..648c50d9567 100644 --- a/hydra-tui/src/Hydra/Client.hs +++ b/hydra-tui/src/Hydra/Client.hs @@ -31,10 +31,10 @@ data HydraEvent tx | ClientDisconnected | Update (TimedServerOutput tx) | Tick UTCTime - deriving (Generic) + deriving stock (Generic) -deriving instance (Eq (TimedServerOutput tx)) => Eq (HydraEvent tx) -deriving instance (Show (TimedServerOutput tx)) => Show (HydraEvent tx) +deriving stock instance (Eq (TimedServerOutput tx)) => Eq (HydraEvent tx) +deriving stock instance (Show (TimedServerOutput tx)) => Show (HydraEvent tx) -- | Handle to interact with Hydra node data Client tx m = Client @@ -110,5 +110,5 @@ withClient Options{hydraNodeHost = Host{hostname, port}, cardanoSigningKey, card (Req.port $ fromIntegral port) data ClientError = ClientJSONDecodeError String ByteString - deriving (Eq, Show, Generic) + deriving stock (Eq, Show, Generic) deriving anyclass (Exception) diff --git a/hydra-tui/test/Hydra/TUISpec.hs b/hydra-tui/test/Hydra/TUISpec.hs index 31c023b0ef2..aab6e2cc918 100644 --- a/hydra-tui/test/Hydra/TUISpec.hs +++ b/hydra-tui/test/Hydra/TUISpec.hs @@ -295,4 +295,5 @@ data TUILog = FromCardano NodeLog | FromHydra EndToEndLog | FromFaucet FaucetLog - deriving (Show, Generic, ToJSON) + deriving stock (Show, Generic) + deriving anyclass (ToJSON)