aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-02-18 21:59:00 +0000
committerGregor Kleen <gkleen@yggdrasil.li>2016-02-18 21:59:00 +0000
commit55074a07fdb847749e4f57c6c2eac4ffab1d48b6 (patch)
tree5cd211775cf84fffa934a17ce276be2d6b3990f6
parent2d16ad6786e6047fc61b34e6bd7e59e794a9d5a3 (diff)
downloadthermoprint-55074a07fdb847749e4f57c6c2eac4ffab1d48b6.tar
thermoprint-55074a07fdb847749e4f57c6c2eac4ffab1d48b6.tar.gz
thermoprint-55074a07fdb847749e4f57c6c2eac4ffab1d48b6.tar.bz2
thermoprint-55074a07fdb847749e4f57c6c2eac4ffab1d48b6.tar.xz
thermoprint-55074a07fdb847749e4f57c6c2eac4ffab1d48b6.zip
Api tests for Thermoprint.Server
-rw-r--r--default.nix2
-rw-r--r--server/src/Thermoprint/Server/Queue.hs19
-rw-r--r--server/test/Thermoprint/Server/QueueSpec.hs13
-rw-r--r--server/test/Thermoprint/ServerSpec.hs126
-rw-r--r--server/thermoprint-server.cabal7
-rw-r--r--server/thermoprint-server.nix13
-rw-r--r--spec/src/Thermoprint/API.hs17
7 files changed, 153 insertions, 44 deletions
diff --git a/default.nix b/default.nix
index 6fe42e3..52ecd20 100644
--- a/default.nix
+++ b/default.nix
@@ -12,7 +12,7 @@ rec {
12 thermoprint-server = pkgs.callPackage ./server/wrapped.nix { 12 thermoprint-server = pkgs.callPackage ./server/wrapped.nix {
13 inherit (pkgs.haskellPackages) ghcWithPackages; 13 inherit (pkgs.haskellPackages) ghcWithPackages;
14 thermoprint-server = pkgs.haskellPackages.callPackage ./server/thermoprint-server.nix { 14 thermoprint-server = pkgs.haskellPackages.callPackage ./server/thermoprint-server.nix {
15 inherit thermoprint-spec; 15 inherit thermoprint-spec thermoprint-client;
16 }; 16 };
17 }; 17 };
18 bbcode = pkgs.haskellPackages.callPackage ./bbcode/bbcode.nix {}; 18 bbcode = pkgs.haskellPackages.callPackage ./bbcode/bbcode.nix {};
diff --git a/server/src/Thermoprint/Server/Queue.hs b/server/src/Thermoprint/Server/Queue.hs
index cc87886..3c8fb9e 100644
--- a/server/src/Thermoprint/Server/Queue.hs
+++ b/server/src/Thermoprint/Server/Queue.hs
@@ -46,6 +46,11 @@ import Data.Foldable
46import Data.Monoid 46import Data.Monoid
47import Data.Ord 47import Data.Ord
48 48
49import Test.QuickCheck.Arbitrary (Arbitrary(..), CoArbitrary(..))
50import Test.QuickCheck.Gen (Gen, scale)
51import Test.QuickCheck.Instances
52import Test.QuickCheck.Modifiers
53
49-- | Zipper for 'Seq QueueEntry' with additional support for 'PrintingError' in the section after point 54-- | Zipper for 'Seq QueueEntry' with additional support for 'PrintingError' in the section after point
50data Queue = Queue 55data Queue = Queue
51 { pending :: Seq QueueEntry -- ^ Pending jobs, closest last 56 { pending :: Seq QueueEntry -- ^ Pending jobs, closest last
@@ -54,6 +59,14 @@ data Queue = Queue
54 } 59 }
55 deriving (Typeable, Generic, NFData, Show) 60 deriving (Typeable, Generic, NFData, Show)
56 61
62instance Arbitrary Queue where
63 arbitrary = Queue
64 <$> scale (`div` 2) arbitrary
65 <*> arbitrary
66 <*> scale (`div` 2) arbitrary
67
68instance CoArbitrary Queue
69
57class HasQueue a where 70class HasQueue a where
58 extractQueue :: a -> TVar Queue 71 extractQueue :: a -> TVar Queue
59 72
@@ -73,6 +86,12 @@ data QueueEntry = QueueEntry
73 } 86 }
74 deriving (Typeable, Generic, NFData, Eq, Ord, Show) 87 deriving (Typeable, Generic, NFData, Eq, Ord, Show)
75 88
89instance Arbitrary QueueEntry where
90 arbitrary = QueueEntry <$> (fromIntegral . getNonNegative <$> (arbitrary :: Gen (NonNegative Integer))) <*> arbitrary
91
92instance CoArbitrary QueueEntry where
93 coarbitrary QueueEntry{..} = coarbitrary created . coarbitrary (fromIntegral jobId :: Integer)
94
76data QueueItem = Pending Int QueueEntry | Current QueueEntry | History Int QueueEntry (Maybe PrintingError) 95data QueueItem = Pending Int QueueEntry | Current QueueEntry | History Int QueueEntry (Maybe PrintingError)
77 96
78instance Eq QueueItem where 97instance Eq QueueItem where
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
16deriving instance (Eq PrintingError) 16deriving instance (Eq PrintingError)
17deriving instance (Eq Queue) 17deriving instance (Eq Queue)
18 18
19instance Arbitrary Queue where
20 arbitrary = Queue <$> arbitrary <*> arbitrary <*> arbitrary
21
22instance Arbitrary QueueEntry where
23 arbitrary = QueueEntry <$> arbitrary <*> arbitrary
24
25instance Arbitrary PrintingError where
26 arbitrary = oneof [ return (IOError "dummy")
27 ]
28
29instance Arbitrary JobId where
30 arbitrary = castId . getNonNegative <$> (arbitrary :: Gen (NonNegative Integer))
31
32spec :: Spec 19spec :: Spec
33spec = do 20spec = 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
4module Thermoprint.ServerSpec (spec) where 7module Thermoprint.ServerSpec (spec) where
5 8
6import Test.Hspec 9import Test.Hspec
10import Test.Hspec.QuickCheck
11import qualified Test.Hspec as Hspec
12
13import Test.QuickCheck
7 14
8import Thermoprint.API 15import Thermoprint.API
9import Thermoprint.Server 16import qualified Thermoprint.Server as S
17import Thermoprint.Client
10 18
19import Data.Monoid
20import Data.Function
11import Control.Monad 21import Control.Monad
12import Control.Monad.Logger 22import Control.Monad.Logger
13import Control.Monad.Reader 23import Control.Monad.Reader
24import Control.Monad.State
14import Control.Monad.Trans.Identity 25import Control.Monad.Trans.Identity
15import Control.Monad.Trans.Resource 26import Control.Monad.Trans.Resource
27import Control.Monad.Catch (finally)
16 28
17import Database.Persist.Sqlite 29import Database.Persist.Sqlite
18 30
19import Control.Concurrent 31import Control.Concurrent
20import Control.Concurrent.STM 32import Control.Concurrent.STM
33import Control.Concurrent.STM.TSem
21 34
22import System.IO 35import System.IO
23import System.IO.Temp 36import System.IO.Temp
24 37
25import qualified Data.Text as T 38import qualified Data.Text as T
26 39
27import Debug.Trace 40import Network.Wai.Handler.Warp (defaultSettings, setBeforeMainLoop)
41
42import qualified Data.Map as Map
43
44deriving instance Eq PrintingError
45deriving instance Eq JobStatus
46deriving instance Eq PrinterStatus
47
48-- Equality via cotext on Block
49instance Eq Block where
50 (==) = (==) `on` cotext
51-- Structural equality for Chunk
52deriving instance Eq Chunk
28 53
29data TestPrinter = TestPrinter 54data TestPrinter = TestPrinter
30 { outputChan :: TChan Printout 55 { outputChan :: TMVar Printout
31 , failSwitch :: TMVar PrintingError 56 , failSwitch :: TMVar PrintingError
32 } 57 }
33 58
34data TestManager = TestManager 59data TestManager = TestManager
35 { manage :: TMVar (QueueManager IdentityT) 60 { manage :: TMVar (S.QueueManager IdentityT)
61 , ran :: TSem
36 } 62 }
37 63
38setup :: IO (ThreadId, QSem, TestPrinter, TestManager) 64data RunningServer = RunningServer
39setup = 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
71setup :: QSem -> IO RunningServer
72setup 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
56withSetup :: SpecWith (ThreadId, QSem, TestPrinter, TestManager) -> Spec 89 def' :: MonadIO m => S.Config m
57withSetup = beforeAll setup . afterAll (\(tId, termSem, _, _) -> killThread tId >> waitQSem termSem) 90 def' = S.def { S.warpSettings = setBeforeMainLoop (signalQSem startup) $ defaultSettings }
91
92withSetup :: SpecWith RunningServer -> Spec
93withSetup = 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
59spec :: Spec 100spec :: Spec
60spec = withSetup $ do 101spec = 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
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal
index cfef947..7afcb55 100644
--- a/server/thermoprint-server.cabal
+++ b/server/thermoprint-server.cabal
@@ -55,6 +55,8 @@ library
55 , bytestring >=0.10.6 && <1 55 , bytestring >=0.10.6 && <1
56 , encoding >=0.8 && <1 56 , encoding >=0.8 && <1
57 , binary >=0.7.5 && <1 57 , binary >=0.7.5 && <1
58 , QuickCheck >=2.8.1 && <3
59 , quickcheck-instances >=0.3.11 && <4
58 hs-source-dirs: src 60 hs-source-dirs: src
59 default-language: Haskell2010 61 default-language: Haskell2010
60 62
@@ -63,7 +65,8 @@ Test-Suite tests
63 hs-source-dirs: test 65 hs-source-dirs: test
64 main-is: Spec.hs 66 main-is: Spec.hs
65 build-depends: base >=4.8.1 && <5 67 build-depends: base >=4.8.1 && <5
66 , thermoprint-server -any 68 , thermoprint-server ==0.0.*
69 , thermoprint-client ==0.0.*
67 , thermoprint-spec -any 70 , thermoprint-spec -any
68 , hspec >=2.2.1 && <3 71 , hspec >=2.2.1 && <3
69 , QuickCheck >=2.8.1 && <3 72 , QuickCheck >=2.8.1 && <3
@@ -76,6 +79,8 @@ Test-Suite tests
76 , persistent-sqlite >=2.2 && <3 79 , persistent-sqlite >=2.2 && <3
77 , text >=1.2.1 && <2 80 , text >=1.2.1 && <2
78 , stm >=2.4.4 && <3 81 , stm >=2.4.4 && <3
82 , warp >=3.1.9 && <4
83 , exceptions >=0.8.0 && <1
79 84
80executable thermoprint-server 85executable thermoprint-server
81 main-is: Main.hs 86 main-is: Main.hs
diff --git a/server/thermoprint-server.nix b/server/thermoprint-server.nix
index 737f571..d7a7684 100644
--- a/server/thermoprint-server.nix
+++ b/server/thermoprint-server.nix
@@ -1,10 +1,10 @@
1{ mkDerivation, base, binary, bytestring, conduit, containers 1{ mkDerivation, base, binary, bytestring, conduit, containers
2, data-default-class, deepseq, dyre, either, encoding, exceptions 2, data-default-class, deepseq, dyre, either, encoding, exceptions
3, extended-reals, filelock, hspec, hspec-contrib, HUnit, mmorph 3, extended-reals, filelock, hspec, mmorph, monad-control
4, monad-control, monad-logger, mtl, persistent, persistent-sqlite 4, monad-logger, mtl, persistent, persistent-sqlite
5, persistent-template, QuickCheck, quickcheck-instances, resourcet 5, persistent-template, QuickCheck, quickcheck-instances, resourcet
6, servant-server, stdenv, stm, temporary, text, thermoprint-spec 6, servant-server, stdenv, stm, temporary, text, thermoprint-client
7, time, transformers, wai, warp 7, thermoprint-spec, time, transformers, wai, warp
8}: 8}:
9mkDerivation { 9mkDerivation {
10 pname = "thermoprint-server"; 10 pname = "thermoprint-server";
@@ -23,8 +23,9 @@ mkDerivation {
23 base monad-logger mtl persistent-sqlite resourcet 23 base monad-logger mtl persistent-sqlite resourcet
24 ]; 24 ];
25 testHaskellDepends = [ 25 testHaskellDepends = [
26 base hspec hspec-contrib HUnit QuickCheck quickcheck-instances 26 base exceptions hspec monad-logger mtl persistent-sqlite QuickCheck
27 temporary thermoprint-spec 27 quickcheck-instances resourcet stm temporary text
28 thermoprint-client thermoprint-spec transformers warp
28 ]; 29 ];
29 homepage = "http://dirty-haskell.org/tags/thermoprint.html"; 30 homepage = "http://dirty-haskell.org/tags/thermoprint.html";
30 description = "Server for thermoprint-spec"; 31 description = "Server for thermoprint-spec";
diff --git a/spec/src/Thermoprint/API.hs b/spec/src/Thermoprint/API.hs
index 5bfe431..3ffd239 100644
--- a/spec/src/Thermoprint/API.hs
+++ b/spec/src/Thermoprint/API.hs
@@ -50,6 +50,10 @@ import Data.Time.Format
50 50
51import Data.Encoding.Exception (EncodingException(..)) 51import Data.Encoding.Exception (EncodingException(..))
52 52
53import Test.QuickCheck.Arbitrary (Arbitrary(..), CoArbitrary(..))
54import Test.QuickCheck.Gen (scale, variant, oneof)
55import Test.QuickCheck.Instances
56
53instance (Integral k, Ord k, ToJSON v) => ToJSON (Map k v) where 57instance (Integral k, Ord k, ToJSON v) => ToJSON (Map k v) where
54 toJSON = toJSON . Map.foldMapWithKey (IntMap.singleton . castId) 58 toJSON = toJSON . Map.foldMapWithKey (IntMap.singleton . castId)
55 59
@@ -75,6 +79,13 @@ data PrintingError = IOError String -- ^ Not the actual error because we can't m
75 | EncError EncodingException -- ^ Could not encode some part of the 'Printout' 79 | EncError EncodingException -- ^ Could not encode some part of the 'Printout'
76 deriving (Typeable, Generic, NFData, Show, FromJSON, ToJSON) 80 deriving (Typeable, Generic, NFData, Show, FromJSON, ToJSON)
77 81
82instance Arbitrary PrintingError where
83 arbitrary = IOError <$> arbitrary
84
85instance CoArbitrary PrintingError where
86 coarbitrary (IOError _) = variant 0
87 coarbitrary (EncError _) = variant 1
88
78instance Exception PrintingError 89instance Exception PrintingError
79 90
80type DraftTitle = Text 91type DraftTitle = Text
@@ -87,6 +98,12 @@ instance ToText UTCTime where
87 98
88data Range a = Min a | Max a | Through a a 99data Range a = Min a | Max a | Through a a
89 100
101instance Arbitrary a => Arbitrary (Range a) where
102 arbitrary = oneof [ Min <$> arbitrary
103 , Max <$> arbitrary
104 , Through <$> arbitrary <*> arbitrary
105 ]
106
90contains :: Ord a => Range a -> a -> Bool 107contains :: Ord a => Range a -> a -> Bool
91-- ^ Check if a 'Range' contains a point 108-- ^ Check if a 'Range' contains a point
92contains (Min min) x = min <= x 109contains (Min min) x = min <= x