Strip CRs for Windows testing
This commit is contained in:
parent
3b58652483
commit
3647bf94b7
@ -8,6 +8,7 @@ import Language.Haskell.TH
|
||||
import Test.HUnit
|
||||
import Yesod.EmbeddedStatic.Types as Y
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import RIO (HasCallStack)
|
||||
|
||||
-- We test the generators by executing them at compile time
|
||||
-- and sticking the result into the GenTestResult. We then
|
||||
@ -28,11 +29,15 @@ testEntry name _ _ e | ebHaskellName e /= (mkName Control.Applicative.<$> name)
|
||||
testEntry _ loc _ e | ebLocation e /= loc =
|
||||
[| GenError ("location " ++ $(litE $ stringL $ show $ ebLocation e)) |]
|
||||
testEntry _ _ act e = do
|
||||
expected <- runIO act
|
||||
actual <- runIO $ ebProductionContent e
|
||||
expected <- fmap stripCR $ runIO act
|
||||
actual <- fmap stripCR $ runIO $ ebProductionContent e
|
||||
if expected == actual
|
||||
then [| GenSuccessWithDevel $(ebDevelReload e) |]
|
||||
else [| GenError "production content" |]
|
||||
else [| GenError $ "production content: " ++ $(litE $ stringL $ show (expected, actual)) |]
|
||||
|
||||
-- | Remove all carriage returns, for Windows testing
|
||||
stripCR :: BL.ByteString -> BL.ByteString
|
||||
stripCR = BL.filter (/= 13)
|
||||
|
||||
testOneEntry :: Maybe String -> Y.Location -> IO BL.ByteString -> [Entry] -> ExpQ
|
||||
testOneEntry name loc ct [e] = testEntry name loc ct e
|
||||
@ -48,12 +53,13 @@ testEntries a b = listE $ zipWith f a' b'
|
||||
f (name, loc, ct) e = testEntry name loc ct e
|
||||
|
||||
-- | Use this at runtime to assert the 'GenTestResult' is OK
|
||||
assertGenResult :: (IO BL.ByteString) -- ^ expected development content
|
||||
assertGenResult :: HasCallStack
|
||||
=> (IO BL.ByteString) -- ^ expected development content
|
||||
-> GenTestResult -- ^ test result created at compile time
|
||||
-> Assertion
|
||||
assertGenResult _ (GenError e) = assertFailure ("invalid " ++ e)
|
||||
assertGenResult mexpected (GenSuccessWithDevel mactual) = do
|
||||
expected <- mexpected
|
||||
actual <- mactual
|
||||
expected <- fmap stripCR mexpected
|
||||
actual <- fmap stripCR mactual
|
||||
when (expected /= actual) $
|
||||
assertFailure "invalid devel content"
|
||||
assertFailure $ "invalid devel content: " ++ show (expected, actual)
|
||||
|
||||
@ -115,6 +115,7 @@ test-suite tests
|
||||
, wai
|
||||
, wai-app-static
|
||||
, yesod-core
|
||||
, rio
|
||||
|
||||
ghc-options: -Wall -threaded
|
||||
extensions: TemplateHaskell
|
||||
|
||||
Loading…
Reference in New Issue
Block a user