Use CPP hackery to make it compile with ghc-8.0 and ghc 7.10. If
ghc-7.10 works, I assume earlier supported versions of GHC also
work. All tests pass with both GHC versions.
Unfortunately, the TH changes force changes in the type signature
of Yesod.Routes.TH.RenderRoute.mkRouteCons from:
mkRouteCons :: [ResourceTree Type] -> ([Con], [Dec])
to
mkRouteCons :: [ResourceTree Type] -> Q ([Con], [Dec])
and I can't see a way around that.
51 lines
1.2 KiB
Haskell
51 lines
1.2 KiB
Haskell
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
module YesodCoreTest.Exceptions (exceptionsTest, Widget) where
|
|
|
|
import Test.Hspec
|
|
|
|
import Yesod.Core
|
|
import Network.Wai
|
|
import Network.Wai.Test
|
|
import Network.HTTP.Types (status301)
|
|
|
|
data Y = Y
|
|
mkYesod "Y" [parseRoutes|
|
|
/ RootR GET
|
|
/redirect RedirR GET
|
|
|]
|
|
|
|
instance Yesod Y where
|
|
approot = ApprootStatic "http://test"
|
|
errorHandler (InternalError e) = return $ toTypedContent e
|
|
errorHandler x = defaultErrorHandler x
|
|
|
|
getRootR :: Handler ()
|
|
getRootR = error "FOOBAR" >> return ()
|
|
|
|
getRedirR :: Handler ()
|
|
getRedirR = do
|
|
addHeader "foo" "bar"
|
|
redirectWith status301 RootR
|
|
|
|
exceptionsTest :: Spec
|
|
exceptionsTest = describe "Test.Exceptions" $ do
|
|
it "500" case500
|
|
it "redirect keeps headers" caseRedirect
|
|
|
|
runner :: Session () -> IO ()
|
|
runner f = toWaiApp Y >>= runSession f
|
|
|
|
case500 :: IO ()
|
|
case500 = runner $ do
|
|
res <- request defaultRequest
|
|
assertStatus 500 res
|
|
assertBodyContains "FOOBAR" res
|
|
|
|
caseRedirect :: IO ()
|
|
caseRedirect = runner $ do
|
|
res <- request defaultRequest { pathInfo = ["redirect"] }
|
|
assertStatus 301 res
|
|
assertHeader "foo" "bar" res
|