Skip to content

Commit

Permalink
Merge #3728
Browse files Browse the repository at this point in the history
3728: Coverage tests for the diffusion test suite r=bolt12 a=bolt12



Co-authored-by: Armando Santos <[email protected]>
  • Loading branch information
iohk-bors[bot] and bolt12 authored May 19, 2022
2 parents 85b1db3 + 4e31bf4 commit dfa2697
Show file tree
Hide file tree
Showing 4 changed files with 464 additions and 18 deletions.
52 changes: 52 additions & 0 deletions ouroboros-network-framework/testlib/TestLib/ConnectionManager.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module TestLib.ConnectionManager where

import Prelude hiding (read)

import Ouroboros.Network.ConnectionHandler (ConnectionHandlerTrace)
import Ouroboros.Network.ConnectionManager.Types

import Test.QuickCheck (counterexample, property)
Expand Down Expand Up @@ -252,3 +253,54 @@ allValidTransitionsNames =
abstractStateIsFinalTransition :: Transition' AbstractState -> Bool
abstractStateIsFinalTransition (Transition _ UnknownConnectionSt) = True
abstractStateIsFinalTransition _ = False


connectionManagerTraceMap
:: ConnectionManagerTrace
ntnAddr
(ConnectionHandlerTrace ntnVersion ntnVersionData)
-> String
connectionManagerTraceMap (TrIncludeConnection p _) =
"TrIncludeConnection " ++ show p
connectionManagerTraceMap (TrUnregisterConnection p _) =
"TrUnregisterConnection " ++ show p
connectionManagerTraceMap (TrConnect _ _) =
"TrConnect"
connectionManagerTraceMap (TrConnectError _ _ _) =
"TrConnectError"
connectionManagerTraceMap (TrTerminatingConnection p _) =
"TrTerminatingConnection " ++ show p
connectionManagerTraceMap (TrTerminatedConnection p _) =
"TrTerminatedConnection " ++ show p
connectionManagerTraceMap (TrConnectionHandler _ _) =
"TrConnectionHandler"
connectionManagerTraceMap TrShutdown =
"TrShutdown"
connectionManagerTraceMap (TrConnectionExists p _ as) =
"TrConnectionExists " ++ show p ++ " " ++ show as
connectionManagerTraceMap (TrForbiddenConnection _) =
"TrForbiddenConnection"
connectionManagerTraceMap (TrImpossibleConnection _) =
"TrImpossibleConnection"
connectionManagerTraceMap (TrConnectionFailure _) =
"TrConnectionFailure"
connectionManagerTraceMap (TrConnectionNotFound p _) =
"TrConnectionNotFound " ++ show p
connectionManagerTraceMap (TrForbiddenOperation _ as) =
"TrForbiddenOperation" ++ show as
connectionManagerTraceMap (TrPruneConnections _ _ _) =
"TrPruneConnections"
connectionManagerTraceMap (TrConnectionCleanup _) =
"TrConnectionCleanup"
connectionManagerTraceMap (TrConnectionTimeWait _) =
"TrConnectionTimeWait"
connectionManagerTraceMap (TrConnectionTimeWaitDone _) =
"TrConnectionTimeWaitDone"
connectionManagerTraceMap (TrConnectionManagerCounters _) =
"TrConnectionManagerCounters"
connectionManagerTraceMap (TrState _) =
"TrState"
connectionManagerTraceMap (TrUnknownConnection _) =
"TrUnknownConnection"
connectionManagerTraceMap (TrUnexpectedlyFalseAssertion _) =
"TrUnexpectedlyFalseAssertion"
52 changes: 50 additions & 2 deletions ouroboros-network-framework/testlib/TestLib/InboundGovernor.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,10 @@ module TestLib.InboundGovernor where
import Test.QuickCheck

import Ouroboros.Network.ConnectionManager.Types
import Ouroboros.Network.InboundGovernor (RemoteSt (..))
import Ouroboros.Network.Server2 (RemoteTransition)
import Ouroboros.Network.InboundGovernor (InboundGovernorTrace (..),
RemoteSt (..))
import qualified Ouroboros.Network.InboundGovernor as IG
import Ouroboros.Network.Server2 (RemoteTransition, ServerTrace (..))

import TestLib.Utils

Expand Down Expand Up @@ -166,3 +168,49 @@ verifyRemoteTransitionOrder checkLast (h:t) = go t h
remoteStrIsFinalTransition :: Transition' (Maybe RemoteSt) -> Bool
remoteStrIsFinalTransition (Transition _ Nothing) = True
remoteStrIsFinalTransition _ = False

inboundGovernorTraceMap :: InboundGovernorTrace ntnAddr -> String
inboundGovernorTraceMap (TrNewConnection p _) =
"TrNewConnection " ++ show p
inboundGovernorTraceMap (TrResponderRestarted _ mpn) =
"TrResponderRestarted " ++ show mpn
inboundGovernorTraceMap (TrResponderStartFailure _ mpn se) =
"TrResponderStartFailure " ++ show mpn ++ " " ++ show se
inboundGovernorTraceMap (TrResponderErrored _ mpn se) =
"TrResponderErrored " ++ show mpn ++ " " ++ show se
inboundGovernorTraceMap (TrResponderStarted _ mpn) =
"TrResponderStarted " ++ show mpn
inboundGovernorTraceMap (TrResponderTerminated _ mpn) =
"TrResponderTerminated " ++ show mpn
inboundGovernorTraceMap (TrPromotedToWarmRemote _ ora) =
"TrPromotedToWarmRemote " ++ show ora
inboundGovernorTraceMap (TrPromotedToHotRemote _) =
"TrPromotedToHotRemote"
inboundGovernorTraceMap (TrDemotedToWarmRemote _) =
"TrDemotedToWarmRemote"
inboundGovernorTraceMap (TrDemotedToColdRemote _ ora) =
"TrDemotedToColdRemote " ++ show ora
inboundGovernorTraceMap (TrWaitIdleRemote _ ora) =
"TrWaitIdleRemote " ++ show ora
inboundGovernorTraceMap (TrMuxCleanExit _) =
"TrMuxCleanExit"
inboundGovernorTraceMap (TrMuxErrored _ se) =
"TrMuxErrored " ++ show se
inboundGovernorTraceMap (TrInboundGovernorCounters _) =
"TrInboundGovernorCounters"
inboundGovernorTraceMap (TrRemoteState _) =
"TrRemoteState"
inboundGovernorTraceMap (IG.TrUnexpectedlyFalseAssertion _) =
"TrUnexpectedlyFalseAssertion"
inboundGovernorTraceMap (TrInboundGovernorError se) =
"TrInboundGovernorError " ++ show se


serverTraceMap :: Show ntnAddr => ServerTrace ntnAddr -> String
serverTraceMap (TrAcceptConnection _) = "TrAcceptConnection"
serverTraceMap st@(TrAcceptError _) = show st
serverTraceMap st@(TrAcceptPolicyTrace _) = show st
serverTraceMap (TrServerStarted _) = "TrServerStarted"
serverTraceMap st@TrServerStopped = show st
serverTraceMap st@(TrServerError _) = show st

Loading

0 comments on commit dfa2697

Please sign in to comment.