Updated scaffolding

This commit is contained in:
Michael Snoyman 2013-02-01 00:19:13 +02:00
parent 3de491870a
commit 38292d6357
4 changed files with 95 additions and 15 deletions

View File

@ -425,6 +425,7 @@ test-suite test
, yesod-core
, persistent
, persistent-mongoDB
, resourcet
{-# START_FILE Settings.hs #-}
-- | Settings are centralized, as much as possible, into this file. This
@ -5728,10 +5729,12 @@ module HomeTest
) where
import TestImport
import qualified Data.List as L
homeSpecs :: Specs
homeSpecs =
describe "These are some example tests" $
describe "These are some example tests" $ do
it "loads the index and checks it looks right" $ do
get_ "/"
statusIs 200
@ -5747,21 +5750,38 @@ homeSpecs =
htmlAllContain ".message" "Some Content"
htmlAllContain ".message" "text/plain"
-- This is a simple example of using a database access in a test. The
-- test will succeed for a fresh scaffolded site with an empty database,
-- but will fail on an existing database with a non-empty user table.
it "leaves the user table empty" $ do
get_ "/"
statusIs 200
users <- runDB $ selectList ([] :: [Filter User]) []
assertEqual "user table empty" 0 $ L.length users
{-# START_FILE tests/TestImport.hs #-}
{-# LANGUAGE OverloadedStrings #-}
module TestImport
( module Yesod.Test
, module Model
, module Database.Persist
, runDB
, Specs
) where
import Yesod.Test
import Database.Persist hiding (get)
import Database.Persist.MongoDB hiding (master)
import Control.Monad.Trans.Resource (ResourceT, runResourceT)
import Model
type Specs = SpecsConn Connection
runDB :: Action IO a -> OneSpec Connection a
runDB = runDBRunner runMongoDBPoolDef
runDB :: Action (ResourceT IO) a -> OneSpec Connection a
runDB = runDBRunner poolRunner
where
poolRunner query pool = runResourceT $ runMongoDBPoolDef query pool
{-# START_FILE tests/main.hs #-}
{-# LANGUAGE OverloadedStrings #-}

View File

@ -423,6 +423,7 @@ test-suite test
, yesod-core
, persistent
, persistent-mysql
, resourcet
{-# START_FILE Settings.hs #-}
-- | Settings are centralized, as much as possible, into this file. This
@ -5752,10 +5753,12 @@ module HomeTest
) where
import TestImport
import qualified Data.List as L
homeSpecs :: Specs
homeSpecs =
describe "These are some example tests" $
describe "These are some example tests" $ do
it "loads the index and checks it looks right" $ do
get_ "/"
statusIs 200
@ -5771,21 +5774,38 @@ homeSpecs =
htmlAllContain ".message" "Some Content"
htmlAllContain ".message" "text/plain"
-- This is a simple example of using a database access in a test. The
-- test will succeed for a fresh scaffolded site with an empty database,
-- but will fail on an existing database with a non-empty user table.
it "leaves the user table empty" $ do
get_ "/"
statusIs 200
users <- runDB $ selectList ([] :: [Filter User]) []
assertEqual "user table empty" 0 $ L.length users
{-# START_FILE tests/TestImport.hs #-}
{-# LANGUAGE OverloadedStrings #-}
module TestImport
( module Yesod.Test
, module Model
, module Database.Persist
, runDB
, Specs
) where
import Yesod.Test
import Database.Persist.GenericSql
import Database.Persist hiding (get)
import Database.Persist.GenericSql (runSqlPool, SqlPersist, Connection)
import Control.Monad.Trans.Resource (ResourceT, runResourceT)
import Model
type Specs = SpecsConn Connection
runDB :: SqlPersist IO a -> OneSpec Connection a
runDB = runDBRunner runSqlPool
runDB :: SqlPersist (ResourceT IO) a -> OneSpec Connection a
runDB = runDBRunner poolRunner
where
poolRunner query pool = runResourceT $ runSqlPool query pool
{-# START_FILE tests/main.hs #-}
{-# LANGUAGE OverloadedStrings #-}

View File

@ -423,6 +423,7 @@ test-suite test
, yesod-core
, persistent
, persistent-postgresql
, resourcet
{-# START_FILE Settings.hs #-}
-- | Settings are centralized, as much as possible, into this file. This
@ -5726,10 +5727,12 @@ module HomeTest
) where
import TestImport
import qualified Data.List as L
homeSpecs :: Specs
homeSpecs =
describe "These are some example tests" $
describe "These are some example tests" $ do
it "loads the index and checks it looks right" $ do
get_ "/"
statusIs 200
@ -5745,21 +5748,38 @@ homeSpecs =
htmlAllContain ".message" "Some Content"
htmlAllContain ".message" "text/plain"
-- This is a simple example of using a database access in a test. The
-- test will succeed for a fresh scaffolded site with an empty database,
-- but will fail on an existing database with a non-empty user table.
it "leaves the user table empty" $ do
get_ "/"
statusIs 200
users <- runDB $ selectList ([] :: [Filter User]) []
assertEqual "user table empty" 0 $ L.length users
{-# START_FILE tests/TestImport.hs #-}
{-# LANGUAGE OverloadedStrings #-}
module TestImport
( module Yesod.Test
, module Model
, module Database.Persist
, runDB
, Specs
) where
import Yesod.Test
import Database.Persist.GenericSql
import Database.Persist hiding (get)
import Database.Persist.GenericSql (runSqlPool, SqlPersist, Connection)
import Control.Monad.Trans.Resource (ResourceT, runResourceT)
import Model
type Specs = SpecsConn Connection
runDB :: SqlPersist IO a -> OneSpec Connection a
runDB = runDBRunner runSqlPool
runDB :: SqlPersist (ResourceT IO) a -> OneSpec Connection a
runDB = runDBRunner poolRunner
where
poolRunner query pool = runResourceT $ runSqlPool query pool
{-# START_FILE tests/main.hs #-}
{-# LANGUAGE OverloadedStrings #-}

View File

@ -423,6 +423,7 @@ test-suite test
, yesod-core
, persistent
, persistent-sqlite
, resourcet
{-# START_FILE Settings.hs #-}
-- | Settings are centralized, as much as possible, into this file. This
@ -5722,10 +5723,12 @@ module HomeTest
) where
import TestImport
import qualified Data.List as L
homeSpecs :: Specs
homeSpecs =
describe "These are some example tests" $
describe "These are some example tests" $ do
it "loads the index and checks it looks right" $ do
get_ "/"
statusIs 200
@ -5741,21 +5744,38 @@ homeSpecs =
htmlAllContain ".message" "Some Content"
htmlAllContain ".message" "text/plain"
-- This is a simple example of using a database access in a test. The
-- test will succeed for a fresh scaffolded site with an empty database,
-- but will fail on an existing database with a non-empty user table.
it "leaves the user table empty" $ do
get_ "/"
statusIs 200
users <- runDB $ selectList ([] :: [Filter User]) []
assertEqual "user table empty" 0 $ L.length users
{-# START_FILE tests/TestImport.hs #-}
{-# LANGUAGE OverloadedStrings #-}
module TestImport
( module Yesod.Test
, module Model
, module Database.Persist
, runDB
, Specs
) where
import Yesod.Test
import Database.Persist.GenericSql
import Database.Persist hiding (get)
import Database.Persist.GenericSql (runSqlPool, SqlPersist, Connection)
import Control.Monad.Trans.Resource (ResourceT, runResourceT)
import Model
type Specs = SpecsConn Connection
runDB :: SqlPersist IO a -> OneSpec Connection a
runDB = runDBRunner runSqlPool
runDB :: SqlPersist (ResourceT IO) a -> OneSpec Connection a
runDB = runDBRunner poolRunner
where
poolRunner query pool = runResourceT $ runSqlPool query pool
{-# START_FILE tests/main.hs #-}
{-# LANGUAGE OverloadedStrings #-}