Skip to content

Commit fab327e

Browse files
cleanup
1 parent 10eaa57 commit fab327e

File tree

3 files changed

+6
-12
lines changed

3 files changed

+6
-12
lines changed

dmq-node/app/Main.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ runDMQ commandLineConfig = do
115115
res <- KES.evolutionConfigFromGenesisFile genesisFile
116116
evolutionConfig <- case res of
117117
Left err -> traceWith tracer (WithEventType "ShelleyGenesisFile" err)
118-
>> throwIO (userError $ err)
118+
>> throwIO (userError err)
119119
Right ev -> return ev
120120

121121
traceWith tracer (WithEventType "Configuration" dmqConfig)
@@ -136,7 +136,7 @@ runDMQ commandLineConfig = do
136136
psRng
137137
mkStakePoolMonitor $ \nodeKernel -> do
138138
dmqDiffusionConfiguration <-
139-
mkDiffusionConfiguration dmqConfig nt (nodeKernel.stakePools.ledgerBigPeersVar)
139+
mkDiffusionConfiguration dmqConfig nt nodeKernel.stakePools.ledgerBigPeersVar
140140

141141
let sigSize :: Sig StandardCrypto -> SizeInBytes
142142
sigSize _ = 0 -- TODO
@@ -179,7 +179,7 @@ runDMQ commandLineConfig = do
179179
(if localHandshakeTracer
180180
then WithEventType "Handshake" >$< tracer
181181
else nullTracer)
182-
$ maybe [] out <$> (tryReadTMVar $ nodeKernel.stakePools.ledgerPeersVar)
182+
$ maybe [] out <$> tryReadTMVar nodeKernel.stakePools.ledgerPeersVar
183183
where
184184
out :: LedgerPeerSnapshot AllLedgerPeers
185185
-> [(PoolStake, NonEmpty LedgerRelayAccessPoint)]

dmq-node/src/DMQ/NodeToNode.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
{-# LANGUAGE OverloadedStrings #-}
55
{-# LANGUAGE RankNTypes #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
7-
{-# LANGUAGE TypeOperators #-}
87

98
module DMQ.NodeToNode
109
( RemoteAddress

dmq-node/src/DMQ/Protocol/SigSubmission/Type.hs

Lines changed: 3 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
{-# LANGUAGE ScopedTypeVariables #-}
88
{-# LANGUAGE StandaloneDeriving #-}
99
{-# LANGUAGE TypeFamilies #-}
10-
{-# LANGUAGE TypeOperators #-}
1110
{-# LANGUAGE UndecidableInstances #-}
1211

1312
module DMQ.Protocol.SigSubmission.Type
@@ -32,7 +31,6 @@ module DMQ.Protocol.SigSubmission.Type
3231
) where
3332

3433
import Data.Aeson
35-
import Data.Bifunctor (first)
3634
import Data.ByteString (ByteString)
3735
import Data.ByteString.Base16 as BS.Base16
3836
import Data.ByteString.Base16.Lazy as LBS.Base16
@@ -42,13 +40,10 @@ import Data.Text.Encoding qualified as Text
4240
import Data.Time.Clock.POSIX (POSIXTime)
4341
import Data.Typeable
4442

45-
import Cardano.Crypto.DSIGN.Class (ContextDSIGN, DSIGNAlgorithm, VerKeyDSIGN)
46-
import Cardano.Crypto.DSIGN.Class qualified as DSIGN
47-
import Cardano.Crypto.KES.Class (KESAlgorithm (..), Signable)
43+
import Cardano.Crypto.DSIGN.Class (DSIGNAlgorithm, VerKeyDSIGN)
44+
import Cardano.Crypto.KES.Class (KESAlgorithm (..))
4845
import Cardano.KESAgent.KES.Crypto as KES
49-
import Cardano.KESAgent.KES.Evolution qualified as KES
50-
import Cardano.KESAgent.KES.OCert (KESPeriod (..), OCert (..), OCertSignable,
51-
validateOCert)
46+
import Cardano.KESAgent.KES.OCert (KESPeriod (..), OCert (..))
5247

5348
import Ouroboros.Network.Protocol.TxSubmission2.Type as SigSubmission hiding
5449
(TxSubmission2)

0 commit comments

Comments
 (0)