module Snap.Test.BDD
(
SnapTesting
, TestResult(..)
, Sentiment(..)
, TestResponse(..)
, SnapTestingConfig (..)
, defaultConfig
, runSnapTests
, consoleReport
, linuxDesktopReport
, name
, should
, shouldNot
, css
, val
, get
, get'
, post
, params
, equal
, beTrue
, succeed
, notfound
, redirect
, redirectTo
, haveText
, haveSelector
, changes
, FormExpectations(..)
, form
, cleanup
, eval
, modifySite
, quickCheck
) where
import Prelude hiding (FilePath, log)
import Data.Map (Map)
import qualified Data.Map as M (lookup, mapKeys, empty, fromList)
import Data.ByteString (ByteString)
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T (append, concat, isInfixOf)
import Data.Text.Encoding (encodeUtf8, decodeUtf8)
import Data.Maybe (fromMaybe)
import Data.List (intercalate, intersperse)
import Control.Applicative
import Control.Monad (void)
import Control.Monad.Trans
import Control.Monad.Trans.State (StateT, evalStateT)
import qualified Control.Monad.Trans.State as S (get, put)
import Control.Exception (SomeException, catch)
import Control.Concurrent.Async
import System.Process (system)
import Snap.Core (Response(..), getHeader)
import Snap.Snaplet (Handler, SnapletInit, Snaplet)
import Snap.Test (RequestBuilder, getResponseBody)
import qualified Snap.Test as Test
import Snap.Snaplet.Test (runHandler', evalHandler', getSnaplet
, closeSnaplet, InitializerState)
import Test.QuickCheck (Args(..), Result(..), Testable, quickCheckWithResult, stdArgs)
import System.IO.Streams (InputStream, OutputStream)
import qualified System.IO.Streams as Stream
import qualified System.IO.Streams.Concurrent as Stream
import qualified Text.Digestive as DF
import qualified Text.HandsomeSoup as HS
import qualified Text.XML.HXT.Core as HXT
type SnapTesting b a = StateT (Handler b b ()
, (Snaplet b, InitializerState b)
, OutputStream TestResult) IO a
data TestResponse = Html Text | NotFound | Redirect Int Text | Other Int | Empty
data CssSelector = CssSelector Text
data Sentiment a = Positive a | Negative a deriving Show
flipSentiment :: Sentiment a -> Sentiment a
flipSentiment (Positive a) = Negative a
flipSentiment (Negative a) = Positive a
data TestResult = NameStart Text
| NameEnd
| TestPass (Sentiment Text)
| TestFail (Sentiment Text)
| TestError Text deriving Show
data SnapTestingConfig = SnapTestingConfig { reportGenerators :: [InputStream TestResult -> IO ()]
}
defaultConfig :: SnapTestingConfig
defaultConfig = SnapTestingConfig { reportGenerators = [consoleReport]
}
dupN :: Int -> InputStream a -> IO [InputStream a]
dupN 0 _ = return []
dupN 1 s = return [s]
dupN n s = do (a, b) <- Stream.map (\x -> (x,x)) s >>= Stream.unzip
rest <- dupN (n 1) b
return (a:rest)
runSnapTests :: SnapTestingConfig
-> Handler b b ()
-> SnapletInit b b
-> SnapTesting b ()
-> IO ()
runSnapTests conf site app tests = do
(inp, out) <- Stream.makeChanPipe
let rgs = reportGenerators conf
istreams <- dupN (length rgs) inp
consumers <- mapM (\(inp', hndl) -> async (hndl inp')) (zip istreams rgs)
init <- getSnaplet (Just "test") app
case init of
Left err -> error $ show err
Right (snaplet, initstate) -> do
evalStateT tests (site, (snaplet, initstate), out)
Stream.write Nothing out
mapM_ wait consumers
closeSnaplet initstate
return ()
consoleReport :: InputStream TestResult -> IO ()
consoleReport stream = cr 0
where cr indent = do log <- Stream.read stream
case log of
Nothing -> putStrLn "" >> return ()
Just (NameStart n) -> do putStrLn ""
printIndent indent
putStr (unpack n)
cr (indent + indentUnit)
Just NameEnd -> cr (indent indentUnit)
Just (TestPass _) -> do putStr " PASSED"
cr indent
Just (TestFail msg) -> do putStr " FAILED\n"
printMessage indent msg
cr indent
Just (TestError msg) -> do putStr " ERROR("
putStr (unpack msg)
putStr ")"
cr indent
indentUnit = 2
printIndent n = putStr (replicate n ' ')
printMessage n (Positive m) = do printIndent n
putStrLn "Should have held:"
printIndent n
putStrLn (unpack m)
printMessage n (Negative m) = do printIndent n
putStrLn "Should not have held:"
printIndent n
putStrLn (unpack m)
linuxDesktopReport :: InputStream TestResult -> IO ()
linuxDesktopReport stream = do
res <- Stream.toList stream
let (failing, total) = count [] res
case failing of
[] ->
void $ system $ "notify-send -u low -t 2000 'All Tests Passing' 'All " ++
(show total) ++ " tests passed.'"
_ ->
void $ system $ "notify-send -u normal -t 2000 'Some Tests Failing' '" ++
(show (length failing)) ++ " out of " ++
(show total) ++ " tests failed:\n\n" ++ (intercalate "\n\n" $ reverse failing) ++ "'"
where count :: [Text] -> [TestResult] -> ([String], Int)
count _ [] = ([], 0)
count n (TestPass _ : xs) = let (f, t) = count n xs
in (f, 1 + t)
count n (TestFail _ : xs) = let (f, t) = count n xs
in (f ++ [unpack $ T.concat $ intersperse " > " $ reverse n], 1 + t)
count n (TestError _ : xs) = let (f, t) = count n xs
in (f, 1 + t)
count n (NameStart nm : xs) = count (nm:n) xs
count n (NameEnd : xs) = count (tail n) xs
writeRes :: TestResult -> SnapTesting b ()
writeRes log = do (_,_,out) <- S.get
lift $ Stream.write (Just log) out
name :: Text
-> SnapTesting b ()
-> SnapTesting b ()
name s a = do
writeRes (NameStart s)
a
writeRes NameEnd
runRequest :: RequestBuilder IO () -> SnapTesting b TestResponse
runRequest req = do
(site, app, _) <- S.get
res <- liftIO $ runHandlerSafe req site app
case res of
Left err -> do
writeRes (TestError err)
return $ Empty
Right response -> do
case rspStatus response of
404 -> return NotFound
200 -> do
body <- liftIO $ getResponseBody response
return $ Html $ decodeUtf8 body
_ -> if (rspStatus response) >= 300 && (rspStatus response) < 400
then do let url = fromMaybe "" $ getHeader "Location" response
return (Redirect (rspStatus response) (decodeUtf8 url))
else return (Other (rspStatus response))
get :: Text
-> SnapTesting b TestResponse
get = flip get' M.empty
get' :: Text
-> Map ByteString [ByteString]
-> SnapTesting b TestResponse
get' path ps = runRequest (Test.get (encodeUtf8 path) ps)
post :: Text
-> Map ByteString [ByteString]
-> SnapTesting b TestResponse
post path ps = runRequest (Test.postUrlEncoded (encodeUtf8 path) ps)
params :: [(ByteString, ByteString)]
-> Map ByteString [ByteString]
params = M.fromList . map (\x -> (fst x, [snd x]))
css :: Applicative m => Text -> m CssSelector
css = pure . CssSelector
val :: Applicative m => a -> m a
val = pure
should :: SnapTesting b TestResult -> SnapTesting b ()
should test = do res <- test
writeRes res
shouldNot :: SnapTesting b TestResult -> SnapTesting b ()
shouldNot test = do res <- test
case res of
TestPass msg -> writeRes (TestFail (flipSentiment msg))
TestFail msg -> writeRes (TestPass (flipSentiment msg))
_ -> writeRes res
haveSelector :: TestResponse -> CssSelector -> TestResult
haveSelector (Html body) (CssSelector selector) = case HXT.runLA (HXT.hread HXT.>>> HS.css (unpack selector)) (unpack body) of
[] -> TestFail msg
_ -> TestPass msg
where msg = (Positive $ T.concat ["Html contains selector: ", selector, "\n\n", body])
haveSelector _ (CssSelector match) = TestFail (Positive (T.concat ["Body contains css selector: ", match]))
haveText :: TestResponse -> Text -> TestResult
haveText (Html body) match =
if T.isInfixOf match body
then TestPass (Positive $ T.concat [body, "' contains '", match, "'."])
else TestFail (Positive $ T.concat [body, "' contains '", match, "'."])
haveText _ match = TestFail (Positive (T.concat ["Body contains: ", match]))
equal :: (Show a, Eq a)
=> a
-> a
-> TestResult
equal a b = if a == b
then TestPass (Positive (T.concat [pack $ show a, " == ", pack $ show b]))
else TestFail (Positive (T.concat [pack $ show a, " == ", pack $ show b]))
beTrue :: Bool -> TestResult
beTrue True = TestPass (Positive "assertion")
beTrue False = TestFail (Positive "assertion")
data FormExpectations a = Value a
| ErrorPaths [Text]
form :: (Eq a, Show a)
=> FormExpectations a
-> DF.Form Text (Handler b b) a
-> Map Text Text
-> SnapTesting b ()
form expected theForm theParams =
do r <- eval $ DF.postForm "form" theForm (const $ return lookupParam)
case expected of
Value a -> should $ equal <$> val (snd r) <*> val (Just a)
ErrorPaths expectedPaths ->
do let viewErrorPaths = map (DF.fromPath . fst) $ DF.viewErrors $ fst r
should $ beTrue <$> val (all (`elem` viewErrorPaths) expectedPaths
&& (length viewErrorPaths == length expectedPaths))
where lookupParam pth = case M.lookup (DF.fromPath pth) fixedParams of
Nothing -> return []
Just v -> return [DF.TextInput v]
fixedParams = M.mapKeys (T.append "form.") theParams
succeed :: TestResponse -> TestResult
succeed (Html _) = TestPass (Positive "Request 200s.")
succeed _ = TestFail (Positive "Request 200s.")
notfound :: TestResponse -> TestResult
notfound NotFound = TestPass (Positive "Request 404s.")
notfound _ = TestFail (Positive "Request 404s.")
redirect :: TestResponse -> TestResult
redirect (Redirect _ _) = TestPass (Positive "Request redirects.")
redirect _ = TestFail (Positive "Request redirects.")
redirectTo :: TestResponse
-> Text
-> TestResult
redirectTo (Redirect _ actual) expected | actual == expected = TestPass (Positive (T.concat ["Redirecting actual: ", actual, " expected: ", expected]))
redirectTo (Redirect _ actual) expected = TestFail (Positive (T.concat ["Redirecting actual: ", actual, " expected: ", expected]))
redirectTo _ expected = TestFail (Positive (T.concat ["Redirects to ", expected]))
changes :: (Show a, Eq a)
=> (a -> a)
-> Handler b b a
-> SnapTesting b c
-> SnapTesting b ()
changes delta measure act = do
before <- eval measure
_ <- act
after <- eval measure
should $ equal <$> val (delta before) <*> val after
cleanup :: Handler b b ()
-> SnapTesting b ()
-> SnapTesting b ()
cleanup cu act = do
act
(_, app, _) <- S.get
_ <- liftIO $ runHandlerSafe (Test.get "" M.empty) cu app
return ()
eval :: Handler b b a
-> SnapTesting b a
eval act = do
(_, app, _) <- S.get
liftIO $ fmap (either (error . unpack) id) $ evalHandlerSafe act app
modifySite :: (Handler b b () -> Handler b b ())
-> SnapTesting b a
-> SnapTesting b a
modifySite f act = do
(site, app, out) <- S.get
S.put (f site, app, out)
res <- act
S.put (site, app, out)
return res
quickCheck :: Testable prop => prop -> SnapTesting b ()
quickCheck p = do
res <- liftIO $ quickCheckWithResult (stdArgs { chatty = False }) p
case res of
Success{} -> writeRes (TestPass (Positive ""))
GaveUp{} -> writeRes (TestPass (Positive ""))
Failure{} -> writeRes (TestFail (Positive ""))
NoExpectedFailure{} -> writeRes (TestFail (Positive ""))
runHandlerSafe :: RequestBuilder IO ()
-> Handler b b v
-> (Snaplet b, InitializerState b)
-> IO (Either Text Response)
runHandlerSafe req site (s, is) =
catch (runHandler' s is req site) (\(e::SomeException) -> return $ Left (pack $ show e))
evalHandlerSafe :: Handler b b v
-> (Snaplet b, InitializerState b)
-> IO (Either Text v)
evalHandlerSafe act (s, is) =
catch (evalHandler' s is (Test.get "" M.empty) act) (\(e::SomeException) -> return $ Left (pack $ show e))