module Load.CoreSpec (spec) where import Control.Exception.Base import Control.Monad.State import Data.List (sort) import Load.Core import Test.Hspec data TestException = TestException deriving (Show) instance Exception TestException spec :: SpecWith () spec = do basic basic :: SpecWith () basic = do let n = 100 it "performs all requests" $ do let cfg = Config { supplier = do cur <- get let next = cur + 1 put next return next, performer = \x -> return (2 * x), collector = (:), queue = 20, workers = 4, rate = 1000, burst = 10 } evalStateT (runLoadN n cfg) 0 >>= flip shouldBe [2, 4 .. 2 * n] . sort it "does not hang on exception" $ do let cfg = Config { supplier = do cur <- get let next = cur + 1 put next return next, performer = \i -> when (even i) $ throwIO TestException, collector = \_ s -> s + 1, queue = 1, workers = 1, rate = 1000, burst = 10 } -- since half of the request throw IO exception we expect to collect the other half evalStateT (runLoadN n cfg) (0 :: Integer) >>= flip shouldBe (toInteger (n `div` 2))