{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Network.Protocol.LocalTxMonitor.Test (tests) where
import Codec.Serialise (Serialise)
import Codec.Serialise qualified as S
import Data.ByteString.Lazy (ByteString)
import Control.Monad.Class.MonadAsync
import Control.Monad.Class.MonadST
import Control.Monad.Class.MonadThrow
import Control.Monad.IOSim
import Control.Monad.ST qualified as ST
import Control.Tracer (nullTracer)
import Network.TypedProtocol.Codec
import Network.TypedProtocol.Proofs
import Ouroboros.Network.Block (SlotNo)
import Ouroboros.Network.Channel
import Ouroboros.Network.Driver.Simple (runConnectedPeers)
import Ouroboros.Network.Util.ShowProxy
import Ouroboros.Network.Protocol.LocalTxMonitor.Client
import Ouroboros.Network.Protocol.LocalTxMonitor.Codec
import Ouroboros.Network.Protocol.LocalTxMonitor.Direct
import Ouroboros.Network.Protocol.LocalTxMonitor.Examples
import Ouroboros.Network.Protocol.LocalTxMonitor.Server
import Ouroboros.Network.Protocol.LocalTxMonitor.Type
import Test.ChainGenerators ()
import Test.Ouroboros.Network.Testing.Utils (prop_codec_cborM,
prop_codec_valid_cbor_encoding, splits2, splits3)
import Test.QuickCheck hiding (Result)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.QuickCheck (testProperty)
tests :: TestTree
tests :: TestTree
tests = TestName -> [TestTree] -> TestTree
testGroup TestName
"Ouroboros.Network.Protocol"
[ TestName -> [TestTree] -> TestTree
testGroup TestName
"LocalTxMonitor"
[ TestName
-> (AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"codecM" AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codecM_LocalTxMonitor
, TestName
-> (AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"codec 2-splits" ((ByteString -> [[ByteString]])
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codec_splitsM_LocalTxMonitor ByteString -> [[ByteString]]
splits2)
, TestName
-> (AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"codec 3-splits" ((ByteString -> [[ByteString]])
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codec_splitsM_LocalTxMonitor ByteString -> [[ByteString]]
splits3)
, TestName
-> (AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"codec cborM" AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codec_cborM_LocalTxMonitor
, TestName
-> (AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Property)
-> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"codec valid cbor encoding" AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Property
prop_codec_valid_cbor_encoding_LocalTxMonitor
, TestName -> ((SlotNo, [Tx]) -> Property) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"direct" (SlotNo, [Tx]) -> Property
prop_direct
, TestName -> ((SlotNo, [Tx]) -> Bool) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"connect" (SlotNo, [Tx]) -> Bool
prop_connect
, TestName -> ((SlotNo, [Tx]) -> Bool) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"channel ST" (SlotNo, [Tx]) -> Bool
prop_channel_ST
, TestName -> ((SlotNo, [Tx]) -> Property) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"channel IO" (SlotNo, [Tx]) -> Property
prop_channel_IO
, TestName -> ((SlotNo, [Tx]) -> Property) -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"pipe IO" (SlotNo, [Tx]) -> Property
prop_pipe_IO
]
]
codec ::
( MonadST m
)
=> Codec (LocalTxMonitor TxId Tx SlotNo) S.DeserialiseFailure m ByteString
codec :: forall (m :: * -> *).
MonadST m =>
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
codec = (TxId -> Encoding)
-> (forall s. Decoder s TxId)
-> (Tx -> Encoding)
-> (forall s. Decoder s Tx)
-> (SlotNo -> Encoding)
-> (forall s. Decoder s SlotNo)
-> Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
forall txid tx slot (m :: * -> *) ptcl.
(MonadST m, ptcl ~ LocalTxMonitor txid tx slot) =>
(txid -> Encoding)
-> (forall s. Decoder s txid)
-> (tx -> Encoding)
-> (forall s. Decoder s tx)
-> (slot -> Encoding)
-> (forall s. Decoder s slot)
-> Codec
(LocalTxMonitor txid tx slot) DeserialiseFailure m ByteString
codecLocalTxMonitor
TxId -> Encoding
forall a. Serialise a => a -> Encoding
S.encode Decoder s TxId
forall s. Decoder s TxId
forall a s. Serialise a => Decoder s a
S.decode
Tx -> Encoding
forall a. Serialise a => a -> Encoding
S.encode Decoder s Tx
forall s. Decoder s Tx
forall a s. Serialise a => Decoder s a
S.decode
SlotNo -> Encoding
forall a. Serialise a => a -> Encoding
S.encode Decoder s SlotNo
forall s. Decoder s SlotNo
forall a s. Serialise a => Decoder s a
S.decode
prop_codecM_LocalTxMonitor ::
AnyMessage (LocalTxMonitor TxId Tx SlotNo)
-> Bool
prop_codecM_LocalTxMonitor :: AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codecM_LocalTxMonitor AnyMessage (LocalTxMonitor TxId Tx SlotNo)
msg =
(forall s. ST s Bool) -> Bool
forall a. (forall s. ST s a) -> a
ST.runST ((forall s. ST s Bool) -> Bool) -> (forall s. ST s Bool) -> Bool
forall a b. (a -> b) -> a -> b
$ Codec
(LocalTxMonitor TxId Tx SlotNo)
DeserialiseFailure
(ST s)
ByteString
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> ST s Bool
forall ps failure (m :: * -> *) bytes.
(Monad m, Eq (AnyMessage ps)) =>
Codec ps failure m bytes -> AnyMessage ps -> m Bool
prop_codecM Codec
(LocalTxMonitor TxId Tx SlotNo)
DeserialiseFailure
(ST s)
ByteString
forall (m :: * -> *).
MonadST m =>
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
codec AnyMessage (LocalTxMonitor TxId Tx SlotNo)
msg
prop_codec_cborM_LocalTxMonitor ::
AnyMessage (LocalTxMonitor TxId Tx SlotNo)
-> Bool
prop_codec_cborM_LocalTxMonitor :: AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codec_cborM_LocalTxMonitor AnyMessage (LocalTxMonitor TxId Tx SlotNo)
msg =
(forall s. ST s Bool) -> Bool
forall a. (forall s. ST s a) -> a
ST.runST ((forall s. ST s Bool) -> Bool) -> (forall s. ST s Bool) -> Bool
forall a b. (a -> b) -> a -> b
$ Codec
(LocalTxMonitor TxId Tx SlotNo)
DeserialiseFailure
(ST s)
ByteString
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> ST s Bool
forall ps (m :: * -> *).
Monad m =>
Codec ps DeserialiseFailure m ByteString -> AnyMessage ps -> m Bool
prop_codec_cborM Codec
(LocalTxMonitor TxId Tx SlotNo)
DeserialiseFailure
(ST s)
ByteString
forall (m :: * -> *).
MonadST m =>
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
codec AnyMessage (LocalTxMonitor TxId Tx SlotNo)
msg
prop_codec_splitsM_LocalTxMonitor ::
(ByteString -> [[ByteString]])
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo)
-> Bool
prop_codec_splitsM_LocalTxMonitor :: (ByteString -> [[ByteString]])
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Bool
prop_codec_splitsM_LocalTxMonitor ByteString -> [[ByteString]]
splitN AnyMessage (LocalTxMonitor TxId Tx SlotNo)
msg =
(forall s. ST s Bool) -> Bool
forall a. (forall s. ST s a) -> a
ST.runST ((forall s. ST s Bool) -> Bool) -> (forall s. ST s Bool) -> Bool
forall a b. (a -> b) -> a -> b
$ (ByteString -> [[ByteString]])
-> Codec
(LocalTxMonitor TxId Tx SlotNo)
DeserialiseFailure
(ST s)
ByteString
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo)
-> ST s Bool
forall ps failure (m :: * -> *) bytes.
(Monad m, Eq (AnyMessage ps)) =>
(bytes -> [[bytes]])
-> Codec ps failure m bytes -> AnyMessage ps -> m Bool
prop_codec_splitsM ByteString -> [[ByteString]]
splitN Codec
(LocalTxMonitor TxId Tx SlotNo)
DeserialiseFailure
(ST s)
ByteString
forall (m :: * -> *).
MonadST m =>
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
codec AnyMessage (LocalTxMonitor TxId Tx SlotNo)
msg
prop_codec_valid_cbor_encoding_LocalTxMonitor ::
AnyMessage (LocalTxMonitor TxId Tx SlotNo)
-> Property
prop_codec_valid_cbor_encoding_LocalTxMonitor :: AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Property
prop_codec_valid_cbor_encoding_LocalTxMonitor =
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure IO ByteString
-> AnyMessage (LocalTxMonitor TxId Tx SlotNo) -> Property
forall ps.
Codec ps DeserialiseFailure IO ByteString
-> AnyMessage ps -> Property
prop_codec_valid_cbor_encoding Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure IO ByteString
forall (m :: * -> *).
MonadST m =>
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
codec
prop_direct ::
(SlotNo, [Tx])
-> Property
prop_direct :: (SlotNo, [Tx]) -> Property
prop_direct (SlotNo
slot, [Tx]
txs) =
let (([(Tx, Bool)]
txs', MempoolSizeAndCapacity
sz), ()) = (forall s. IOSim s (([(Tx, Bool)], MempoolSizeAndCapacity), ()))
-> (([(Tx, Bool)], MempoolSizeAndCapacity), ())
forall a. (forall s. IOSim s a) -> a
runSimOrThrow (LocalTxMonitorClient
TxId Tx SlotNo (IOSim s) ([(Tx, Bool)], MempoolSizeAndCapacity)
-> LocalTxMonitorServer TxId Tx SlotNo (IOSim s) ()
-> IOSim s (([(Tx, Bool)], MempoolSizeAndCapacity), ())
forall (m :: * -> *) txid tx slot a b.
Monad m =>
LocalTxMonitorClient txid tx slot m a
-> LocalTxMonitorServer txid tx slot m b -> m (a, b)
direct
((Tx -> TxId)
-> LocalTxMonitorClient
TxId Tx SlotNo (IOSim s) ([(Tx, Bool)], MempoolSizeAndCapacity)
forall txid tx slot (m :: * -> *).
Applicative m =>
(tx -> txid)
-> LocalTxMonitorClient
txid tx slot m ([(tx, Bool)], MempoolSizeAndCapacity)
localTxMonitorClient Tx -> TxId
txId)
((Tx -> TxId)
-> (SlotNo, [Tx])
-> LocalTxMonitorServer TxId Tx SlotNo (IOSim s) ()
forall txid tx slot (m :: * -> *).
(Applicative m, Eq txid) =>
(tx -> txid)
-> (slot, [tx]) -> LocalTxMonitorServer txid tx slot m ()
localTxMonitorServer Tx -> TxId
txId (SlotNo
slot, [Tx]
txs))
)
in
( [(Tx, Bool)]
txs'
, MempoolSizeAndCapacity -> Word32
numberOfTxs MempoolSizeAndCapacity
sz
)
([(Tx, Bool)], Word32) -> ([(Tx, Bool)], Word32) -> Property
forall a. (Eq a, Show a) => a -> a -> Property
===
( [ (Tx
tx, Bool
True) | Tx
tx <- [Tx]
txs ]
, Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Tx] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Tx]
txs
)
prop_connect :: (SlotNo, [Tx]) -> Bool
prop_connect :: (SlotNo, [Tx]) -> Bool
prop_connect (SlotNo
slot, [Tx]
txs) =
case (forall s.
IOSim
s
(([(Tx, Bool)], MempoolSizeAndCapacity), (),
TerminalStates (LocalTxMonitor TxId Tx SlotNo)))
-> (([(Tx, Bool)], MempoolSizeAndCapacity), (),
TerminalStates (LocalTxMonitor TxId Tx SlotNo))
forall a. (forall s. IOSim s a) -> a
runSimOrThrow
(Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
(IOSim s)
([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
(FlipAgency 'AsClient)
'NonPipelined
'StIdle
(IOSim s)
()
-> IOSim
s
(([(Tx, Bool)], MempoolSizeAndCapacity), (),
TerminalStates (LocalTxMonitor TxId Tx SlotNo))
forall ps (pr :: PeerRole) (initSt :: ps) (m :: * -> *) a b.
(Monad m, SingI pr) =>
Peer ps pr 'NonPipelined initSt m a
-> Peer ps (FlipAgency pr) 'NonPipelined initSt m b
-> m (a, b, TerminalStates ps)
connect
(LocalTxMonitorClient
TxId Tx SlotNo (IOSim s) ([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
(IOSim s)
([(Tx, Bool)], MempoolSizeAndCapacity)
forall txid tx slot (m :: * -> *) a.
Monad m =>
LocalTxMonitorClient txid tx slot m a
-> Client (LocalTxMonitor txid tx slot) 'NonPipelined 'StIdle m a
localTxMonitorClientPeer (LocalTxMonitorClient
TxId Tx SlotNo (IOSim s) ([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
(IOSim s)
([(Tx, Bool)], MempoolSizeAndCapacity))
-> LocalTxMonitorClient
TxId Tx SlotNo (IOSim s) ([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
(IOSim s)
([(Tx, Bool)], MempoolSizeAndCapacity)
forall a b. (a -> b) -> a -> b
$
(Tx -> TxId)
-> LocalTxMonitorClient
TxId Tx SlotNo (IOSim s) ([(Tx, Bool)], MempoolSizeAndCapacity)
forall txid tx slot (m :: * -> *).
Applicative m =>
(tx -> txid)
-> LocalTxMonitorClient
txid tx slot m ([(tx, Bool)], MempoolSizeAndCapacity)
localTxMonitorClient Tx -> TxId
txId)
(LocalTxMonitorServer TxId Tx SlotNo (IOSim s) ()
-> Server
(LocalTxMonitor TxId Tx SlotNo) 'NonPipelined 'StIdle (IOSim s) ()
forall txid tx slot (m :: * -> *) a.
Monad m =>
LocalTxMonitorServer txid tx slot m a
-> Server (LocalTxMonitor txid tx slot) 'NonPipelined 'StIdle m a
localTxMonitorServerPeer (LocalTxMonitorServer TxId Tx SlotNo (IOSim s) ()
-> Server
(LocalTxMonitor TxId Tx SlotNo) 'NonPipelined 'StIdle (IOSim s) ())
-> LocalTxMonitorServer TxId Tx SlotNo (IOSim s) ()
-> Server
(LocalTxMonitor TxId Tx SlotNo) 'NonPipelined 'StIdle (IOSim s) ()
forall a b. (a -> b) -> a -> b
$
(Tx -> TxId)
-> (SlotNo, [Tx])
-> LocalTxMonitorServer TxId Tx SlotNo (IOSim s) ()
forall txid tx slot (m :: * -> *).
(Applicative m, Eq txid) =>
(tx -> txid)
-> (slot, [tx]) -> LocalTxMonitorServer txid tx slot m ()
localTxMonitorServer Tx -> TxId
txId (SlotNo
slot, [Tx]
txs))) of
(([(Tx, Bool)]
txs', MempoolSizeAndCapacity
_), (), TerminalStates SingLocalTxMonitor st
StateToken st
SingDone SingLocalTxMonitor 'StDone
StateToken st
SingDone) ->
[(Tx, Bool)]
txs' [(Tx, Bool)] -> [(Tx, Bool)] -> Bool
forall a. Eq a => a -> a -> Bool
== [ (Tx
tx, Bool
True) | Tx
tx <- [Tx]
txs ]
prop_channel :: (MonadAsync m, MonadCatch m, MonadST m)
=> m (Channel m ByteString, Channel m ByteString)
-> (SlotNo, [Tx])
-> m Bool
prop_channel :: forall (m :: * -> *).
(MonadAsync m, MonadCatch m, MonadST m) =>
m (Channel m ByteString, Channel m ByteString)
-> (SlotNo, [Tx]) -> m Bool
prop_channel m (Channel m ByteString, Channel m ByteString)
createChannels (SlotNo
slot, [Tx]
txs) = do
((txs', _), ()) <- m (Channel m ByteString, Channel m ByteString)
-> Tracer m (Role, TraceSendRecv (LocalTxMonitor TxId Tx SlotNo))
-> Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
m
([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
(FlipAgency 'AsClient)
'NonPipelined
'StIdle
m
()
-> m (([(Tx, Bool)], MempoolSizeAndCapacity), ())
forall ps (pr :: PeerRole) (st :: ps) failure bytes (m :: * -> *) a
b.
(MonadAsync m, MonadThrow m, ShowProxy ps,
forall (st' :: ps) stok. (stok ~ StateToken st') => Show stok,
Show failure) =>
m (Channel m bytes, Channel m bytes)
-> Tracer m (Role, TraceSendRecv ps)
-> Codec ps failure m bytes
-> Peer ps pr 'NonPipelined st m a
-> Peer ps (FlipAgency pr) 'NonPipelined st m b
-> m (a, b)
runConnectedPeers m (Channel m ByteString, Channel m ByteString)
createChannels Tracer m (Role, TraceSendRecv (LocalTxMonitor TxId Tx SlotNo))
forall (m :: * -> *) a. Applicative m => Tracer m a
nullTracer Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
forall (m :: * -> *).
MonadST m =>
Codec
(LocalTxMonitor TxId Tx SlotNo) DeserialiseFailure m ByteString
codec
(LocalTxMonitorClient
TxId Tx SlotNo m ([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
m
([(Tx, Bool)], MempoolSizeAndCapacity)
forall txid tx slot (m :: * -> *) a.
Monad m =>
LocalTxMonitorClient txid tx slot m a
-> Client (LocalTxMonitor txid tx slot) 'NonPipelined 'StIdle m a
localTxMonitorClientPeer (LocalTxMonitorClient
TxId Tx SlotNo m ([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
m
([(Tx, Bool)], MempoolSizeAndCapacity))
-> LocalTxMonitorClient
TxId Tx SlotNo m ([(Tx, Bool)], MempoolSizeAndCapacity)
-> Peer
(LocalTxMonitor TxId Tx SlotNo)
'AsClient
'NonPipelined
'StIdle
m
([(Tx, Bool)], MempoolSizeAndCapacity)
forall a b. (a -> b) -> a -> b
$
(Tx -> TxId)
-> LocalTxMonitorClient
TxId Tx SlotNo m ([(Tx, Bool)], MempoolSizeAndCapacity)
forall txid tx slot (m :: * -> *).
Applicative m =>
(tx -> txid)
-> LocalTxMonitorClient
txid tx slot m ([(tx, Bool)], MempoolSizeAndCapacity)
localTxMonitorClient Tx -> TxId
txId)
(LocalTxMonitorServer TxId Tx SlotNo m ()
-> Server
(LocalTxMonitor TxId Tx SlotNo) 'NonPipelined 'StIdle m ()
forall txid tx slot (m :: * -> *) a.
Monad m =>
LocalTxMonitorServer txid tx slot m a
-> Server (LocalTxMonitor txid tx slot) 'NonPipelined 'StIdle m a
localTxMonitorServerPeer (LocalTxMonitorServer TxId Tx SlotNo m ()
-> Server
(LocalTxMonitor TxId Tx SlotNo) 'NonPipelined 'StIdle m ())
-> LocalTxMonitorServer TxId Tx SlotNo m ()
-> Server
(LocalTxMonitor TxId Tx SlotNo) 'NonPipelined 'StIdle m ()
forall a b. (a -> b) -> a -> b
$
(Tx -> TxId)
-> (SlotNo, [Tx]) -> LocalTxMonitorServer TxId Tx SlotNo m ()
forall txid tx slot (m :: * -> *).
(Applicative m, Eq txid) =>
(tx -> txid)
-> (slot, [tx]) -> LocalTxMonitorServer txid tx slot m ()
localTxMonitorServer Tx -> TxId
txId (SlotNo
slot, [Tx]
txs))
pure (txs' == [ (tx, True) | tx <- txs ])
prop_channel_ST :: (SlotNo, [Tx]) -> Bool
prop_channel_ST :: (SlotNo, [Tx]) -> Bool
prop_channel_ST (SlotNo, [Tx])
txs =
(forall s. IOSim s Bool) -> Bool
forall a. (forall s. IOSim s a) -> a
runSimOrThrow
(IOSim
s (Channel (IOSim s) ByteString, Channel (IOSim s) ByteString)
-> (SlotNo, [Tx]) -> IOSim s Bool
forall (m :: * -> *).
(MonadAsync m, MonadCatch m, MonadST m) =>
m (Channel m ByteString, Channel m ByteString)
-> (SlotNo, [Tx]) -> m Bool
prop_channel IOSim
s (Channel (IOSim s) ByteString, Channel (IOSim s) ByteString)
forall (m :: * -> *) a. MonadSTM m => m (Channel m a, Channel m a)
createConnectedChannels (SlotNo, [Tx])
txs)
prop_channel_IO :: (SlotNo, [Tx]) -> Property
prop_channel_IO :: (SlotNo, [Tx]) -> Property
prop_channel_IO (SlotNo, [Tx])
txs =
IO Bool -> Property
forall prop. Testable prop => IO prop -> Property
ioProperty (IO (Channel IO ByteString, Channel IO ByteString)
-> (SlotNo, [Tx]) -> IO Bool
forall (m :: * -> *).
(MonadAsync m, MonadCatch m, MonadST m) =>
m (Channel m ByteString, Channel m ByteString)
-> (SlotNo, [Tx]) -> m Bool
prop_channel IO (Channel IO ByteString, Channel IO ByteString)
forall (m :: * -> *) a. MonadSTM m => m (Channel m a, Channel m a)
createConnectedChannels (SlotNo, [Tx])
txs)
prop_pipe_IO :: (SlotNo, [Tx]) -> Property
prop_pipe_IO :: (SlotNo, [Tx]) -> Property
prop_pipe_IO (SlotNo, [Tx])
txs =
IO Bool -> Property
forall prop. Testable prop => IO prop -> Property
ioProperty (IO (Channel IO ByteString, Channel IO ByteString)
-> (SlotNo, [Tx]) -> IO Bool
forall (m :: * -> *).
(MonadAsync m, MonadCatch m, MonadST m) =>
m (Channel m ByteString, Channel m ByteString)
-> (SlotNo, [Tx]) -> m Bool
prop_channel IO (Channel IO ByteString, Channel IO ByteString)
createPipeConnectedChannels (SlotNo, [Tx])
txs)
newtype Tx = Tx { Tx -> TxId
txId :: TxId }
deriving (Tx -> Tx -> Bool
(Tx -> Tx -> Bool) -> (Tx -> Tx -> Bool) -> Eq Tx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tx -> Tx -> Bool
== :: Tx -> Tx -> Bool
$c/= :: Tx -> Tx -> Bool
/= :: Tx -> Tx -> Bool
Eq, Int -> Tx -> ShowS
[Tx] -> ShowS
Tx -> TestName
(Int -> Tx -> ShowS)
-> (Tx -> TestName) -> ([Tx] -> ShowS) -> Show Tx
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Tx -> ShowS
showsPrec :: Int -> Tx -> ShowS
$cshow :: Tx -> TestName
show :: Tx -> TestName
$cshowList :: [Tx] -> ShowS
showList :: [Tx] -> ShowS
Show, Gen Tx
Gen Tx -> (Tx -> [Tx]) -> Arbitrary Tx
Tx -> [Tx]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen Tx
arbitrary :: Gen Tx
$cshrink :: Tx -> [Tx]
shrink :: Tx -> [Tx]
Arbitrary, [Tx] -> Encoding
Tx -> Encoding
(Tx -> Encoding)
-> (forall s. Decoder s Tx)
-> ([Tx] -> Encoding)
-> (forall s. Decoder s [Tx])
-> Serialise Tx
forall s. Decoder s [Tx]
forall s. Decoder s Tx
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
$cencode :: Tx -> Encoding
encode :: Tx -> Encoding
$cdecode :: forall s. Decoder s Tx
decode :: forall s. Decoder s Tx
$cencodeList :: [Tx] -> Encoding
encodeList :: [Tx] -> Encoding
$cdecodeList :: forall s. Decoder s [Tx]
decodeList :: forall s. Decoder s [Tx]
Serialise)
instance ShowProxy Tx where
showProxy :: Proxy Tx -> TestName
showProxy Proxy Tx
_ = TestName
"Tx"
newtype TxId = TxId Int
deriving (TxId -> TxId -> Bool
(TxId -> TxId -> Bool) -> (TxId -> TxId -> Bool) -> Eq TxId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxId -> TxId -> Bool
== :: TxId -> TxId -> Bool
$c/= :: TxId -> TxId -> Bool
/= :: TxId -> TxId -> Bool
Eq, Eq TxId
Eq TxId =>
(TxId -> TxId -> Ordering)
-> (TxId -> TxId -> Bool)
-> (TxId -> TxId -> Bool)
-> (TxId -> TxId -> Bool)
-> (TxId -> TxId -> Bool)
-> (TxId -> TxId -> TxId)
-> (TxId -> TxId -> TxId)
-> Ord TxId
TxId -> TxId -> Bool
TxId -> TxId -> Ordering
TxId -> TxId -> TxId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TxId -> TxId -> Ordering
compare :: TxId -> TxId -> Ordering
$c< :: TxId -> TxId -> Bool
< :: TxId -> TxId -> Bool
$c<= :: TxId -> TxId -> Bool
<= :: TxId -> TxId -> Bool
$c> :: TxId -> TxId -> Bool
> :: TxId -> TxId -> Bool
$c>= :: TxId -> TxId -> Bool
>= :: TxId -> TxId -> Bool
$cmax :: TxId -> TxId -> TxId
max :: TxId -> TxId -> TxId
$cmin :: TxId -> TxId -> TxId
min :: TxId -> TxId -> TxId
Ord, Int -> TxId -> ShowS
[TxId] -> ShowS
TxId -> TestName
(Int -> TxId -> ShowS)
-> (TxId -> TestName) -> ([TxId] -> ShowS) -> Show TxId
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxId -> ShowS
showsPrec :: Int -> TxId -> ShowS
$cshow :: TxId -> TestName
show :: TxId -> TestName
$cshowList :: [TxId] -> ShowS
showList :: [TxId] -> ShowS
Show, Gen TxId
Gen TxId -> (TxId -> [TxId]) -> Arbitrary TxId
TxId -> [TxId]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen TxId
arbitrary :: Gen TxId
$cshrink :: TxId -> [TxId]
shrink :: TxId -> [TxId]
Arbitrary, [TxId] -> Encoding
TxId -> Encoding
(TxId -> Encoding)
-> (forall s. Decoder s TxId)
-> ([TxId] -> Encoding)
-> (forall s. Decoder s [TxId])
-> Serialise TxId
forall s. Decoder s [TxId]
forall s. Decoder s TxId
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
$cencode :: TxId -> Encoding
encode :: TxId -> Encoding
$cdecode :: forall s. Decoder s TxId
decode :: forall s. Decoder s TxId
$cencodeList :: [TxId] -> Encoding
encodeList :: [TxId] -> Encoding
$cdecodeList :: forall s. Decoder s [TxId]
decodeList :: forall s. Decoder s [TxId]
Serialise)
instance ShowProxy TxId where
showProxy :: Proxy TxId -> TestName
showProxy Proxy TxId
_ = TestName
"TxId"
instance (Arbitrary txid, Arbitrary tx, Arbitrary slot)
=> Arbitrary (AnyMessage (LocalTxMonitor txid tx slot))
where
arbitrary :: Gen (AnyMessage (LocalTxMonitor txid tx slot))
arbitrary = [Gen (AnyMessage (LocalTxMonitor txid tx slot))]
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. [Gen a] -> Gen a
oneof
[ AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot)))
-> AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a b. (a -> b) -> a -> b
$ Message (LocalTxMonitor txid tx slot) 'StIdle 'StAcquiring
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage Message (LocalTxMonitor txid tx slot) 'StIdle 'StAcquiring
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Message (LocalTxMonitor txid tx slot) 'StIdle 'StAcquiring
MsgAcquire
, Message (LocalTxMonitor txid tx slot) 'StAcquiring 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage (Message (LocalTxMonitor txid tx slot) 'StAcquiring 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot))
-> (slot
-> Message (LocalTxMonitor txid tx slot) 'StAcquiring 'StAcquired)
-> slot
-> AnyMessage (LocalTxMonitor txid tx slot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. slot
-> Message (LocalTxMonitor txid tx slot) 'StAcquiring 'StAcquired
forall {k} {k1} slot1 (txid :: k) (tx :: k1).
slot1
-> Message (LocalTxMonitor txid tx slot1) 'StAcquiring 'StAcquired
MsgAcquired (slot -> AnyMessage (LocalTxMonitor txid tx slot))
-> Gen slot -> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen slot
forall a. Arbitrary a => Gen a
arbitrary
, AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot)))
-> AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a b. (a -> b) -> a -> b
$ Message (LocalTxMonitor txid tx slot) 'StAcquired 'StAcquiring
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage Message (LocalTxMonitor txid tx slot) 'StAcquired 'StAcquiring
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Message (LocalTxMonitor txid tx slot) 'StAcquired 'StAcquiring
MsgAwaitAcquire
, AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot)))
-> AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a b. (a -> b) -> a -> b
$ Message (LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'NextTx)
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage Message (LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'NextTx)
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Message (LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'NextTx)
MsgNextTx
, Message (LocalTxMonitor txid tx slot) ('StBusy 'NextTx) 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage (Message
(LocalTxMonitor txid tx slot) ('StBusy 'NextTx) 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot))
-> (Maybe tx
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'NextTx) 'StAcquired)
-> Maybe tx
-> AnyMessage (LocalTxMonitor txid tx slot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe tx
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'NextTx) 'StAcquired
forall {k} {k2} tx1 (txid :: k) (slot :: k2).
Maybe tx1
-> Message
(LocalTxMonitor txid tx1 slot) ('StBusy 'NextTx) 'StAcquired
MsgReplyNextTx (Maybe tx -> AnyMessage (LocalTxMonitor txid tx slot))
-> Gen (Maybe tx) -> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe tx)
forall a. Arbitrary a => Gen a
arbitrary
, Message (LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'HasTx)
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage (Message (LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'HasTx)
-> AnyMessage (LocalTxMonitor txid tx slot))
-> (txid
-> Message
(LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'HasTx))
-> txid
-> AnyMessage (LocalTxMonitor txid tx slot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. txid
-> Message
(LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'HasTx)
forall {k1} {k2} txid1 (tx :: k1) (slot :: k2).
txid1
-> Message
(LocalTxMonitor txid1 tx slot) 'StAcquired ('StBusy 'HasTx)
MsgHasTx (txid -> AnyMessage (LocalTxMonitor txid tx slot))
-> Gen txid -> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen txid
forall a. Arbitrary a => Gen a
arbitrary
, Message (LocalTxMonitor txid tx slot) ('StBusy 'HasTx) 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage (Message (LocalTxMonitor txid tx slot) ('StBusy 'HasTx) 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot))
-> (Bool
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'HasTx) 'StAcquired)
-> Bool
-> AnyMessage (LocalTxMonitor txid tx slot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'HasTx) 'StAcquired
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Bool
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'HasTx) 'StAcquired
MsgReplyHasTx (Bool -> AnyMessage (LocalTxMonitor txid tx slot))
-> Gen Bool -> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
, AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot)))
-> AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a b. (a -> b) -> a -> b
$ Message
(LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'GetSizes)
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage Message
(LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'GetSizes)
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Message
(LocalTxMonitor txid tx slot) 'StAcquired ('StBusy 'GetSizes)
MsgGetSizes
, Message
(LocalTxMonitor txid tx slot) ('StBusy 'GetSizes) 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage (Message
(LocalTxMonitor txid tx slot) ('StBusy 'GetSizes) 'StAcquired
-> AnyMessage (LocalTxMonitor txid tx slot))
-> (MempoolSizeAndCapacity
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'GetSizes) 'StAcquired)
-> MempoolSizeAndCapacity
-> AnyMessage (LocalTxMonitor txid tx slot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MempoolSizeAndCapacity
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'GetSizes) 'StAcquired
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
MempoolSizeAndCapacity
-> Message
(LocalTxMonitor txid tx slot) ('StBusy 'GetSizes) 'StAcquired
MsgReplyGetSizes (MempoolSizeAndCapacity
-> AnyMessage (LocalTxMonitor txid tx slot))
-> Gen MempoolSizeAndCapacity
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen MempoolSizeAndCapacity
forall a. Arbitrary a => Gen a
arbitrary
, AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot)))
-> AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a b. (a -> b) -> a -> b
$ Message (LocalTxMonitor txid tx slot) 'StAcquired 'StIdle
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage Message (LocalTxMonitor txid tx slot) 'StAcquired 'StIdle
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Message (LocalTxMonitor txid tx slot) 'StAcquired 'StIdle
MsgRelease
, AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot)))
-> AnyMessage (LocalTxMonitor txid tx slot)
-> Gen (AnyMessage (LocalTxMonitor txid tx slot))
forall a b. (a -> b) -> a -> b
$ Message (LocalTxMonitor txid tx slot) 'StIdle 'StDone
-> AnyMessage (LocalTxMonitor txid tx slot)
forall ps (st :: ps) (st' :: ps).
(StateTokenI st, ActiveState st) =>
Message ps st st' -> AnyMessage ps
AnyMessage Message (LocalTxMonitor txid tx slot) 'StIdle 'StDone
forall {k} {k1} {k2} (txid :: k) (tx :: k1) (slot :: k2).
Message (LocalTxMonitor txid tx slot) 'StIdle 'StDone
MsgDone
]
instance Arbitrary MempoolSizeAndCapacity where
arbitrary :: Gen MempoolSizeAndCapacity
arbitrary =
Word32 -> Word32 -> Word32 -> MempoolSizeAndCapacity
MempoolSizeAndCapacity
(Word32 -> Word32 -> Word32 -> MempoolSizeAndCapacity)
-> Gen Word32 -> Gen (Word32 -> Word32 -> MempoolSizeAndCapacity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
Gen (Word32 -> Word32 -> MempoolSizeAndCapacity)
-> Gen Word32 -> Gen (Word32 -> MempoolSizeAndCapacity)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
Gen (Word32 -> MempoolSizeAndCapacity)
-> Gen Word32 -> Gen MempoolSizeAndCapacity
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
instance (Eq txid, Eq tx, Eq slot)
=> Eq (AnyMessage (LocalTxMonitor txid tx slot))
where
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgAcquire == :: AnyMessage (LocalTxMonitor txid tx slot)
-> AnyMessage (LocalTxMonitor txid tx slot) -> Bool
== AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgAcquire = Bool
True
AnyMessage (MsgAcquired slot1
a) == AnyMessage (MsgAcquired slot1
b) = slot1
a slot1 -> slot1 -> Bool
forall a. Eq a => a -> a -> Bool
== slot1
slot1
b
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgAwaitAcquire == AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgAwaitAcquire = Bool
True
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgNextTx == AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgNextTx = Bool
True
AnyMessage (MsgReplyNextTx Maybe tx1
a) == AnyMessage (MsgReplyNextTx Maybe tx1
b) = Maybe tx1
a Maybe tx1 -> Maybe tx1 -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe tx1
Maybe tx1
b
AnyMessage (MsgHasTx txid1
a) == AnyMessage (MsgHasTx txid1
b) = txid1
a txid1 -> txid1 -> Bool
forall a. Eq a => a -> a -> Bool
== txid1
txid1
b
AnyMessage (MsgReplyHasTx Bool
a) == AnyMessage (MsgReplyHasTx Bool
b) = Bool
a Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
b
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgGetSizes == AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgGetSizes = Bool
True
AnyMessage (MsgReplyGetSizes MempoolSizeAndCapacity
a) == AnyMessage (MsgReplyGetSizes MempoolSizeAndCapacity
b) = MempoolSizeAndCapacity
a MempoolSizeAndCapacity -> MempoolSizeAndCapacity -> Bool
forall a. Eq a => a -> a -> Bool
== MempoolSizeAndCapacity
b
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgRelease == AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgRelease = Bool
True
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgDone == AnyMessage Message (LocalTxMonitor txid tx slot) st st'
R:MessageLocalTxMonitorfromto (*) (*) (*) txid tx slot st st'
MsgDone = Bool
True
AnyMessage Message (LocalTxMonitor txid tx slot) st st'
_ == AnyMessage Message (LocalTxMonitor txid tx slot) st st'
_ = Bool
False