2018-07-11 10:13:07 +03:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
|
|
|
module Spec (mkSpecs) where
|
|
|
|
|
2018-08-10 15:05:07 +03:00
|
|
|
import Hasura.Prelude hiding (get)
|
|
|
|
import Network.Wai (Application)
|
2018-07-11 10:13:07 +03:00
|
|
|
import Test.Hspec
|
|
|
|
import Test.Hspec.Wai
|
2018-08-10 15:05:07 +03:00
|
|
|
import Test.Hspec.Wai.Matcher
|
2018-07-11 10:13:07 +03:00
|
|
|
|
2018-08-10 15:05:07 +03:00
|
|
|
import qualified Data.Aeson as J
|
|
|
|
import qualified Data.Aeson.Casing as J
|
|
|
|
import qualified Data.Aeson.TH as J
|
|
|
|
import qualified Data.CaseInsensitive as CI
|
|
|
|
import qualified Data.HashMap.Strict as HM
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import qualified Data.Text.Encoding as T
|
|
|
|
import qualified Data.Yaml as Y
|
2018-07-11 10:13:07 +03:00
|
|
|
|
2018-08-10 15:05:07 +03:00
|
|
|
type Headers = HM.HashMap T.Text T.Text
|
2018-07-11 10:13:07 +03:00
|
|
|
|
|
|
|
data TestCase
|
|
|
|
= TestCase
|
|
|
|
{ tcDescription :: !T.Text
|
|
|
|
, tcQuery :: !J.Value
|
|
|
|
, tcUrl :: !T.Text
|
2018-08-10 15:05:07 +03:00
|
|
|
, tcHeaders :: !(Maybe Headers)
|
2018-07-11 10:13:07 +03:00
|
|
|
, tcStatus :: !Int
|
2018-08-10 15:05:07 +03:00
|
|
|
, tcResponse :: !(Maybe J.Value)
|
2018-07-20 11:19:06 +03:00
|
|
|
-- , tcDependsOn :: !(Maybe TestCase)
|
2018-07-11 10:13:07 +03:00
|
|
|
} deriving (Show)
|
|
|
|
|
|
|
|
$(J.deriveJSON (J.aesonDrop 2 J.snakeCase) ''TestCase)
|
|
|
|
|
2018-07-20 11:19:06 +03:00
|
|
|
|
2018-07-11 10:13:07 +03:00
|
|
|
querySpecFiles :: [FilePath]
|
|
|
|
querySpecFiles =
|
|
|
|
[ "create_tables.yaml"
|
|
|
|
, "track_tables.yaml"
|
|
|
|
, "create_author_article_relationship.yaml"
|
2018-07-20 11:19:06 +03:00
|
|
|
, "create_author_article_permissions.yaml"
|
2018-08-03 12:34:37 +03:00
|
|
|
, "create_address_resident_relationship_error.yaml"
|
2018-08-10 15:05:07 +03:00
|
|
|
, "create_user_permission_address.yaml"
|
2018-09-05 18:25:30 +03:00
|
|
|
, "reload_metadata.yaml"
|
2018-08-27 14:50:18 +03:00
|
|
|
, "create_author_permission_role_admin_error.yaml"
|
2018-08-29 16:41:33 +03:00
|
|
|
, "create_user_permission_test_table.yaml"
|
|
|
|
, "all_json_queries.yaml"
|
|
|
|
, "upsert_role_user.yaml"
|
|
|
|
, "upsert_role_user_error.yaml"
|
2018-07-11 10:13:07 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
gqlSpecFiles :: [FilePath]
|
|
|
|
gqlSpecFiles =
|
2018-07-17 16:23:23 +03:00
|
|
|
[ "introspection.yaml"
|
2018-09-03 10:05:00 +03:00
|
|
|
, "introspection_user_role.yaml"
|
2018-07-20 13:51:20 +03:00
|
|
|
, "insert_mutation/author.yaml"
|
2018-07-11 10:13:07 +03:00
|
|
|
, "simple_select_query_author.yaml"
|
2018-08-27 17:17:03 +03:00
|
|
|
, "select_query_author_by_pkey.yaml"
|
2018-07-20 13:51:20 +03:00
|
|
|
, "insert_mutation/article.yaml"
|
|
|
|
, "insert_mutation/article_on_conflict.yaml"
|
2018-09-04 16:39:48 +03:00
|
|
|
, "insert_mutation/article_on_conflict_user_role.yaml"
|
|
|
|
, "insert_mutation/article_on_conflict_update_columns.yaml"
|
2018-07-20 13:51:20 +03:00
|
|
|
, "insert_mutation/article_on_conflict_ignore.yaml"
|
|
|
|
, "insert_mutation/article_on_conflict_ignore_constraint.yaml"
|
2018-09-04 16:39:48 +03:00
|
|
|
, "insert_mutation/article_on_conflict_empty_update_columns.yaml"
|
|
|
|
, "insert_mutation/article_on_conflict_only_constraint.yaml"
|
2018-07-20 13:51:20 +03:00
|
|
|
, "insert_mutation/article_on_conflict_error_01.yaml"
|
|
|
|
, "insert_mutation/article_on_conflict_error_02.yaml"
|
|
|
|
, "insert_mutation/article_on_conflict_error_03.yaml"
|
|
|
|
, "insert_mutation/person.yaml"
|
|
|
|
, "insert_mutation/person_array.yaml"
|
2018-08-07 13:43:42 +03:00
|
|
|
, "insert_mutation/order.yaml"
|
2018-08-10 15:05:07 +03:00
|
|
|
, "insert_mutation/address_check_constraint_error.yaml"
|
|
|
|
, "insert_mutation/address_not_null_constraint_error.yaml"
|
|
|
|
, "insert_mutation/author_unique_constraint_error.yaml"
|
2018-08-17 17:44:43 +03:00
|
|
|
, "insert_mutation/author_on_conflict_ignore_user_role.yaml"
|
|
|
|
, "insert_mutation/author_on_conflict_update_user_role.yaml"
|
2018-07-11 10:13:07 +03:00
|
|
|
, "nested_select_query_article.yaml"
|
2018-08-06 15:15:08 +03:00
|
|
|
, "select_query_article_limit_offset.yaml"
|
|
|
|
, "select_query_article_limit_offset_error_01.yaml"
|
|
|
|
, "select_query_article_limit_offset_error_02.yaml"
|
2018-07-20 13:51:20 +03:00
|
|
|
, "update_mutation/author.yaml"
|
|
|
|
, "update_mutation/person_set.yaml"
|
|
|
|
, "update_mutation/person_append.yaml"
|
|
|
|
, "update_mutation/person_prepend.yaml"
|
|
|
|
, "update_mutation/person_delete_key.yaml"
|
|
|
|
, "update_mutation/person_delete_elem.yaml"
|
|
|
|
, "update_mutation/person_delete_at_path.yaml"
|
|
|
|
, "update_mutation/person_inc.yaml"
|
|
|
|
, "update_mutation/person_error_01.yaml"
|
|
|
|
, "delete_mutation/article.yaml"
|
2018-08-08 10:01:49 +03:00
|
|
|
, "delete_mutation/article_returning.yaml"
|
2018-08-10 15:05:07 +03:00
|
|
|
, "delete_mutation/author_foreign_key_violation.yaml"
|
2018-07-11 10:13:07 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
readTestCase :: FilePath -> IO TestCase
|
|
|
|
readTestCase fpath = do
|
|
|
|
res <- Y.decodeFileEither ("test/testcases/" ++ fpath)
|
|
|
|
case res of
|
|
|
|
Left e -> do
|
|
|
|
putStrLn $ Y.prettyPrintParseException e
|
|
|
|
error $ "Could not parse testcase YAML: " ++ fpath
|
|
|
|
Right q -> return q
|
|
|
|
|
|
|
|
mkSpec :: TestCase -> SpecWith Application
|
|
|
|
mkSpec tc = do
|
|
|
|
let desc = tcDescription tc
|
|
|
|
url = tcUrl tc
|
|
|
|
q = tcQuery tc
|
2018-08-10 15:05:07 +03:00
|
|
|
mHeaders = tcHeaders tc
|
|
|
|
statusCode = tcStatus tc
|
|
|
|
mRespBody = tcResponse tc
|
|
|
|
headers = maybe [] (map toHeader . HM.toList) mHeaders
|
|
|
|
body = maybe matchAny bodyEquals $ fmap J.encode mRespBody
|
|
|
|
resp = ResponseMatcher statusCode [] body
|
2018-07-20 11:19:06 +03:00
|
|
|
it (T.unpack desc) $
|
2018-08-10 15:05:07 +03:00
|
|
|
request "POST" (T.encodeUtf8 url) headers (J.encode q) `shouldRespondWith` resp
|
|
|
|
where
|
|
|
|
matchAny = MatchBody (\_ _ -> Nothing)
|
|
|
|
toHeader (k, v) = (CI.mk $ T.encodeUtf8 k, T.encodeUtf8 v)
|
2018-07-11 10:13:07 +03:00
|
|
|
|
2018-07-20 11:19:06 +03:00
|
|
|
|
2018-07-11 10:13:07 +03:00
|
|
|
mkSpecs :: IO (SpecWith Application)
|
|
|
|
mkSpecs = do
|
|
|
|
ddlTc <- mapM readTestCase querySpecFiles
|
|
|
|
gqlTc <- mapM readTestCase gqlSpecFiles
|
|
|
|
return $ do
|
|
|
|
describe "version API" $
|
|
|
|
it "responds with version" $
|
|
|
|
get "/v1/version" `shouldRespondWith` 200
|
|
|
|
|
2018-07-20 11:19:06 +03:00
|
|
|
describe "console endpoint" $
|
|
|
|
it "responds with 200" $
|
|
|
|
get "/console" `shouldRespondWith` 200
|
|
|
|
|
|
|
|
describe "CORS test" $
|
|
|
|
it "should respond with correct CORS headers" $
|
|
|
|
request "OPTIONS" "/v1/version" [("Origin", "example.com")] ""
|
|
|
|
`shouldRespondWith` 204
|
|
|
|
{matchHeaders = ["Access-Control-Allow-Origin" <:> "example.com"]}
|
|
|
|
|
2018-07-11 10:13:07 +03:00
|
|
|
describe "Query API" $ mapM_ mkSpec ddlTc
|
|
|
|
|
|
|
|
describe "GraphQL API" $ mapM_ mkSpec gqlTc
|