{-# LANGUAGE NamedFieldPuns #-}
module Ouroboros.Network.ConnectionManager.Test.Utils where
import Prelude hiding (read)
import Ouroboros.Network.ConnectionHandler (ConnectionHandlerTrace)
import Ouroboros.Network.ConnectionManager.Core as CM
import Ouroboros.Network.ConnectionManager.Types
import Test.QuickCheck (counterexample, property)
import Test.QuickCheck.Monoids (All (..))
verifyAbstractTransition :: AbstractTransition
-> Bool
verifyAbstractTransition :: Transition' AbstractState -> Bool
verifyAbstractTransition Transition { AbstractState
fromState :: AbstractState
fromState :: forall state. Transition' state -> state
fromState, AbstractState
toState :: AbstractState
toState :: forall state. Transition' state -> state
toState } =
case (AbstractState
fromState, AbstractState
toState) of
(AbstractState
TerminatedSt, AbstractState
ReservedOutboundSt) -> Bool
True
(AbstractState
UnknownConnectionSt, AbstractState
ReservedOutboundSt) -> Bool
True
(AbstractState
ReservedOutboundSt, UnnegotiatedSt Provenance
Outbound) -> Bool
True
(UnnegotiatedSt Provenance
Outbound, AbstractState
OutboundUniSt) -> Bool
True
(UnnegotiatedSt Provenance
Outbound, OutboundDupSt TimeoutExpired
Ticking) -> Bool
True
(UnnegotiatedSt Provenance
_, AbstractState
TerminatingSt) -> Bool
True
(AbstractState
OutboundUniSt, OutboundIdleSt DataFlow
Unidirectional) -> Bool
True
(OutboundDupSt TimeoutExpired
Ticking, OutboundDupSt TimeoutExpired
Expired) -> Bool
True
(OutboundDupSt TimeoutExpired
Expired, OutboundIdleSt DataFlow
Duplex) -> Bool
True
(OutboundIdleSt DataFlow
dataFlow, OutboundIdleSt DataFlow
dataFlow') -> DataFlow
dataFlow DataFlow -> DataFlow -> Bool
forall a. Eq a => a -> a -> Bool
== DataFlow
dataFlow'
(OutboundDupSt TimeoutExpired
Ticking, InboundIdleSt DataFlow
Duplex) -> Bool
True
(InboundIdleSt DataFlow
Duplex, OutboundDupSt TimeoutExpired
Ticking) -> Bool
True
(OutboundDupSt TimeoutExpired
Ticking, AbstractState
DuplexSt) -> Bool
True
(OutboundDupSt TimeoutExpired
Expired, AbstractState
DuplexSt) -> Bool
True
(OutboundDupSt TimeoutExpired
expired, OutboundDupSt TimeoutExpired
expired')
-> TimeoutExpired
expired TimeoutExpired -> TimeoutExpired -> Bool
forall a. Eq a => a -> a -> Bool
== TimeoutExpired
expired'
(InboundSt DataFlow
Duplex, AbstractState
DuplexSt) -> Bool
True
(AbstractState
DuplexSt, OutboundDupSt TimeoutExpired
Ticking) -> Bool
True
(AbstractState
DuplexSt, InboundSt DataFlow
Duplex) -> Bool
True
(AbstractState
TerminatedSt, UnnegotiatedSt Provenance
Inbound) -> Bool
True
(AbstractState
UnknownConnectionSt, UnnegotiatedSt Provenance
Inbound) -> Bool
True
(AbstractState
ReservedOutboundSt, UnnegotiatedSt Provenance
Inbound) -> Bool
True
(UnnegotiatedSt Provenance
Inbound, InboundIdleSt DataFlow
Duplex) -> Bool
True
(UnnegotiatedSt Provenance
Inbound, InboundIdleSt DataFlow
Unidirectional) -> Bool
True
(UnnegotiatedSt Provenance
Outbound, InboundIdleSt DataFlow
Duplex) -> Bool
True
(UnnegotiatedSt Provenance
Outbound, InboundIdleSt DataFlow
Unidirectional) -> Bool
True
(InboundIdleSt DataFlow
Duplex, InboundIdleSt DataFlow
Duplex) -> Bool
True
(InboundIdleSt DataFlow
Duplex, InboundSt DataFlow
Duplex) -> Bool
True
(InboundIdleSt DataFlow
Duplex, AbstractState
TerminatingSt) -> Bool
True
(InboundSt DataFlow
Duplex, InboundIdleSt DataFlow
Duplex) -> Bool
True
(InboundIdleSt DataFlow
Unidirectional, InboundSt DataFlow
Unidirectional) -> Bool
True
(InboundIdleSt DataFlow
Unidirectional, AbstractState
TerminatingSt) -> Bool
True
(InboundSt DataFlow
Unidirectional, InboundIdleSt DataFlow
Unidirectional) -> Bool
True
(OutboundIdleSt DataFlow
Duplex, InboundSt DataFlow
Duplex) -> Bool
True
(OutboundIdleSt DataFlow
_dataFlow, AbstractState
TerminatingSt) -> Bool
True
(UnnegotiatedSt Provenance
Outbound, UnnegotiatedSt Provenance
Inbound) -> Bool
True
(UnnegotiatedSt Provenance
Inbound, UnnegotiatedSt Provenance
Outbound) -> Bool
True
(InboundIdleSt DataFlow
Unidirectional, AbstractState
OutboundUniSt) -> Bool
True
(AbstractState
TerminatingSt, AbstractState
TerminatedSt) -> Bool
True
(AbstractState
TerminatedSt, AbstractState
TerminatedSt) -> Bool
False
(AbstractState
_, AbstractState
TerminatedSt) -> Bool
True
(AbstractState
UnknownConnectionSt, AbstractState
UnknownConnectionSt) -> Bool
False
(AbstractState
_, AbstractState
UnknownConnectionSt) -> Bool
True
(AbstractState
TerminatingSt, UnnegotiatedSt Provenance
Inbound) -> Bool
True
(AbstractState, AbstractState)
_ -> Bool
False
validTransitionMap :: AbstractTransition
-> (Int, String)
validTransitionMap :: Transition' AbstractState -> (Int, String)
validTransitionMap t :: Transition' AbstractState
t@Transition { AbstractState
fromState :: forall state. Transition' state -> state
fromState :: AbstractState
fromState, AbstractState
toState :: forall state. Transition' state -> state
toState :: AbstractState
toState } =
case (AbstractState
fromState, AbstractState
toState) of
(AbstractState
TerminatedSt , AbstractState
ReservedOutboundSt) -> (Int
01, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
UnknownConnectionSt , AbstractState
ReservedOutboundSt) -> (Int
02, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
ReservedOutboundSt , UnnegotiatedSt Provenance
Outbound) -> (Int
03, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Outbound , AbstractState
OutboundUniSt) -> (Int
04, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Outbound , OutboundDupSt TimeoutExpired
Ticking) -> (Int
05, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
OutboundUniSt , OutboundIdleSt DataFlow
Unidirectional) -> (Int
06, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundDupSt TimeoutExpired
Ticking , OutboundDupSt TimeoutExpired
Expired) -> (Int
07, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundDupSt TimeoutExpired
Expired , OutboundIdleSt DataFlow
Duplex) -> (Int
08, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundIdleSt DataFlow
dataFlow , OutboundIdleSt DataFlow
dataFlow')
| DataFlow
dataFlow DataFlow -> DataFlow -> Bool
forall a. Eq a => a -> a -> Bool
== DataFlow
dataFlow' -> (Int
09, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundDupSt TimeoutExpired
Ticking , InboundIdleSt DataFlow
Duplex) -> (Int
10, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Duplex , OutboundDupSt TimeoutExpired
Ticking) -> (Int
11, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundDupSt TimeoutExpired
Ticking , AbstractState
DuplexSt) -> (Int
12, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundDupSt TimeoutExpired
Expired , AbstractState
DuplexSt) -> (Int
13, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundDupSt TimeoutExpired
expired , OutboundDupSt TimeoutExpired
expired')
| TimeoutExpired
expired TimeoutExpired -> TimeoutExpired -> Bool
forall a. Eq a => a -> a -> Bool
== TimeoutExpired
expired' -> (Int
14, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundSt DataFlow
Duplex , AbstractState
DuplexSt) -> (Int
15, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
DuplexSt , OutboundDupSt TimeoutExpired
Ticking) -> (Int
16, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
DuplexSt , InboundSt DataFlow
Duplex) -> (Int
17, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
TerminatedSt , UnnegotiatedSt Provenance
Inbound) -> (Int
18, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
UnknownConnectionSt , UnnegotiatedSt Provenance
Inbound) -> (Int
19, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
ReservedOutboundSt , UnnegotiatedSt Provenance
Inbound) -> (Int
20, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Inbound , InboundIdleSt DataFlow
Duplex) -> (Int
21, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Inbound , InboundIdleSt DataFlow
Unidirectional) -> (Int
22, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Duplex , InboundIdleSt DataFlow
Duplex) -> (Int
23, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Duplex , InboundSt DataFlow
Duplex) -> (Int
24, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Duplex , AbstractState
TerminatingSt) -> (Int
25, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundSt DataFlow
Duplex , InboundIdleSt DataFlow
Duplex) -> (Int
26, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Unidirectional , InboundSt DataFlow
Unidirectional) -> (Int
27, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Unidirectional , AbstractState
TerminatingSt) -> (Int
28, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundSt DataFlow
Unidirectional , InboundIdleSt DataFlow
Unidirectional) -> (Int
29, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundIdleSt DataFlow
Duplex , InboundSt DataFlow
Duplex) -> (Int
30, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Outbound , UnnegotiatedSt Provenance
Inbound) -> (Int
36, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Inbound , UnnegotiatedSt Provenance
Outbound) -> (Int
37, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(OutboundIdleSt DataFlow
_dataFlow , AbstractState
TerminatingSt) -> (Int
38, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
TerminatingSt , AbstractState
TerminatedSt) -> (Int
39, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
_ , AbstractState
TerminatedSt) -> (Int
40, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
_ , AbstractState
UnknownConnectionSt) -> (Int
41, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState
TerminatingSt , UnnegotiatedSt Provenance
Inbound) -> (Int
42, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Outbound , InboundIdleSt DataFlow
Duplex) -> (Int
43, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(UnnegotiatedSt Provenance
Outbound , InboundIdleSt DataFlow
Unidirectional) -> (Int
44, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(InboundIdleSt DataFlow
Unidirectional , AbstractState
OutboundUniSt) -> (Int
45, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
(AbstractState, AbstractState)
_ -> (Int
99, Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
t)
verifyAbstractTransitionOrder :: Bool
-> [AbstractTransition]
-> All
verifyAbstractTransitionOrder :: Bool -> [Transition' AbstractState] -> All
verifyAbstractTransitionOrder Bool
_ [] = All
forall a. Monoid a => a
mempty
verifyAbstractTransitionOrder Bool
checkLast (Transition' AbstractState
h:[Transition' AbstractState]
t) = [Transition' AbstractState] -> Transition' AbstractState -> All
go [Transition' AbstractState]
t Transition' AbstractState
h
where
go :: [AbstractTransition] -> AbstractTransition -> All
go :: [Transition' AbstractState] -> Transition' AbstractState -> All
go [] (Transition AbstractState
_ AbstractState
UnknownConnectionSt) = All
forall a. Monoid a => a
mempty
go [] tr :: Transition' AbstractState
tr@(Transition AbstractState
_ AbstractState
_) =
Property -> All
forall p. Testable p => p -> All
All
(Property -> All) -> Property -> All
forall a b. (a -> b) -> a -> b
$ String -> Property -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample
(String
"\nUnexpected last transition: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
tr)
(Bool -> Property
forall prop. Testable prop => prop -> Property
property (Bool -> Bool
not Bool
checkLast))
go (next :: Transition' AbstractState
next@(Transition AbstractState
nextFromState AbstractState
_) : [Transition' AbstractState]
ts)
curr :: Transition' AbstractState
curr@(Transition AbstractState
_ AbstractState
currToState) =
Property -> All
forall p. Testable p => p -> All
All
(String -> Property -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample
(String
"\nUnexpected transition order!\nWent from: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
curr String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nto: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Transition' AbstractState -> String
forall a. Show a => a -> String
show Transition' AbstractState
next)
(Bool -> Property
forall prop. Testable prop => prop -> Property
property (AbstractState
currToState AbstractState -> AbstractState -> Bool
forall a. Eq a => a -> a -> Bool
== AbstractState
nextFromState)))
All -> All -> All
forall a. Semigroup a => a -> a -> a
<> [Transition' AbstractState] -> Transition' AbstractState -> All
go [Transition' AbstractState]
ts Transition' AbstractState
next
allValidTransitionsNames :: [String]
allValidTransitionsNames :: [String]
allValidTransitionsNames =
(Transition' AbstractState -> String)
-> [Transition' AbstractState] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Transition' AbstractState -> String
forall a. Show a => a -> String
show
[ AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
UnknownConnectionSt AbstractState
ReservedOutboundSt
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
ReservedOutboundSt (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound) (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound) (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound) AbstractState
OutboundUniSt
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound) (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Ticking)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
OutboundUniSt (DataFlow -> AbstractState
OutboundIdleSt DataFlow
Unidirectional)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Ticking) (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Expired)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Ticking) (DataFlow -> AbstractState
InboundIdleSt DataFlow
Duplex)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (DataFlow -> AbstractState
InboundIdleSt DataFlow
Duplex) (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Ticking)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Ticking) AbstractState
DuplexSt
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (DataFlow -> AbstractState
InboundSt DataFlow
Duplex) AbstractState
DuplexSt
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
DuplexSt (TimeoutExpired -> AbstractState
OutboundDupSt TimeoutExpired
Ticking)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
DuplexSt (DataFlow -> AbstractState
InboundSt DataFlow
Duplex)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
UnknownConnectionSt (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
ReservedOutboundSt (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound) (DataFlow -> AbstractState
InboundIdleSt DataFlow
Duplex)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound) (DataFlow -> AbstractState
InboundIdleSt DataFlow
Unidirectional)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (DataFlow -> AbstractState
InboundIdleSt DataFlow
Duplex) (DataFlow -> AbstractState
InboundSt DataFlow
Duplex)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound) (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Inbound) (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition AbstractState
TerminatingSt AbstractState
TerminatedSt
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound) (DataFlow -> AbstractState
InboundIdleSt DataFlow
Unidirectional)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (Provenance -> AbstractState
UnnegotiatedSt Provenance
Outbound) (DataFlow -> AbstractState
InboundIdleSt DataFlow
Duplex)
, AbstractState -> AbstractState -> Transition' AbstractState
forall state. state -> state -> Transition' state
Transition (DataFlow -> AbstractState
InboundIdleSt DataFlow
Unidirectional) AbstractState
OutboundUniSt
]
abstractStateIsFinalTransition :: Transition' AbstractState -> Bool
abstractStateIsFinalTransition :: Transition' AbstractState -> Bool
abstractStateIsFinalTransition (Transition AbstractState
_ AbstractState
UnknownConnectionSt) = Bool
True
abstractStateIsFinalTransition Transition' AbstractState
_ = Bool
False
abstractStateIsFinalTransitionTVarTracing :: Transition' AbstractState -> Bool
abstractStateIsFinalTransitionTVarTracing :: Transition' AbstractState -> Bool
abstractStateIsFinalTransitionTVarTracing (Transition AbstractState
_ AbstractState
UnknownConnectionSt) = Bool
True
abstractStateIsFinalTransitionTVarTracing Transition' AbstractState
_ = Bool
False
connectionManagerTraceMap
:: CM.Trace
ntnAddr
(ConnectionHandlerTrace ntnVersion ntnVersionData)
-> String
connectionManagerTraceMap :: forall ntnAddr ntnVersion ntnVersionData.
Trace ntnAddr (ConnectionHandlerTrace ntnVersion ntnVersionData)
-> String
connectionManagerTraceMap (TrIncludeConnection Provenance
p ntnAddr
_) =
String
"TrIncludeConnection " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Provenance -> String
forall a. Show a => a -> String
show Provenance
p
connectionManagerTraceMap (TrReleaseConnection Provenance
p ntnAddr
_) =
String
"TrUnregisterConnection " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Provenance -> String
forall a. Show a => a -> String
show Provenance
p
connectionManagerTraceMap (TrConnect Maybe ntnAddr
_ ntnAddr
_) =
String
"TrConnect"
connectionManagerTraceMap (TrConnectError Maybe ntnAddr
_ ntnAddr
_ SomeException
_) =
String
"TrConnectError"
connectionManagerTraceMap (TrTerminatingConnection Provenance
p ConnectionId ntnAddr
_) =
String
"TrTerminatingConnection " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Provenance -> String
forall a. Show a => a -> String
show Provenance
p
connectionManagerTraceMap (TrTerminatedConnection Provenance
p ntnAddr
_) =
String
"TrTerminatedConnection " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Provenance -> String
forall a. Show a => a -> String
show Provenance
p
connectionManagerTraceMap (TrConnectionHandler ConnectionId ntnAddr
_ ConnectionHandlerTrace ntnVersion ntnVersionData
_) =
String
"TrConnectionHandler"
connectionManagerTraceMap Trace ntnAddr (ConnectionHandlerTrace ntnVersion ntnVersionData)
TrShutdown =
String
"TrShutdown"
connectionManagerTraceMap (TrConnectionExists Provenance
p ntnAddr
_ AbstractState
as) =
String
"TrConnectionExists " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Provenance -> String
forall a. Show a => a -> String
show Provenance
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ AbstractState -> String
forall a. Show a => a -> String
show AbstractState
as
connectionManagerTraceMap (TrForbiddenConnection ConnectionId ntnAddr
_) =
String
"TrForbiddenConnection"
connectionManagerTraceMap (TrConnectionFailure ConnectionId ntnAddr
_) =
String
"TrConnectionFailure"
connectionManagerTraceMap (TrConnectionNotFound Provenance
p ntnAddr
_) =
String
"TrConnectionNotFound " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Provenance -> String
forall a. Show a => a -> String
show Provenance
p
connectionManagerTraceMap (TrForbiddenOperation ntnAddr
_ AbstractState
as) =
String
"TrForbiddenOperation" String -> String -> String
forall a. [a] -> [a] -> [a]
++ AbstractState -> String
forall a. Show a => a -> String
show AbstractState
as
connectionManagerTraceMap (TrPruneConnections Set ntnAddr
_ Int
_ Set ntnAddr
_) =
String
"TrPruneConnections"
connectionManagerTraceMap (TrConnectionCleanup ConnectionId ntnAddr
_) =
String
"TrConnectionCleanup"
connectionManagerTraceMap (TrConnectionTimeWait ConnectionId ntnAddr
_) =
String
"TrConnectionTimeWait"
connectionManagerTraceMap (TrConnectionTimeWaitDone ConnectionId ntnAddr
_) =
String
"TrConnectionTimeWaitDone"
connectionManagerTraceMap (TrConnectionManagerCounters ConnectionManagerCounters
_) =
String
"TrConnectionManagerCounters"
connectionManagerTraceMap (TrState Map ntnAddr AbstractState
_) =
String
"TrState"
connectionManagerTraceMap (TrUnexpectedlyFalseAssertion AssertionLocation ntnAddr
_) =
String
"TrUnexpectedlyFalseAssertion"