graphql-engine/server/test/Main.hs

84 lines
3.0 KiB
Haskell
Raw Normal View History

2018-06-27 16:11:32 +03:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
2018-06-27 16:11:32 +03:00
module Main where
import Control.Monad.Trans.Except
import Data.Time.Clock (getCurrentTime)
import Network.Wai (Application)
import Options.Applicative
import System.Environment (withArgs)
2018-06-27 16:11:32 +03:00
import System.Exit (exitFailure)
import Test.Hspec.Core.Runner
import Test.Hspec.Wai
import qualified Data.Aeson as J
import qualified Data.ByteString.Lazy.Char8 as BLC
2018-06-27 16:11:32 +03:00
import qualified Database.PG.Query as Q
import qualified Hasura.Logging as L
2018-06-27 16:11:32 +03:00
import Hasura.Prelude
import Hasura.Server.App (mkWaiApp)
import Hasura.Server.Auth (AuthMode (..))
2018-06-27 16:11:32 +03:00
import qualified Database.PG.Query as PGQ
2018-06-27 16:11:32 +03:00
import Hasura.Server.Init
import Ops (initCatalogSafe)
import Spec (mkSpecs)
2018-06-27 16:11:32 +03:00
data ConnectionParams = ConnectionParams RawConnInfo Q.ConnParams
2018-06-27 16:11:32 +03:00
defTxMode :: Q.TxMode
defTxMode = (Q.Serializable, Nothing)
resetStateTx :: Q.TxE PGQ.PGExecErr ()
resetStateTx = do
Q.unitQE PGQ.PGExecErrTx "DROP SCHEMA hdb_catalog CASCADE" () False
Q.unitQE PGQ.PGExecErrTx "DROP SCHEMA hdb_views CASCADE" () False
2018-06-27 16:11:32 +03:00
Q.unitQE PGQ.PGExecErrTx "DROP SCHEMA public CASCADE" () False
Q.unitQE PGQ.PGExecErrTx "CREATE SCHEMA public" () False
ravenApp :: L.LoggerCtx -> PGQ.PGPool -> IO Application
ravenApp loggerCtx pool = do
2018-07-20 11:19:06 +03:00
let corsCfg = CorsConfigG "*" False -- cors is enabled
-- spockAsApp $ spockT id $ app Q.Serializable Nothing rlogger pool AMNoAuth corsCfg True -- no access key and no webhook
mkWaiApp Q.Serializable Nothing loggerCtx pool AMNoAuth corsCfg True -- no access key and no webhook
2018-06-27 16:11:32 +03:00
main :: IO ()
main = do
-- parse CLI flags for connection params
ConnectionParams rci cp <- parseArgs
-- form the postgres connection info
2018-06-27 16:11:32 +03:00
ci <- either ((>> exitFailure) . (putStrLn . connInfoErrModifier))
return $ mkConnInfo Nothing rci
-- intialize the pool
2018-06-27 16:11:32 +03:00
pool <- Q.initPGPool ci cp
-- reset state in the database
void $ liftIO $ runExceptT $ Q.runTx pool defTxMode resetStateTx
-- intialize state for graphql-engine in the database
liftIO $ initialise pool
2018-07-20 11:19:06 +03:00
-- generate the test specs
specs <- mkSpecs
loggerCtx <- L.mkLoggerCtx L.defaultLoggerSettings
-- run the tests
2018-07-20 11:19:06 +03:00
withArgs [] $ hspecWith defaultConfig $ with (ravenApp loggerCtx pool) specs
2018-06-27 16:11:32 +03:00
where
initialise :: Q.PGPool -> IO ()
initialise pool = do
currentTime <- getCurrentTime
res <- runExceptT $ Q.runTx pool defTxMode $ initCatalogSafe currentTime
either ((>> exitFailure) . (BLC.putStrLn . J.encode)) putStrLn res
2018-06-27 16:11:32 +03:00
parseArgs :: IO ConnectionParams
2018-06-27 16:11:32 +03:00
parseArgs = execParser opts
where
optParser = ConnectionParams <$> parseRawConnInfo <*> parseConnParams
2018-06-27 16:11:32 +03:00
opts = info (helper <*> optParser)
( fullDesc <>
header "graphql-engine-test")