2022-05-11 09:14:25 +03:00
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
|
|
|
|
-- | Data Connector helpers.
|
|
|
|
module Harness.Backend.DataConnector
|
2022-06-25 22:05:58 +03:00
|
|
|
( -- * Reference Agent
|
|
|
|
setupFixture,
|
2022-05-11 09:14:25 +03:00
|
|
|
teardown,
|
2022-06-24 09:58:25 +03:00
|
|
|
defaultBackendConfig,
|
2022-06-25 22:05:58 +03:00
|
|
|
|
|
|
|
-- * Mock Agent
|
|
|
|
MockConfig (..),
|
|
|
|
MockAgentEnvironment (..),
|
|
|
|
TestCase (..),
|
2022-07-19 04:51:42 +03:00
|
|
|
TestCaseRequired (..),
|
|
|
|
defaultTestCase,
|
2022-06-25 22:05:58 +03:00
|
|
|
mockBackendConfig,
|
|
|
|
chinookMock,
|
|
|
|
runMockedTest,
|
|
|
|
mkLocalTestEnvironmentMock,
|
|
|
|
setupMock,
|
|
|
|
teardownMock,
|
2022-05-11 09:14:25 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2022-07-21 07:56:26 +03:00
|
|
|
import Control.Concurrent.Async (Async)
|
|
|
|
import Control.Concurrent.Async qualified as Async
|
2022-06-25 22:05:58 +03:00
|
|
|
import Data.Aeson qualified as Aeson
|
|
|
|
import Data.IORef qualified as I
|
|
|
|
import Harness.Backend.DataConnector.MockAgent
|
2022-05-11 09:14:25 +03:00
|
|
|
import Harness.GraphqlEngine qualified as GraphqlEngine
|
2022-06-29 10:42:51 +03:00
|
|
|
import Harness.Http (healthCheck)
|
2022-06-25 22:05:58 +03:00
|
|
|
import Harness.Quoter.Yaml (shouldReturnYaml, yaml)
|
2022-08-02 21:01:34 +03:00
|
|
|
import Harness.Test.Fixture (BackendType (DataConnector), Options, defaultBackendTypeString)
|
2022-05-11 09:14:25 +03:00
|
|
|
import Harness.TestEnvironment (TestEnvironment)
|
2022-06-25 22:05:58 +03:00
|
|
|
import Hasura.Backends.DataConnector.API qualified as API
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Test.Hspec (shouldBe)
|
2022-05-11 09:14:25 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2022-06-25 22:05:58 +03:00
|
|
|
defaultBackendConfig :: Aeson.Value
|
|
|
|
defaultBackendConfig =
|
|
|
|
let backendType = defaultBackendTypeString $ DataConnector
|
2022-05-11 09:14:25 +03:00
|
|
|
in [yaml|
|
2022-06-25 22:05:58 +03:00
|
|
|
dataconnector:
|
|
|
|
*backendType:
|
|
|
|
uri: "http://127.0.0.1:65005/"
|
2022-05-11 09:14:25 +03:00
|
|
|
|]
|
|
|
|
|
2022-06-25 22:05:58 +03:00
|
|
|
mockBackendConfig :: Aeson.Value
|
|
|
|
mockBackendConfig =
|
|
|
|
let backendType = defaultBackendTypeString $ DataConnector
|
2022-06-29 10:42:51 +03:00
|
|
|
agentUri = "http://127.0.0.1:" <> show mockAgentPort <> "/"
|
2022-05-11 09:14:25 +03:00
|
|
|
in [yaml|
|
|
|
|
dataconnector:
|
|
|
|
*backendType:
|
2022-06-29 10:42:51 +03:00
|
|
|
uri: *agentUri
|
2022-05-11 09:14:25 +03:00
|
|
|
|]
|
|
|
|
|
2022-06-25 22:05:58 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Chinook Agent
|
|
|
|
|
|
|
|
-- | Setup the schema given source metadata and backend config.
|
|
|
|
setupFixture :: Aeson.Value -> Aeson.Value -> (TestEnvironment, ()) -> IO ()
|
|
|
|
setupFixture sourceMetadata backendConfig (testEnvironment, _) = do
|
2022-05-11 09:14:25 +03:00
|
|
|
-- Clear and reconfigure the metadata
|
2022-06-25 22:05:58 +03:00
|
|
|
GraphqlEngine.setSource testEnvironment sourceMetadata (Just backendConfig)
|
2022-05-11 09:14:25 +03:00
|
|
|
|
|
|
|
-- | Teardown the schema and tracking in the most expected way.
|
2022-06-23 11:07:52 +03:00
|
|
|
teardown :: (TestEnvironment, ()) -> IO ()
|
|
|
|
teardown (testEnvironment, _) = do
|
2022-05-11 09:14:25 +03:00
|
|
|
GraphqlEngine.clearMetadata testEnvironment
|
2022-06-25 22:05:58 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Mock Agent
|
|
|
|
--
|
|
|
|
-- Current Design:
|
|
|
|
--
|
|
|
|
-- The Mock Agent receives at startup a 'I.IORef MockConfig' and an
|
|
|
|
-- empty 'I.IORef (Maybe API.Query)'.
|
|
|
|
--
|
|
|
|
-- The 'MockConfig' contains static responses for all the Agent
|
|
|
|
-- endpoints. When the agent handlers are called, they read from the
|
|
|
|
-- 'I.IORef MockConfig' and return the value revelevant to the handler.
|
|
|
|
--
|
|
|
|
-- In the case of the Query Handler, before returning the mock value,
|
|
|
|
-- the handler writes the incoming 'API.Query' value to the 'I.IORef
|
|
|
|
-- (Maybe API.Query)'.
|
|
|
|
--
|
|
|
|
-- The two 'I.IORef' values are constructed when we build the local
|
|
|
|
-- test environment in 'mkLocalTestEnvironmentMock' and call
|
|
|
|
-- 'runMockServer'. We return '(I.IORef MockConfig, I.IORef (Maybe
|
|
|
|
-- API.Query), ThreadId)' so that we can use the 'I.IORef' values in
|
|
|
|
-- test setups and the 'ThreadId' in teardown (to kill the agent
|
|
|
|
-- thread).
|
|
|
|
--
|
|
|
|
-- NOTE: In the current design we use the same agent and the same
|
|
|
|
-- 'I.IORef's for all tests. This is safe because the tests are run
|
|
|
|
-- sequentially. Parallelizing the test suite would break the testing
|
|
|
|
-- setup for 'DataConnector'.
|
|
|
|
--
|
|
|
|
-- If a parallelization refactor occurs, we will need to construct a
|
|
|
|
-- mock agent and corresponding 'I.IORef's for each individual
|
|
|
|
-- test. To make this work we would likely need to use hspec hooks on
|
|
|
|
-- the individual tests to spawn and destroy a mock agent and
|
|
|
|
-- associated 'I.IORef's.
|
|
|
|
|
|
|
|
data MockAgentEnvironment = MockAgentEnvironment
|
|
|
|
{ maeConfig :: I.IORef MockConfig,
|
|
|
|
maeQuery :: I.IORef (Maybe API.QueryRequest),
|
2022-07-21 07:56:26 +03:00
|
|
|
maeThread :: Async (),
|
2022-07-19 04:51:42 +03:00
|
|
|
maeQueryConfig :: I.IORef (Maybe API.Config)
|
2022-06-25 22:05:58 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
-- | Create the 'I.IORef's and launch the servant mock agent.
|
|
|
|
mkLocalTestEnvironmentMock :: TestEnvironment -> IO MockAgentEnvironment
|
|
|
|
mkLocalTestEnvironmentMock _ = do
|
|
|
|
maeConfig <- I.newIORef chinookMock
|
|
|
|
maeQuery <- I.newIORef Nothing
|
2022-07-19 04:51:42 +03:00
|
|
|
maeQueryConfig <- I.newIORef Nothing
|
2022-07-21 07:56:26 +03:00
|
|
|
maeThread <- Async.async $ runMockServer maeConfig maeQuery maeQueryConfig
|
2022-06-30 11:36:54 +03:00
|
|
|
healthCheck $ "http://127.0.0.1:" <> show mockAgentPort <> "/health"
|
2022-06-25 22:05:58 +03:00
|
|
|
pure $ MockAgentEnvironment {..}
|
|
|
|
|
|
|
|
-- | Load the agent schema into HGE.
|
|
|
|
setupMock :: Aeson.Value -> Aeson.Value -> (TestEnvironment, MockAgentEnvironment) -> IO ()
|
|
|
|
setupMock sourceMetadata backendConfig (testEnvironment, _mockAgentEnvironment) = do
|
|
|
|
-- Clear and reconfigure the metadata
|
|
|
|
GraphqlEngine.setSource testEnvironment sourceMetadata (Just backendConfig)
|
|
|
|
|
|
|
|
-- | Teardown the schema and kill the servant mock agent.
|
|
|
|
teardownMock :: (TestEnvironment, MockAgentEnvironment) -> IO ()
|
|
|
|
teardownMock (testEnvironment, MockAgentEnvironment {..}) = do
|
|
|
|
GraphqlEngine.clearMetadata testEnvironment
|
2022-07-21 07:56:26 +03:00
|
|
|
Async.cancel maeThread
|
2022-06-25 22:05:58 +03:00
|
|
|
|
|
|
|
-- | Mock Agent test case input.
|
|
|
|
data TestCase = TestCase
|
|
|
|
{ -- | The Mock configuration for the agent
|
|
|
|
_given :: MockConfig,
|
|
|
|
-- | The Graphql Query to test
|
|
|
|
_whenRequest :: Aeson.Value,
|
|
|
|
-- | The expected HGE 'API.Query' value to be provided to the
|
|
|
|
-- agent. A @Nothing@ value indicates that the 'API.Query'
|
|
|
|
-- assertion should be skipped.
|
|
|
|
_whenQuery :: Maybe API.QueryRequest,
|
2022-07-19 04:51:42 +03:00
|
|
|
-- | The expected HGE 'API.QueryHeaders' response and outgoing HGE 'API.QueryHeaders'
|
|
|
|
_whenConfig :: Maybe API.Config,
|
2022-06-25 22:05:58 +03:00
|
|
|
-- | The expected GQL response and outgoing HGE 'API.Query'
|
|
|
|
_then :: Aeson.Value
|
|
|
|
}
|
|
|
|
|
2022-07-19 04:51:42 +03:00
|
|
|
data TestCaseRequired = TestCaseRequired
|
|
|
|
{ -- | The Mock configuration for the agent
|
|
|
|
_givenRequired :: MockConfig,
|
|
|
|
-- | The Graphql Query to test
|
|
|
|
_whenRequestRequired :: Aeson.Value,
|
|
|
|
-- | The expected GQL response and outgoing HGE 'API.Query'
|
|
|
|
_thenRequired :: Aeson.Value
|
|
|
|
}
|
|
|
|
|
|
|
|
defaultTestCase :: TestCaseRequired -> TestCase
|
|
|
|
defaultTestCase TestCaseRequired {..} =
|
|
|
|
TestCase
|
|
|
|
{ _given = _givenRequired,
|
|
|
|
_whenRequest = _whenRequestRequired,
|
|
|
|
_whenQuery = Nothing,
|
|
|
|
_whenConfig = Nothing,
|
|
|
|
_then = _thenRequired
|
|
|
|
}
|
|
|
|
|
2022-06-25 22:05:58 +03:00
|
|
|
-- | Test runner for the Mock Agent. 'runMockedTest' sets the mocked
|
|
|
|
-- value in the agent, fires a GQL request, then asserts on the
|
|
|
|
-- expected response and 'API.Query' value.
|
|
|
|
runMockedTest :: Options -> TestCase -> (TestEnvironment, MockAgentEnvironment) -> IO ()
|
|
|
|
runMockedTest opts TestCase {..} (testEnvironment, MockAgentEnvironment {..}) = do
|
|
|
|
-- Set the Agent with the 'MockConfig'
|
|
|
|
I.writeIORef maeConfig _given
|
|
|
|
|
|
|
|
-- Execute the GQL Query and assert on the result
|
|
|
|
shouldReturnYaml
|
|
|
|
opts
|
|
|
|
( GraphqlEngine.postGraphql
|
|
|
|
testEnvironment
|
|
|
|
_whenRequest
|
|
|
|
)
|
|
|
|
_then
|
|
|
|
|
|
|
|
-- Read the logged 'API.QueryRequest' from the Agent
|
|
|
|
query <- I.readIORef maeQuery
|
|
|
|
I.writeIORef maeQuery Nothing
|
|
|
|
|
2022-07-19 04:51:42 +03:00
|
|
|
-- Read the logged 'API.Config' from the Agent
|
|
|
|
queryConfig <- I.readIORef maeQueryConfig
|
|
|
|
I.writeIORef maeQueryConfig Nothing
|
|
|
|
|
2022-06-25 22:05:58 +03:00
|
|
|
-- Assert that the 'API.QueryRequest' was constructed how we expected.
|
|
|
|
onJust _whenQuery ((query `shouldBe`) . Just)
|
2022-07-19 04:51:42 +03:00
|
|
|
onJust _whenConfig ((queryConfig `shouldBe`) . Just)
|