From fff9cbfc9e7919723349e18c4b9aea89bcc48c1a Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 17 Feb 2016 01:05:57 +0000 Subject: Harness for tests of Thermoprint.Server --- server/test/Thermoprint/ServerSpec.hs | 59 +++++++++++++++++++++++++++++++++++ 1 file changed, 59 insertions(+) create mode 100644 server/test/Thermoprint/ServerSpec.hs (limited to 'server/test/Thermoprint') 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 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ImpredicativeTypes #-} + +module Thermoprint.ServerSpec (spec) where + +import Test.HUnit +import Test.Hspec +import Test.Hspec.Contrib.HUnit + +import Thermoprint.API +import Thermoprint.Server + +import Control.Monad +import Control.Monad.Logger +import Control.Monad.Reader +import Control.Monad.Trans.Identity +import Control.Monad.Trans.Resource + +import Database.Persist.Sqlite + +import Control.Concurrent +import Control.Concurrent.STM + +import System.IO +import System.IO.Temp + +import qualified Data.Text as T + +data TestPrinter = TestPrinter + { outputChan :: TChan Printout + , failSwitch :: TMVar PrintingError + } + +data TestManager = TestManager + { manage :: TMVar (QueueManager IdentityT) + } + +setup :: IO (ThreadId, TestPrinter, TestManager) +setup = withSystemTempFile "thermoprint.sqlite" $ \fp h -> hClose h >> do + tPrinter <- TestPrinter <$> newTChanIO <*> newEmptyTMVarIO + tManager <- TestManager <$> newEmptyTMVarIO + let + runSqlite :: ReaderT ConnectionPool (LoggingT IO) a -> IO a + runSqlite = runStderrLoggingT . withSqlitePool (T.pack fp) 1 . runReaderT + + printers = [ ( pure $ PM tPM + , QMConfig (join . lift $ takeTMVar (manage tManager)) (Nat $ liftIO . runIdentityT) + ) + ] + + tPM :: MonadIO m => Printout -> m (Maybe PrintingError) + tPM printout = liftIO . atomically $ writeTChan (outputChan tPrinter) printout >> tryTakeTMVar (failSwitch tPrinter) + (,,) <$> forkIO (thermoprintServer (Nat runSqlite) $ def `withPrinters` printers) <*> pure tPrinter <*> pure tManager + +spec :: Spec +spec = do + fromHUnitTest . test . ("blub" ~:) $ do + putStrLn "Blub." + return True -- cgit v1.2.3