convert to hspec

This commit is contained in:
Greg Weber 2011-08-14 19:30:02 -07:00
parent 016d6e76f5
commit 7bece4c246
8 changed files with 54 additions and 50 deletions

View File

@ -3,14 +3,14 @@
{-# LANGUAGE FlexibleInstances #-}
module Test.CleanPath (cleanPathTest) where
import Test.Hspec
import Test.Hspec.HUnit
import Yesod.Core hiding (Request)
import Yesod.Content
import Yesod.Dispatch
import Yesod.Handler (Route)
import Test.Framework (defaultMain, testGroup, Test)
import Test.Framework.Providers.HUnit
import Test.HUnit hiding (Test)
import Network.Wai
import Network.Wai.Test
import Network.HTTP.Types (status200, decodePathSegments)
@ -57,15 +57,16 @@ getFooStringR = return . RepPlain . toContent
getBarR = return $ RepPlain "bar"
getPlainR = return $ RepPlain "plain"
cleanPathTest :: Test
cleanPathTest = testGroup "Test.CleanPath"
[ testCase "remove trailing slash" removeTrailingSlash
, testCase "noTrailingSlash" noTrailingSlash
, testCase "add trailing slash" addTrailingSlash
, testCase "has trailing slash" hasTrailingSlash
, testCase "/foo/something" fooSomething
, testCase "subsite dispatch" subsiteDispatch
, testCase "redirect with query string" redQueryString
cleanPathTest :: IO [IO Spec]
cleanPathTest =
describe "Test.CleanPath"
[ it "remove trailing slash" removeTrailingSlash
, it "noTrailingSlash" noTrailingSlash
, it "add trailing slash" addTrailingSlash
, it "has trailing slash" hasTrailingSlash
, it "/foo/something" fooSomething
, it "subsite dispatch" subsiteDispatch
, it "redirect with query string" redQueryString
]
runner f = toWaiApp Y >>= runSession f

View File

@ -3,14 +3,14 @@
{-# LANGUAGE FlexibleInstances #-}
module Test.Exceptions (exceptionsTest) where
import Test.Hspec
import Test.Hspec.HUnit
import Yesod.Core hiding (Request)
import Yesod.Content
import Yesod.Dispatch
import Yesod.Handler (Route, ErrorResponse (InternalError))
import Test.Framework (defaultMain, testGroup, Test)
import Test.Framework.Providers.HUnit
import Test.HUnit hiding (Test)
import Network.Wai
import Network.Wai.Test
@ -28,9 +28,9 @@ instance Yesod Y where
getRootR = error "FOOBAR" >> return ()
exceptionsTest :: Test
exceptionsTest = testGroup "Test.Exceptions"
[ testCase "500" case500
exceptionsTest :: IO [IO Spec]
exceptionsTest = describe "Test.Exceptions"
[ it "500" case500
]
runner f = toWaiApp Y >>= runSession f

View File

@ -3,12 +3,12 @@
{-# LANGUAGE FlexibleInstances #-}
module Test.Links (linksTest) where
import Test.Hspec
import Test.Hspec.HUnit
import Yesod.Core hiding (Request)
import Text.Hamlet
import Test.Framework (defaultMain, testGroup, Test)
import Test.Framework.Providers.HUnit
import Test.HUnit hiding (Test)
import Network.Wai
import Network.Wai.Test
@ -24,9 +24,9 @@ instance Yesod Y where
getRootR = defaultLayout $ addHamlet [$hamlet|<a href=@{RootR}>|]
linksTest :: Test
linksTest = testGroup "Test.Links"
[ testCase "linkToHome" case_linkToHome
linksTest :: IO [IO Spec]
linksTest = describe "Test.Links"
[ it "linkToHome" case_linkToHome
]
runner f = toWaiApp Y >>= runSession f

View File

@ -3,11 +3,11 @@
{-# LANGUAGE FlexibleInstances #-}
module Test.Media (mediaTest) where
import Test.Hspec
import Test.Hspec.HUnit
import Yesod.Core hiding (Request)
import Test.Framework (defaultMain, testGroup, Test)
import Test.Framework.Providers.HUnit
import Test.HUnit hiding (Test)
import Network.Wai
import Network.Wai.Test
import Network.HTTP.Types (status200, decodePathSegments)
@ -58,7 +58,8 @@ caseMediaLink = runner $ do
assertStatus 200 res
flip assertBody res "<!DOCTYPE html>\n<html><head><title></title><link rel=\"stylesheet\" href=\"all.css\"><link rel=\"stylesheet\" media=\"screen\" href=\"screen.css\"></head><body></body></html>"
mediaTest = testGroup "Test.Media"
[ testCase "media" caseMedia
, testCase "media link" caseMediaLink
mediaTest :: IO [IO Spec]
mediaTest = describe "Test.Media"
[ it "media" caseMedia
, it "media link" caseMediaLink
]

View File

@ -2,9 +2,10 @@
{-# LANGUAGE FlexibleInstances #-}
module Test.NoOverloadedStrings (noOverloadedTest) where
import Test.Hspec
import Test.Hspec.HUnit
import Yesod.Core hiding (Request)
import Test.Framework (testGroup, Test)
import Test.Framework.Providers.HUnit
import Network.Wai.Test
import Network.Wai
import Data.Monoid (mempty)
@ -44,7 +45,7 @@ case_sanity = runner $ do
res <- request defaultRequest
assertBody mempty res
noOverloadedTest :: Test
noOverloadedTest = testGroup "Test.NoOverloadedStrings"
[ testCase "sanity" case_sanity
noOverloadedTest :: IO [IO Spec]
noOverloadedTest = describe "Test.NoOverloadedStrings"
[ it "sanity" case_sanity
]

View File

@ -3,15 +3,15 @@
{-# LANGUAGE FlexibleInstances #-}
module Test.Widget (widgetTest) where
import Test.Hspec
import Test.Hspec.HUnit
import Yesod.Core hiding (Request)
import Yesod.Content
import Yesod.Dispatch
import Yesod.Widget
import Text.Julius
import Test.Framework (defaultMain, testGroup, Test)
import Test.Framework.Providers.HUnit
import Test.HUnit hiding (Test)
import Network.Wai
import Network.Wai.Test
@ -54,10 +54,10 @@ getWhamletR = defaultLayout [$whamlet|
where
embed = [$whamlet|<h4>Embed|]
widgetTest :: Test
widgetTest = testGroup "Test.Widget"
[ testCase "addJuliusBody" case_addJuliusBody
, testCase "whamlet" case_whamlet
widgetTest :: IO [IO Spec]
widgetTest = describe "Test.Widget"
[ it "addJuliusBody" case_addJuliusBody
, it "whamlet" case_whamlet
]
runner f = toWaiApp Y >>= runSession f

View File

@ -1,4 +1,5 @@
import Test.Framework (defaultMain)
import Test.Hspec
import Test.CleanPath
import Test.Exceptions
import Test.Widget
@ -7,7 +8,7 @@ import Test.Links
import Test.NoOverloadedStrings
main :: IO ()
main = defaultMain
main = hspecX $ descriptions $
[ cleanPathTest
, exceptionsTest
, widgetTest

View File

@ -78,6 +78,8 @@ library
test-suite runtests
type: exitcode-stdio-1.0
main-is: test/main.hs
if flag(ghc7)
type: exitcode-stdio-1.0
build-depends: base >= 4.3 && < 5
@ -88,12 +90,10 @@ test-suite runtests
build-depends: base >= 4 && < 4.3
main-is: runtests.hs
cpp-options: -DTEST
build-depends: test-framework,
test-framework-quickcheck2,
test-framework-hunit,
HUnit,
wai-test,
QuickCheck >= 2 && < 3
build-depends: hspec >= 0.6 && < 0.7
,wai-test
,HUnit
,QuickCheck >= 2 && < 3
ghc-options: -Wall
main-is: runtests.hs