diff options
Diffstat (limited to 'server/test')
| -rw-r--r-- | server/test/Thermoprint/Server/QueueSpec.hs | 13 | ||||
| -rw-r--r-- | server/test/Thermoprint/ServerSpec.hs | 126 |
2 files changed, 103 insertions, 36 deletions
diff --git a/server/test/Thermoprint/Server/QueueSpec.hs b/server/test/Thermoprint/Server/QueueSpec.hs index 4a9297e..8a6bb7b 100644 --- a/server/test/Thermoprint/Server/QueueSpec.hs +++ b/server/test/Thermoprint/Server/QueueSpec.hs | |||
| @@ -16,19 +16,6 @@ import Test.QuickCheck.Modifiers | |||
| 16 | deriving instance (Eq PrintingError) | 16 | deriving instance (Eq PrintingError) |
| 17 | deriving instance (Eq Queue) | 17 | deriving instance (Eq Queue) |
| 18 | 18 | ||
| 19 | instance Arbitrary Queue where | ||
| 20 | arbitrary = Queue <$> arbitrary <*> arbitrary <*> arbitrary | ||
| 21 | |||
| 22 | instance Arbitrary QueueEntry where | ||
| 23 | arbitrary = QueueEntry <$> arbitrary <*> arbitrary | ||
| 24 | |||
| 25 | instance Arbitrary PrintingError where | ||
| 26 | arbitrary = oneof [ return (IOError "dummy") | ||
| 27 | ] | ||
| 28 | |||
| 29 | instance Arbitrary JobId where | ||
| 30 | arbitrary = castId . getNonNegative <$> (arbitrary :: Gen (NonNegative Integer)) | ||
| 31 | |||
| 32 | spec :: Spec | 19 | spec :: Spec |
| 33 | spec = do | 20 | spec = do |
| 34 | describe "queue morphisms" $ do | 21 | describe "queue morphisms" $ do |
diff --git a/server/test/Thermoprint/ServerSpec.hs b/server/test/Thermoprint/ServerSpec.hs index 495ad10..deb2b9c 100644 --- a/server/test/Thermoprint/ServerSpec.hs +++ b/server/test/Thermoprint/ServerSpec.hs | |||
| @@ -1,66 +1,146 @@ | |||
| 1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} |
| 2 | {-# LANGUAGE OverloadedLists #-} | ||
| 2 | {-# LANGUAGE ImpredicativeTypes #-} | 3 | {-# LANGUAGE ImpredicativeTypes #-} |
| 4 | {-# LANGUAGE RecordWildCards #-} | ||
| 5 | {-# LANGUAGE StandaloneDeriving #-} | ||
| 3 | 6 | ||
| 4 | module Thermoprint.ServerSpec (spec) where | 7 | module Thermoprint.ServerSpec (spec) where |
| 5 | 8 | ||
| 6 | import Test.Hspec | 9 | import Test.Hspec |
| 10 | import Test.Hspec.QuickCheck | ||
| 11 | import qualified Test.Hspec as Hspec | ||
| 12 | |||
| 13 | import Test.QuickCheck | ||
| 7 | 14 | ||
| 8 | import Thermoprint.API | 15 | import Thermoprint.API |
| 9 | import Thermoprint.Server | 16 | import qualified Thermoprint.Server as S |
| 17 | import Thermoprint.Client | ||
| 10 | 18 | ||
| 19 | import Data.Monoid | ||
| 20 | import Data.Function | ||
| 11 | import Control.Monad | 21 | import Control.Monad |
| 12 | import Control.Monad.Logger | 22 | import Control.Monad.Logger |
| 13 | import Control.Monad.Reader | 23 | import Control.Monad.Reader |
| 24 | import Control.Monad.State | ||
| 14 | import Control.Monad.Trans.Identity | 25 | import Control.Monad.Trans.Identity |
| 15 | import Control.Monad.Trans.Resource | 26 | import Control.Monad.Trans.Resource |
| 27 | import Control.Monad.Catch (finally) | ||
| 16 | 28 | ||
| 17 | import Database.Persist.Sqlite | 29 | import Database.Persist.Sqlite |
| 18 | 30 | ||
| 19 | import Control.Concurrent | 31 | import Control.Concurrent |
| 20 | import Control.Concurrent.STM | 32 | import Control.Concurrent.STM |
| 33 | import Control.Concurrent.STM.TSem | ||
| 21 | 34 | ||
| 22 | import System.IO | 35 | import System.IO |
| 23 | import System.IO.Temp | 36 | import System.IO.Temp |
| 24 | 37 | ||
| 25 | import qualified Data.Text as T | 38 | import qualified Data.Text as T |
| 26 | 39 | ||
| 27 | import Debug.Trace | 40 | import Network.Wai.Handler.Warp (defaultSettings, setBeforeMainLoop) |
| 41 | |||
| 42 | import qualified Data.Map as Map | ||
| 43 | |||
| 44 | deriving instance Eq PrintingError | ||
| 45 | deriving instance Eq JobStatus | ||
| 46 | deriving instance Eq PrinterStatus | ||
| 47 | |||
| 48 | -- Equality via cotext on Block | ||
| 49 | instance Eq Block where | ||
| 50 | (==) = (==) `on` cotext | ||
| 51 | -- Structural equality for Chunk | ||
| 52 | deriving instance Eq Chunk | ||
| 28 | 53 | ||
| 29 | data TestPrinter = TestPrinter | 54 | data TestPrinter = TestPrinter |
| 30 | { outputChan :: TChan Printout | 55 | { outputChan :: TMVar Printout |
| 31 | , failSwitch :: TMVar PrintingError | 56 | , failSwitch :: TMVar PrintingError |
| 32 | } | 57 | } |
| 33 | 58 | ||
| 34 | data TestManager = TestManager | 59 | data TestManager = TestManager |
| 35 | { manage :: TMVar (QueueManager IdentityT) | 60 | { manage :: TMVar (S.QueueManager IdentityT) |
| 61 | , ran :: TSem | ||
| 36 | } | 62 | } |
| 37 | 63 | ||
| 38 | setup :: IO (ThreadId, QSem, TestPrinter, TestManager) | 64 | data RunningServer = RunningServer |
| 39 | setup = withSystemTempFile "thermoprint.sqlite" $ \fp h -> hClose h >> do | 65 | { thread :: ThreadId |
| 40 | tPrinter <- TestPrinter <$> newTChanIO <*> newEmptyTMVarIO | 66 | , termination :: QSem |
| 41 | tManager <- TestManager <$> newEmptyTMVarIO | 67 | , printer :: TestPrinter |
| 68 | , manager :: TestManager | ||
| 69 | } | ||
| 70 | |||
| 71 | setup :: QSem -> IO RunningServer | ||
| 72 | setup startup = withSystemTempFile "thermoprint.sqlite" $ \fp h -> hClose h >> do | ||
| 73 | tPrinter <- TestPrinter <$> newEmptyTMVarIO <*> newEmptyTMVarIO | ||
| 74 | tManager <- TestManager <$> newEmptyTMVarIO <*> atomically (newTSem 0) | ||
| 42 | termSem <- newQSem 0 | 75 | termSem <- newQSem 0 |
| 43 | let | 76 | let |
| 44 | runSqlite :: ReaderT ConnectionPool (NoLoggingT IO) a -> IO a | 77 | runSqlite :: ReaderT ConnectionPool (LoggingT IO) a -> IO a |
| 45 | runSqlite = runNoLoggingT . withSqlitePool (T.pack fp) 1 . runReaderT | 78 | runSqlite = runStderrLoggingT . filterLogger (const (> LevelDebug)) . withSqlitePool (T.pack fp) 1 . runReaderT |
| 46 | 79 | ||
| 47 | printers = [ ( pure $ PM tPM | 80 | printers = [ ( pure $ S.PM tPM |
| 48 | , QMConfig (join . lift $ takeTMVar (manage tManager)) (Nat $ liftIO . runIdentityT) | 81 | , S.QMConfig ((join . lift $ takeTMVar (manage tManager) <* signalTSem (ran tManager)) >> return 0) (Nat $ liftIO . runIdentityT) |
| 49 | ) | 82 | ) |
| 50 | ] | 83 | ] |
| 51 | 84 | ||
| 52 | tPM :: MonadIO m => Printout -> m (Maybe PrintingError) | 85 | tPM :: MonadIO m => Printout -> m (Maybe PrintingError) |
| 53 | tPM printout = liftIO . atomically $ writeTChan (outputChan tPrinter) printout >> tryTakeTMVar (failSwitch tPrinter) | 86 | tPM printout = liftIO . atomically $ putTMVar (outputChan tPrinter) printout >> tryTakeTMVar (failSwitch tPrinter) |
| 54 | (,,,) <$> forkFinally (thermoprintServer False (Nat runSqlite) $ def `withPrinters` printers) (const $ signalQSem termSem) <*> pure termSem <*> pure tPrinter <*> pure tManager | 87 | RunningServer <$> forkFinally (S.thermoprintServer False (Nat runSqlite) $ def' `S.withPrinters` printers) (const $ signalQSem termSem) <*> pure termSem <*> pure tPrinter <*> pure tManager |
| 55 | 88 | where | |
| 56 | withSetup :: SpecWith (ThreadId, QSem, TestPrinter, TestManager) -> Spec | 89 | def' :: MonadIO m => S.Config m |
| 57 | withSetup = beforeAll setup . afterAll (\(tId, termSem, _, _) -> killThread tId >> waitQSem termSem) | 90 | def' = S.def { S.warpSettings = setBeforeMainLoop (signalQSem startup) $ defaultSettings } |
| 91 | |||
| 92 | withSetup :: SpecWith RunningServer -> Spec | ||
| 93 | withSetup = beforeAll setup' . afterAll teardown | ||
| 94 | where | ||
| 95 | setup' = do | ||
| 96 | startup <- newQSem 0 | ||
| 97 | setup startup <* waitQSem startup | ||
| 98 | teardown RunningServer{..} = killThread thread >> waitQSem termination | ||
| 58 | 99 | ||
| 59 | spec :: Spec | 100 | spec :: Spec |
| 60 | spec = withSetup $ do | 101 | spec = withSetup $ do |
| 61 | describe "blubTests" $ do | 102 | it "Reports initial server state" $ \RunningServer{..} -> do |
| 62 | it "prints Blub." $ \(tId, _, _, _) -> do | 103 | printers `shouldReturn` [(0, Available)] |
| 63 | threadDelay 5000 | 104 | jobs Nothing Nothing Nothing `shouldReturn` [] |
| 64 | putStrLn "Blub." | 105 | drafts `shouldReturn` [] |
| 65 | System.IO.print tId | 106 | it "Reports printing errors" $ \RunningServer{..} -> do |
| 66 | True `shouldSatisfy` id | 107 | let |
| 108 | err = IOError "test" | ||
| 109 | atomically $ putTMVar (failSwitch printer) err | ||
| 110 | jId <- jobCreate Nothing mempty | ||
| 111 | atomically . takeTMVar $ outputChan printer | ||
| 112 | jobStatus jId `shouldReturn` (Failed err) | ||
| 113 | -- it "Queues any Printout" $ \RunningServer{..} -> property $ \p -> do | ||
| 114 | -- jId <- jobCreate (Just 0) p | ||
| 115 | -- (atomically . takeTMVar . outputChan $ printer) `shouldReturn` p | ||
| 116 | it "Reports qualitative queue position" $ \RunningServer{..} -> do | ||
| 117 | jids <- replicateM 3 $ jobCreate (Just 0) mempty | ||
| 118 | zipWithM_ (\jid ret -> jobStatus jid `shouldReturn` ret) jids | ||
| 119 | [ Done | ||
| 120 | , Printing 0 | ||
| 121 | , Queued 0 | ||
| 122 | ] | ||
| 123 | replicateM_ (length jids) . atomically . takeTMVar . outputChan $ printer | ||
| 124 | zipWithM_ (\jid ret -> jobStatus jid `shouldReturn` ret) jids (replicate (length jids) Done) | ||
| 125 | it "Keeps history" $ \RunningServer{..} -> do | ||
| 126 | jobs Nothing Nothing Nothing `shouldNotReturn` [] | ||
| 127 | it "Runs queue managers" $ \RunningServer{..} -> do | ||
| 128 | atomically $ putTMVar (manage manager) S.nullQM | ||
| 129 | atomically $ waitTSem (ran manager) | ||
| 130 | jobs Nothing Nothing Nothing `shouldReturn` [] | ||
| 131 | it "Handles drafts" $ \RunningServer{..} -> do | ||
| 132 | drafts `shouldReturn` [] | ||
| 133 | dId <- draftCreate Nothing mempty | ||
| 134 | draft dId `shouldReturn` (Nothing, mempty) | ||
| 135 | drafts `shouldReturn` [(dId, mempty)] | ||
| 136 | p <- generate arbitrary | ||
| 137 | draftReplace dId (Just "Title") p | ||
| 138 | draft dId `shouldReturn` (Just "Title", p) | ||
| 139 | jId <- draftPrint dId Nothing | ||
| 140 | (atomically . takeTMVar $ outputChan printer) `shouldReturn` p | ||
| 141 | draftDelete dId | ||
| 142 | drafts `shouldReturn` [] | ||
| 143 | where | ||
| 144 | Client{..} = mkClient' $ BaseUrl Http "localhost" 3000 | ||
| 145 | |||
| 146 | |||
