diff options
Diffstat (limited to 'server/test/Thermoprint')
-rw-r--r-- | server/test/Thermoprint/ServerSpec.hs | 59 |
1 files changed, 59 insertions, 0 deletions
diff --git a/server/test/Thermoprint/ServerSpec.hs b/server/test/Thermoprint/ServerSpec.hs new file mode 100644 index 0000000..aa654b1 --- /dev/null +++ b/server/test/Thermoprint/ServerSpec.hs | |||
@@ -0,0 +1,59 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | {-# LANGUAGE ImpredicativeTypes #-} | ||
3 | |||
4 | module Thermoprint.ServerSpec (spec) where | ||
5 | |||
6 | import Test.HUnit | ||
7 | import Test.Hspec | ||
8 | import Test.Hspec.Contrib.HUnit | ||
9 | |||
10 | import Thermoprint.API | ||
11 | import Thermoprint.Server | ||
12 | |||
13 | import Control.Monad | ||
14 | import Control.Monad.Logger | ||
15 | import Control.Monad.Reader | ||
16 | import Control.Monad.Trans.Identity | ||
17 | import Control.Monad.Trans.Resource | ||
18 | |||
19 | import Database.Persist.Sqlite | ||
20 | |||
21 | import Control.Concurrent | ||
22 | import Control.Concurrent.STM | ||
23 | |||
24 | import System.IO | ||
25 | import System.IO.Temp | ||
26 | |||
27 | import qualified Data.Text as T | ||
28 | |||
29 | data TestPrinter = TestPrinter | ||
30 | { outputChan :: TChan Printout | ||
31 | , failSwitch :: TMVar PrintingError | ||
32 | } | ||
33 | |||
34 | data TestManager = TestManager | ||
35 | { manage :: TMVar (QueueManager IdentityT) | ||
36 | } | ||
37 | |||
38 | setup :: IO (ThreadId, TestPrinter, TestManager) | ||
39 | setup = withSystemTempFile "thermoprint.sqlite" $ \fp h -> hClose h >> do | ||
40 | tPrinter <- TestPrinter <$> newTChanIO <*> newEmptyTMVarIO | ||
41 | tManager <- TestManager <$> newEmptyTMVarIO | ||
42 | let | ||
43 | runSqlite :: ReaderT ConnectionPool (LoggingT IO) a -> IO a | ||
44 | runSqlite = runStderrLoggingT . withSqlitePool (T.pack fp) 1 . runReaderT | ||
45 | |||
46 | printers = [ ( pure $ PM tPM | ||
47 | , QMConfig (join . lift $ takeTMVar (manage tManager)) (Nat $ liftIO . runIdentityT) | ||
48 | ) | ||
49 | ] | ||
50 | |||
51 | tPM :: MonadIO m => Printout -> m (Maybe PrintingError) | ||
52 | tPM printout = liftIO . atomically $ writeTChan (outputChan tPrinter) printout >> tryTakeTMVar (failSwitch tPrinter) | ||
53 | (,,) <$> forkIO (thermoprintServer (Nat runSqlite) $ def `withPrinters` printers) <*> pure tPrinter <*> pure tManager | ||
54 | |||
55 | spec :: Spec | ||
56 | spec = do | ||
57 | fromHUnitTest . test . ("blub" ~:) $ do | ||
58 | putStrLn "Blub." | ||
59 | return True | ||