diff --git a/net-mqtt.cabal b/net-mqtt.cabal index 915749d..1a123c7 100644 --- a/net-mqtt.cabal +++ b/net-mqtt.cabal @@ -122,10 +122,13 @@ executable mqtt-watch test-suite mqtt-test type: exitcode-stdio-1.0 - main-is: Spec.hs + main-is: Main.hs other-modules: + DecayingSpec Example1 Example2 + ExpiringSpec + Spec Paths_net_mqtt hs-source-dirs: test @@ -152,6 +155,7 @@ test-suite mqtt-test , network-uri >=2.6.1 && <2.7 , stm >=2.4.0 && <2.6 , tasty + , tasty-discover , tasty-hunit , tasty-quickcheck , text >=1.2.3 && <2.1.0 diff --git a/package.yaml b/package.yaml index b3db43a..6b5cd62 100644 --- a/package.yaml +++ b/package.yaml @@ -69,7 +69,7 @@ executables: tests: mqtt-test: - main: Spec.hs + main: Main.hs source-dirs: test ghc-options: - -threaded @@ -81,5 +81,6 @@ tests: - tasty - tasty-hunit - tasty-quickcheck + - tasty-discover - checkers - mtl diff --git a/src/Data/Map/Strict/Expiring.hs b/src/Data/Map/Strict/Expiring.hs index 2f1ecf7..0959e01 100644 --- a/src/Data/Map/Strict/Expiring.hs +++ b/src/Data/Map/Strict/Expiring.hs @@ -80,12 +80,12 @@ removeAging g k = Map.update (nonNull . Set.delete k) g -- | 𝑂(log𝑛). Lookup a value in the map. -- This will not return any items that have expired. lookup :: (Ord k, Ord g) => k -> Map g k a -> Maybe a -lookup k Map{..} = value <$> Map.lookup k map +lookup k = fmap value . Map.lookup k . map -- | 𝑂(log𝑛). Delete an item. delete :: (Ord k, Ord g) => k -> Map g k a -> Map g k a delete k m@Map{..} = case Map.lookup k map of - Nothing -> m + Nothing -> m Just Entry{..} -> m { map = Map.delete k map, aging = removeAging gen k aging } -- | 𝑂(𝑛). Return all current key/value associations. diff --git a/test/DecayingSpec.hs b/test/DecayingSpec.hs new file mode 100644 index 0000000..b3b0b92 --- /dev/null +++ b/test/DecayingSpec.hs @@ -0,0 +1,50 @@ +{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ViewPatterns #-} + +module DecayingSpec where + +import Control.Concurrent (threadDelay) +import Control.Concurrent.STM (STM, atomically) +import Control.Monad (foldM, mapM_) +import qualified Data.Attoparsec.ByteString.Lazy as A +import qualified Data.ByteString.Lazy as L +import Data.Foldable (traverse_) +import qualified Data.Map.Strict as Map +import qualified Data.Map.Strict.Decaying as DecayingMap +import Data.Set (Set) +import qualified Data.Set as Set + +import Test.QuickCheck + +prop_decayingMapWorks :: [Int] -> Property +prop_decayingMapWorks keys = idempotentIOProperty $ do + m <- DecayingMap.new 60 + atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys + found <- atomically $ traverse (\x -> DecayingMap.findWithDefault maxBound x m) keys + pure $ found === keys + +prop_decayingMapDecays :: [Int] -> Property +prop_decayingMapDecays keys = idempotentIOProperty $ do + m <- DecayingMap.new 0.001 + atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys + threadDelay 5000 + DecayingMap.tick m + found <- atomically $ DecayingMap.elems m + pure $ found === [] + +prop_decayingMapUpdates :: Set Int -> Property +prop_decayingMapUpdates (Set.toList -> keys) = idempotentIOProperty $ do + m <- DecayingMap.new 60 + atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys + updated <- atomically $ traverse (\x -> DecayingMap.updateLookupWithKey (\_ v -> Just (v + 1)) x m) keys + found <- atomically $ traverse (\x -> DecayingMap.findWithDefault maxBound x m) keys + pure $ (found === fmap (+ 1) keys .&&. Just found === sequenceA updated) + +prop_decayingMapDeletes :: Set Int -> Property +prop_decayingMapDeletes (Set.toList -> keys) = (not . null) keys ==> idempotentIOProperty $ do + m <- DecayingMap.new 60 + atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys + atomically $ traverse (`DecayingMap.delete` m) (tail keys) + found <- atomically $ DecayingMap.elems m + pure $ found === take 1 keys diff --git a/test/ExpiringSpec.hs b/test/ExpiringSpec.hs new file mode 100644 index 0000000..7e799fb --- /dev/null +++ b/test/ExpiringSpec.hs @@ -0,0 +1,142 @@ +{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TupleSections #-} + +module ExpiringSpec where + +import Control.Monad.RWS.Strict (MonadWriter (tell), evalRWS, gets, modify) +import Data.Foldable (toList, traverse_) +import qualified Data.Map.Strict as Map +import qualified Data.Map.Strict.Expiring as ExpiringMap +import Data.Set (Set) +import qualified Data.Set as Set + +import Test.QuickCheck + +newtype SomeKey = SomeKey Char + deriving (Eq, Ord, Show) + +instance Arbitrary SomeKey where + arbitrary = SomeKey <$> elements ['a'..'e'] + +data MapOp = Insert SomeKey Int + | Delete SomeKey + | Lookup SomeKey + | Update SomeKey Int + | UpdateNothing SomeKey + deriving Show + +instance Arbitrary MapOp where + arbitrary = oneof [Insert <$> arbitrary <*> arbitrary, + Delete <$> arbitrary, + Lookup <$> arbitrary, + Update <$> arbitrary <*> arbitrary, + UpdateNothing <$> arbitrary + ] + +allOpTypes :: [String] +allOpTypes = ["Insert", "Delete", "Lookup", "Update", "UpdateNothing"] + +prop_expMapDoesMapStuff :: [MapOp] -> Property +prop_expMapDoesMapStuff ops = + coverTable "pkt types" ((,5) <$> allOpTypes) $ + tabulate "pkt types" (lab <$> ops) $ + checkCoverage $ + massocs === eassocs + where + lab x = let (s,_) = break (== ' ') . show $ x in s + massocs = snd $ evalRWS (applyOpsM ops) () (mempty :: Map.Map SomeKey Int) + eassocs = snd $ evalRWS (applyOpsE ops) () (ExpiringMap.new 0) + + applyOpsM = traverse_ \case + Insert k v -> do + modify $ Map.insert k v + tell =<< gets Map.assocs + Delete k -> do + modify $ Map.delete k + tell =<< gets Map.assocs + Lookup k -> do + gets (Map.lookup k) >>= \case + Nothing -> pure () + Just v -> tell [(k, v)] + Update k v -> do + modify $ (snd <$> Map.updateLookupWithKey (\_ _ -> Just v) k) + tell =<< gets Map.assocs + UpdateNothing k -> do + modify $ (snd <$> Map.updateLookupWithKey (\_ _ -> Nothing) k) + tell =<< gets Map.assocs + + applyOpsE = traverse_ \case + Insert k v -> do + modify $ ExpiringMap.insert 1 k v + tell =<< gets ExpiringMap.assocs + Delete k -> do + modify $ ExpiringMap.delete k + tell =<< gets ExpiringMap.assocs + Lookup k -> do + gets (ExpiringMap.lookup k) >>= \case + Nothing -> pure () + Just v -> tell [(k, v)] + Update k v -> do + modify $ (snd <$> ExpiringMap.updateLookupWithKey 1 (\_ _ -> Just v) k) + tell =<< gets ExpiringMap.assocs + UpdateNothing k -> do + modify $ (snd <$> ExpiringMap.updateLookupWithKey 1 (\_ _ -> Nothing) k) + tell =<< gets ExpiringMap.assocs + +prop_expiringMapWorks :: Int -> [Int] -> Property +prop_expiringMapWorks baseGen keys = Just keys === traverse (`ExpiringMap.lookup` m) keys + where + m = foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys + futureGen = succ baseGen + +ulength :: (Ord a, Foldable t) => t a -> Int +ulength = Set.size . Set.fromList . toList + +prop_expiringMapExpires :: Int -> [Int] -> Property +prop_expiringMapExpires baseGen keys = (ulength keys, futureGen, ulength keys) === ExpiringMap.inspect m1 .&&. (0, lastGen, 0) === ExpiringMap.inspect m2 + where + m1 = ExpiringMap.newGen futureGen $ foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys + m2 = ExpiringMap.newGen lastGen m1 + futureGen = succ baseGen + lastGen = succ futureGen + +prop_expiringMapCannotAcceptExpired :: Positive Int -> Positive Int -> Int -> Property +prop_expiringMapCannotAcceptExpired (Positive lowGen) (Positive offset) k = ExpiringMap.inspect m === ExpiringMap.inspect m' + where + highGen = lowGen + offset + m = ExpiringMap.new highGen :: ExpiringMap.Map Int Int Int + m' = ExpiringMap.insert lowGen k k m + +prop_expiringMapUpdateMissing :: Int -> Int -> Property +prop_expiringMapUpdateMissing gen k = mv === Nothing .&&. ExpiringMap.inspect m === ExpiringMap.inspect m' + where + m = ExpiringMap.new gen :: ExpiringMap.Map Int Int Bool + (mv, m') = ExpiringMap.updateLookupWithKey gen (\_ _ -> Just True) k m + +prop_expiringMapCannotUpdateExpired :: Positive Int -> Positive Int -> Int -> Property +prop_expiringMapCannotUpdateExpired (Positive lowGen) (Positive offset) k = mv === Nothing .&&. ExpiringMap.lookup k m' === Just True + where + highGen = lowGen + offset + m = ExpiringMap.insert highGen k True $ ExpiringMap.new highGen + (mv, m') = ExpiringMap.updateLookupWithKey lowGen (\_ _ -> Just False) k m + +prop_expiringMapDelete :: Int -> [Int] -> Property +prop_expiringMapDelete baseGen keys = (ulength keys, baseGen, ulength keys) === ExpiringMap.inspect m .&&. (0, baseGen, 0) === ExpiringMap.inspect m' + where + m = foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys + m' = foldr ExpiringMap.delete m keys + futureGen = succ baseGen + +prop_expiringMapElems :: Int -> Set Int -> Property +prop_expiringMapElems baseGen keys = keys === Set.fromList (toList m) + where + m = foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys + futureGen = succ baseGen + +prop_expiringMapGen :: Int -> Int -> Property +prop_expiringMapGen g1 g2 = ExpiringMap.inspect m === (0, max g1 g2, 0) + where + m :: ExpiringMap.Map Int Int Int + m = ExpiringMap.newGen g2 $ ExpiringMap.new g1 diff --git a/test/Main.hs b/test/Main.hs new file mode 100644 index 0000000..327adf4 --- /dev/null +++ b/test/Main.hs @@ -0,0 +1 @@ +{-# OPTIONS_GHC -F -pgmF tasty-discover -optF --tree-display #-} diff --git a/test/Spec.hs b/test/Spec.hs index ad8bb14..685ea89 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -1,23 +1,13 @@ {-# LANGUAGE BlockArguments #-} -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeApplications #-} -{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE TupleSections #-} + + +module Spec where -import Control.Concurrent (threadDelay) -import Control.Concurrent.STM (STM, atomically) -import Control.Monad (foldM, mapM_) -import Control.Monad.RWS.Strict import qualified Data.Attoparsec.ByteString.Lazy as A import qualified Data.ByteString.Lazy as L -import Data.ByteString.Lazy.Char8 (foldl') import Data.Foldable (toList, traverse_) -import Data.Functor.Identity (Identity) -import qualified Data.Map.Strict as Map -import qualified Data.Map.Strict.Decaying as DecayingMap -import qualified Data.Map.Strict.Expiring as ExpiringMap -import Data.Set (Set) -import qualified Data.Set as Set import Data.String (fromString) import qualified Data.Text as T import Data.Word (Word8) @@ -34,7 +24,9 @@ import Test.Tasty.QuickCheck as QC prop_rtLengthParser :: SizeT -> QC.Property prop_rtLengthParser (SizeT x) = - label (show (length e) <> "B") $ + coverTable "Sizes" [("1B", 10), ("2B", 10), ("3B", 10), ("4B", 10)] $ + tabulate "Sizes" [show (length e) <> "B"] $ + checkCoverage $ d e == x where e = encodeLength x @@ -56,22 +48,46 @@ testPacketRT = mapM_ tryParse [ f@A.Fail{} -> assertFailure (show f) (A.Done _ x') -> assertEqual (show s) x x' +allPktTypes :: [String] +allPktTypes = [ + "ConnPkt", + "ConnACKPkt", + "PublishPkt", + "PubACKPkt", + "PubRECPkt", + "PubRELPkt", + "PubCOMPPkt", + "SubscribePkt", + "SubACKPkt", + "UnsubscribePkt", + "UnsubACKPkt", + "PingPkt", + "PongPkt", + "DisconnectPkt", + "AuthPkt" + ] + prop_PacketRT50 :: MQTTPkt -> QC.Property -prop_PacketRT50 p = label (lab p) $ case A.parse (parsePacket Protocol50) (toByteString Protocol50 p) of - A.Fail{} -> False - (A.Done _ r) -> r == p +prop_PacketRT50 p = + coverTable "pkt types" ((,1) <$> allPktTypes) $ + tabulate "pkt types" [lab p] $ + checkCoverage $ + case A.parse (parsePacket Protocol50) (toByteString Protocol50 p) of + A.Fail{} -> False + (A.Done _ r) -> r == p where lab x = let (s,_) = break (== ' ') . show $ x in s prop_PacketRT311 :: MQTTPkt -> QC.Property prop_PacketRT311 p = available p ==> - let p' = v311mask p in - label (lab p') $ case A.parse (parsePacket Protocol311) (toByteString Protocol311 p') of - A.Fail{} -> False - (A.Done _ r) -> r == p' + label (lab p) $ + case A.parse (parsePacket Protocol311) (toByteString Protocol311 p') of + A.Fail{} -> False + (A.Done _ r) -> r == p' where lab x = let (s,_) = break (== ' ') . show $ x in s + p' = v311mask p available (AuthPkt _) = False available _ = True @@ -108,7 +124,7 @@ testTopicMatching = let allTopics = ["a", "a/b", "a/b/c/d", "b/a/c/d", prop_TopicMatching :: MatchingTopic -> QC.Property prop_TopicMatching (MatchingTopic (t,ms)) = counterexample (show ms <> " doesn't match " <> show t) $ - all (\m -> match m t) ms + all (`match` t) ms byteRT :: (ByteSize a, Show a, Eq a) => a -> Bool byteRT x = x == (fromByte . toByte) x @@ -121,193 +137,11 @@ testQoSFromInt = do instance EqProp Filter where (=-=) = eq instance EqProp Topic where (=-=) = eq -prop_decayingMapWorks :: [Int] -> QC.Property -prop_decayingMapWorks keys = idempotentIOProperty $ do - m <- DecayingMap.new 60 - atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys - found <- atomically $ traverse (\x -> DecayingMap.findWithDefault maxBound x m) keys - pure $ found === keys - -prop_decayingMapDecays :: [Int] -> QC.Property -prop_decayingMapDecays keys = idempotentIOProperty $ do - m <- DecayingMap.new 0.001 - atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys - threadDelay 5000 - DecayingMap.tick m - found <- atomically $ DecayingMap.elems m - pure $ found === [] - -prop_decayingMapUpdates :: Set Int -> QC.Property -prop_decayingMapUpdates (Set.toList -> keys) = idempotentIOProperty $ do - m <- DecayingMap.new 60 - atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys - updated <- atomically $ traverse (\x -> DecayingMap.updateLookupWithKey (\_ v -> Just (v + 1)) x m) keys - found <- atomically $ traverse (\x -> DecayingMap.findWithDefault maxBound x m) keys - pure $ (found === fmap (+ 1) keys .&&. Just found === sequenceA updated) - -prop_decayingMapDeletes :: Set Int -> QC.Property -prop_decayingMapDeletes (Set.toList -> keys) = (not . null) keys ==> idempotentIOProperty $ do - m <- DecayingMap.new 60 - atomically $ traverse_ (\x -> DecayingMap.insert x x m) keys - atomically $ traverse (\x -> DecayingMap.delete x m) (tail keys) - found <- atomically $ DecayingMap.elems m - pure $ found === take 1 keys - -testDecayingMap :: [TestTree] -testDecayingMap = [ - testProperty "works" prop_decayingMapWorks, - testProperty "decaying map decays" prop_decayingMapDecays, - testProperty "updates" prop_decayingMapUpdates, - testProperty "deletes" prop_decayingMapDeletes - ] - -newtype SomeKey = SomeKey Char - deriving (Eq, Ord, Show) - -instance Arbitrary SomeKey where - arbitrary = SomeKey <$> elements ['a'..'e'] - -data MapOp = MapInsert SomeKey Int - | MapDelete SomeKey - | MapLookup SomeKey - | MapUpdate SomeKey Int - | MapUpdateNothing SomeKey - deriving Show - -instance Arbitrary MapOp where - arbitrary = oneof [MapInsert <$> arbitrary <*> arbitrary, - MapDelete <$> arbitrary, - MapLookup <$> arbitrary, - MapUpdate <$> arbitrary <*> arbitrary, - MapUpdateNothing <$> arbitrary - ] - -prop_expMapDoesMapStuff :: [MapOp] -> QC.Property -prop_expMapDoesMapStuff ops = massocs === eassocs - where - massocs = snd $ evalRWS (applyOpsM ops) () (mempty :: Map.Map SomeKey Int) - eassocs = snd $ evalRWS (applyOpsE ops) () (ExpiringMap.new 0) - - applyOpsM = traverse_ \case - MapInsert k v -> do - modify $ Map.insert k v - tell =<< gets Map.assocs - MapDelete k -> do - modify $ Map.delete k - tell =<< gets Map.assocs - MapLookup k -> do - gets (Map.lookup k) >>= \case - Nothing -> pure () - Just v -> tell [(k, v)] - MapUpdate k v -> do - modify $ fmap snd $ Map.updateLookupWithKey (\_ _ -> Just v) k - tell =<< gets Map.assocs - MapUpdateNothing k -> do - modify $ fmap snd $ Map.updateLookupWithKey (\_ _ -> Nothing) k - tell =<< gets Map.assocs - - applyOpsE = traverse_ \case - MapInsert k v -> do - modify $ ExpiringMap.insert 1 k v - tell =<< gets ExpiringMap.assocs - MapDelete k -> do - modify $ ExpiringMap.delete k - tell =<< gets ExpiringMap.assocs - MapLookup k -> do - gets (ExpiringMap.lookup k) >>= \case - Nothing -> pure () - Just v -> tell [(k, v)] - MapUpdate k v -> do - modify $ fmap snd $ ExpiringMap.updateLookupWithKey 1 (\_ _ -> Just v) k - tell =<< gets ExpiringMap.assocs - MapUpdateNothing k -> do - modify $ fmap snd $ ExpiringMap.updateLookupWithKey 1 (\_ _ -> Nothing) k - tell =<< gets ExpiringMap.assocs - -prop_expiringMapWorks :: Int -> [Int] -> QC.Property -prop_expiringMapWorks baseGen keys = Just keys === traverse (flip ExpiringMap.lookup m) keys - where - m = foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys - futureGen = succ baseGen - -ulength :: (Ord a, Foldable t) => t a -> Int -ulength = Set.size . Set.fromList . toList - -prop_expiringMapExpires :: Int -> [Int] -> QC.Property -prop_expiringMapExpires baseGen keys = (ulength keys, futureGen, ulength keys) === ExpiringMap.inspect m1 .&&. (0, lastGen, 0) === ExpiringMap.inspect m2 - where - m1 = ExpiringMap.newGen futureGen $ foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys - m2 = ExpiringMap.newGen lastGen m1 - futureGen = succ baseGen - lastGen = succ futureGen - -prop_expiringMapCannotAcceptExpired :: Positive Int -> Positive Int -> Int -> QC.Property -prop_expiringMapCannotAcceptExpired (Positive lowGen) (Positive offset) k = ExpiringMap.inspect m === ExpiringMap.inspect m' - where - highGen = lowGen + offset - m = ExpiringMap.new highGen :: ExpiringMap.Map Int Int Int - m' = ExpiringMap.insert lowGen k k m - -prop_expiringMapUpdateMissing :: Int -> Int -> QC.Property -prop_expiringMapUpdateMissing gen k = mv === Nothing .&&. ExpiringMap.inspect m === ExpiringMap.inspect m' - where - m = ExpiringMap.new gen :: ExpiringMap.Map Int Int Bool - (mv, m') = ExpiringMap.updateLookupWithKey gen (\_ _ -> Just True) k m - -prop_expiringMapCannotUpdateExpired :: Positive Int -> Positive Int -> Int -> QC.Property -prop_expiringMapCannotUpdateExpired (Positive lowGen) (Positive offset) k = mv === Nothing .&&. ExpiringMap.lookup k m' === Just True - where - highGen = lowGen + offset - m = ExpiringMap.insert highGen k True $ ExpiringMap.new highGen - (mv, m') = ExpiringMap.updateLookupWithKey lowGen (\_ _ -> Just False) k m - -prop_expiringMapDelete :: Int -> [Int] -> QC.Property -prop_expiringMapDelete baseGen keys = (ulength keys, baseGen, ulength keys) === ExpiringMap.inspect m .&&. (0, baseGen, 0) === ExpiringMap.inspect m' - where - m = foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys - m' = foldr (\x -> ExpiringMap.delete x) m keys - futureGen = succ baseGen - -prop_expiringMapElems :: Int -> Set Int -> QC.Property -prop_expiringMapElems baseGen keys = keys === Set.fromList (toList m) - where - m = foldr (\x -> ExpiringMap.insert futureGen x x) (ExpiringMap.new baseGen) keys - futureGen = succ baseGen - -prop_expiringMapGen :: Int -> Int -> QC.Property -prop_expiringMapGen g1 g2 = ExpiringMap.inspect m === (0, max g1 g2, 0) - where - m :: ExpiringMap.Map Int Int Int - m = ExpiringMap.newGen g2 $ ExpiringMap.new g1 - -testExpiringMap :: [TestTree] -testExpiringMap = [ - testProperty "works" prop_expiringMapWorks, - testProperty "expires" prop_expiringMapExpires, - testProperty "cannot insert expired items" prop_expiringMapCannotAcceptExpired, - testProperty "cannot update expired items" prop_expiringMapCannotUpdateExpired, - testProperty "can't update missing items" prop_expiringMapUpdateMissing, - testProperty "delete cleans up" prop_expiringMapDelete, - testProperty "toList" prop_expiringMapElems, - testProperty "generation never decreases" prop_expiringMapGen, - localOption (QC.QuickCheckTests 10000) $ testProperty "compares to regular map" prop_expMapDoesMapStuff - ] - -tests :: [TestTree] -tests = [ - localOption (QC.QuickCheckTests 10000) $ testProperty "header length rt (parser)" prop_rtLengthParser, - +test_Spec :: [TestTree] +test_Spec = [ testCase "rt some packets" testPacketRT, - localOption (QC.QuickCheckTests 1000) $ testProperty "rt packets 3.11" prop_PacketRT311, - localOption (QC.QuickCheckTests 1000) $ testProperty "rt packets 5.0" prop_PacketRT50, - localOption (QC.QuickCheckTests 1000) $ testProperty "rt property" prop_PropertyRT, - testProperty "rt properties" prop_PropertiesRT, - testProperty "sub options" prop_SubOptionsRT, testCase "qosFromInt" testQoSFromInt, - testGroup "expiring map" testExpiringMap, - testGroup "decaying map" testDecayingMap, - testProperty "conn reasons" (byteRT :: ConnACKRC -> Bool), testProperty "disco reasons" (byteRT :: DiscoReason -> Bool), @@ -317,6 +151,3 @@ tests = [ testGroup "topic matching" testTopicMatching, testProperty "arbitrary topic matching" prop_TopicMatching ] - -main :: IO () -main = defaultMain $ testGroup "All Tests" tests