fradrive/test/TestImport.hs
Gregor Kleen cfaea9c08b chore: bump to lts-15.0
BREAKING CHANGE: major version bumps
2020-02-23 11:12:45 +01:00

128 lines
4.3 KiB
Haskell

module TestImport
( module TestImport
, module X
) where
import Application (makeFoundation, makeLogWare, shutdownApp)
import ClassyPrelude as X
hiding ( delete, deleteBy
, Handler, Index
, (<.>), (<|)
, index, uncons, unsnoc, cons, snoc
, try, catches, handle, catch, bracket, bracketOnError, bracket_, catchJust, finally, handleJust, mask, mask_, onException, tryJust, uninterruptibleMask, uninterruptibleMask_
)
import Database.Persist as X hiding (get)
import Database.Persist.Sql as X (SqlPersistM)
import Database.Persist.Sql (runSqlPersistMPool)
import Foundation as X
import Model as X
import Test.Hspec as X
import Yesod.Default.Config2 (useEnv, loadYamlSettings)
import Yesod.Auth as X
import Yesod.Test as X
import Yesod.Core.Unsafe (fakeHandlerGetLogger)
import Test.QuickCheck as X
import Test.QuickCheck.Gen as X
import Data.Default as X
import Test.QuickCheck.Instances as X ()
import Test.QuickCheck.Arbitrary.Generic as X
import Test.QuickCheck.Classes as X
import Test.QuickCheck.Classes.PathPiece as X
import Test.QuickCheck.Classes.PersistField as X
import Test.QuickCheck.Classes.Hashable as X
import Test.QuickCheck.Classes.JSON as X
import Test.QuickCheck.Classes.HttpApiData as X
import Test.QuickCheck.Classes.Universe as X
import Test.QuickCheck.Classes.Binary as X
import Test.QuickCheck.Classes.Csv as X
import Data.Proxy as X
import Data.UUID as X (UUID)
import System.IO as X (hPrint, hPutStrLn)
import Jobs (handleJobs)
import Numeric.Natural as X
import Control.Lens as X hiding ((<.), elements)
import Net.IP as X (IP)
import Database (truncateDb)
import Database as X (fillDb)
import User as X (fakeUser)
import Control.Monad.Catch as X hiding (Handler(..))
import Control.Monad.Trans.Resource (runResourceT)
import Settings.WellKnownFiles as X
import Data.CaseInsensitive as X (CI)
import qualified Data.CaseInsensitive as CI
import Data.Typeable
import Handler.Utils (runAppLoggingT)
import Web.PathPieces (toPathPiece)
import Utils.Parameters (GlobalPostParam(PostLoginDummy))
runDB :: SqlPersistM a -> YesodExample UniWorX a
runDB query = do
app <- getTestYesod
liftIO $ runDBWithApp app query
runDBWithApp :: MonadIO m => UniWorX -> SqlPersistM a -> m a
runDBWithApp app query = liftIO $ runSqlPersistMPool query (appConnPool app)
runHandler :: Handler a -> YesodExample UniWorX a
runHandler handler = do
app <- getTestYesod
logger <- liftIO . readTVarIO . snd $ appLogger app
fakeHandlerGetLogger (const logger) app handler
withApp :: YSpec UniWorX -> Spec
withApp = around $ \act -> runResourceT $ do
settings <- liftIO $ loadYamlSettings
["config/test-settings.yml", "config/settings.yml"]
[]
useEnv
foundation <- makeFoundation settings
wipeDB foundation
runAppLoggingT foundation $ handleJobs foundation
logWare <- makeLogWare foundation
lift $ act (foundation, logWare) `finally` shutdownApp foundation
-- 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 :: MonadUnliftIO m => UniWorX -> m ()
wipeDB app = runDBWithApp app Database.truncateDb
-- | 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 UniWorX ()
authenticateAs (Entity _ User{..}) = do
request $ do
setMethod "GET"
addRequestHeader ("Accept-Language", "de")
setUrl $ AuthR LoginR
request $ do
setMethod "POST"
addToken_ "#login--dummy"
addPostParam (toPathPiece PostLoginDummy) $ CI.original userIdent
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 :: (User -> User) -> YesodExample UniWorX (Entity User)
createUser = runDB . insertEntity . fakeUser
lawsCheckHspec :: Typeable a => Proxy a -> [Proxy a -> Laws] -> Spec
lawsCheckHspec p = parallel . describe (show $ typeRep p) . mapM_ (checkHspec . ($ p))
where
checkHspec (Laws className properties) = describe className $
forM_ properties $ \(name, prop) -> it name $ property prop