gonito/test/TestImport.hs

96 lines
3.1 KiB
Haskell
Raw Normal View History

2018-09-20 13:02:07 +02:00
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
2015-08-20 22:33:38 +02:00
module TestImport
( module TestImport
, module X
) where
2018-09-20 13:02:07 +02:00
import Application (makeFoundation, makeLogWare)
import ClassyPrelude as X hiding (delete, deleteBy, Handler)
2015-08-20 22:33:38 +02:00
import Database.Persist as X hiding (get)
2018-09-20 13:02:07 +02:00
import Database.Persist.Sql (SqlPersistM, runSqlPersistMPool, rawExecute, rawSql, unSingle, connEscapeName)
2015-08-20 22:33:38 +02:00
import Foundation as X
import Model as X
import Test.Hspec as X
import Text.Shakespeare.Text (st)
2018-09-20 13:02:07 +02:00
import Yesod.Default.Config2 (useEnv, loadYamlSettings)
import Yesod.Auth as X
2015-08-20 22:33:38 +02:00
import Yesod.Test as X
2018-09-20 13:02:07 +02:00
import Yesod.Core.Unsafe (fakeHandlerGetLogger)
2015-08-20 22:33:38 +02:00
runDB :: SqlPersistM a -> YesodExample App a
runDB query = do
app <- getTestYesod
liftIO $ runDBWithApp app query
runDBWithApp :: App -> SqlPersistM a -> IO a
runDBWithApp app query = runSqlPersistMPool query (appConnPool app)
2018-09-20 13:02:07 +02:00
runHandler :: Handler a -> YesodExample App a
runHandler handler = do
app <- getTestYesod
fakeHandlerGetLogger appLogger app handler
2015-08-20 22:33:38 +02:00
2018-09-20 13:02:07 +02:00
withApp :: SpecWith (TestApp App) -> Spec
2015-08-20 22:33:38 +02:00
withApp = before $ do
2018-09-20 13:02:07 +02:00
settings <- loadYamlSettings
2015-08-20 22:33:38 +02:00
["config/test-settings.yml", "config/settings.yml"]
[]
2018-09-20 13:02:07 +02:00
useEnv
2015-08-20 22:33:38 +02:00
foundation <- makeFoundation settings
wipeDB foundation
2018-09-20 13:02:07 +02:00
logWare <- liftIO $ makeLogWare foundation
return (foundation, logWare)
2015-08-20 22:33:38 +02:00
-- This function will truncate all of the tables in your database.
-- 'withApp' calls it before each test, creating a clean environment for each
-- spec to run in.
wipeDB :: App -> IO ()
wipeDB app = runDBWithApp app $ do
tables <- getTables
sqlBackend <- ask
let escapedTables = map (connEscapeName sqlBackend . DBName) tables
query = "TRUNCATE TABLE " ++ intercalate ", " escapedTables
rawExecute query []
2018-09-20 13:02:07 +02:00
getTables :: DB [Text]
2015-08-20 22:33:38 +02:00
getTables = do
tables <- rawSql [st|
SELECT table_name
FROM information_schema.tables
WHERE table_schema = 'public';
|] []
return $ map unSingle tables
2018-09-20 13:02:07 +02:00
-- | Authenticate as a user. This relies on the `auth-dummy-login: true` flag
-- being set in test-settings.yaml, which enables dummy authentication in
-- Foundation.hs
authenticateAs :: Entity User -> YesodExample App ()
authenticateAs (Entity _ u) = do
request $ do
setMethod "POST"
addPostParam "ident" $ userIdent u
setUrl $ AuthR $ PluginR "dummy" []
-- | Create a user. The dummy email entry helps to confirm that foreign-key
-- checking is switched off in wipeDB for those database backends which need it.
createUser :: Text -> YesodExample App (Entity User)
createUser ident = runDB $ do
user <- insertEntity User
{ userIdent = ident
, userPassword = Nothing
, userName = Nothing
, userIsAdmin = False
, userLocalId = Nothing
, userIsAnonymous = False
, userAvatar = Nothing
, userVerificationKey = Nothing
, userKeyExpirationDate = Nothing
, userTriggerToken = Nothing
}
return user