graphql-engine/server/tests-hspec/Test/SelectSpec.hs
Samir Talwar eab4f75212 An ErrorMessage type, to encapsulate.
This introduces an `ErrorMessage` newtype which wraps `Text` in a manner which is designed to be easy to construct, and difficult to deconstruct.

It provides functionality similar to `Data.Text.Extended`, but designed _only_ for error messages. Error messages are constructed through `fromString`, concatenation, or the `toErrorValue` function, which is designed to be overridden for all meaningful domain types that might show up in an error message. Notably, there are not and should never be instances of `ToErrorValue` for `String`, `Text`, `Int`, etc. This is so that we correctly represent the value in a way that is specific to its type. For example, all `Name` values (from the _graphql-parser-hs_ library) are single-quoted now; no exceptions.

I have mostly had to add `instance ToErrorValue` for various backend types (and also add newtypes where necessary). Some of these are not strictly necessary for this changeset, as I had bigger aspirations when I started. These aspirations have been tempered by trying and failing twice.

As such, in this changeset, I have started by introducing this type to the `parseError` and `parseErrorWith` functions. In the future, I would like to extend this to the `QErr` record and the various `throwError` functions, but this is a much larger task and should probably be done in stages.

For now, `toErrorMessage` and `fromErrorMessage` are provided for conversion to and from `Text`, but the intent is to stop exporting these once all error messages are converted to the new type.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5018
GitOrigin-RevId: 84b37e238992e4312255a87ca44f41af65e2d89a
2022-07-18 20:27:06 +00:00

152 lines
4.1 KiB
Haskell

{-# LANGUAGE QuasiQuotes #-}
-- | Select test for various queries
module Test.SelectSpec (spec) where
import Data.Aeson
( Value (..),
object,
(.=),
)
import Harness.Backend.BigQuery qualified as Bigquery
import Harness.Backend.Citus qualified as Citus
import Harness.Backend.Postgres qualified as Postgres
import Harness.Backend.Sqlserver qualified as Sqlserver
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Yaml
( shouldReturnOneOfYaml,
shouldReturnYaml,
yaml,
)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema (Table (..), table)
import Harness.Test.Schema qualified as Schema
import Harness.TestEnvironment (TestEnvironment)
import Harness.Yaml
import Test.Hspec (SpecWith, describe, it)
import Prelude
--------------------------------------------------------------------------------
-- Preamble
spec :: SpecWith TestEnvironment
spec =
Context.run
[ Context.Context
{ name = Context.Backend Context.Postgres,
mkLocalTestEnvironment = Context.noLocalTestEnvironment,
setup = Postgres.setup schema,
teardown = Postgres.teardown schema,
customOptions = Nothing
},
Context.Context
{ name = Context.Backend Context.Citus,
mkLocalTestEnvironment = Context.noLocalTestEnvironment,
setup = Citus.setup schema,
teardown = Citus.teardown schema,
customOptions = Nothing
},
Context.Context
{ name = Context.Backend Context.SQLServer,
mkLocalTestEnvironment = Context.noLocalTestEnvironment,
setup = Sqlserver.setup schema,
teardown = Sqlserver.teardown schema,
customOptions = Nothing
},
Context.Context
{ name = Context.Backend Context.BigQuery,
mkLocalTestEnvironment = Context.noLocalTestEnvironment,
setup = Bigquery.setup schema,
teardown = Bigquery.teardown schema,
customOptions =
Just $
Context.Options
{ stringifyNumbers = True
}
}
]
tests
schema :: [Schema.Table]
schema = [author]
author :: Schema.Table
author =
(table "author")
{ tableColumns =
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr,
Schema.column "createdAt" Schema.TUTCTime
],
tablePrimaryKey = ["id"],
tableData =
[ [ Schema.VInt 1,
Schema.VStr "Author 1",
Schema.parseUTCTimeOrError "2017-09-21 09:39:44"
],
[ Schema.VInt 2,
Schema.VStr "Author 2",
Schema.parseUTCTimeOrError "2017-09-21 09:50:44"
]
]
}
tests :: Context.Options -> SpecWith TestEnvironment
tests opts = describe "SelectSpec" $ do
it "works with simple object query" $ \testEnvironment -> do
let authorOne, authorTwo :: Value
authorOne =
object
[ "id" .= (1 :: Int),
"name" .= String "Author 1",
"createdAt" .= String "2017-09-21T09:39:44"
]
authorTwo =
object
[ "id" .= (2 :: Int),
"name" .= String "Author 2",
"createdAt" .= String "2017-09-21T09:50:44"
]
shouldReturnOneOfYaml
opts
( GraphqlEngine.postGraphql
testEnvironment
[graphql|
query {
hasura_author {
id
name
createdAt
}
}|]
)
(combinationsObject responseAuthor (map fromObject [authorOne, authorTwo]))
it "fails when placehold query is used with schemas present" $ \testEnvironment ->
shouldReturnYaml
opts
( GraphqlEngine.postGraphql
testEnvironment
[graphql|
query {
no_queries_available
}
|]
)
[yaml|
errors:
- extensions:
code: validation-failed
path: $.selectionSet.no_queries_available
message: |-
field 'no_queries_available' not found in type: 'query_root'
|]
responseAuthor :: Value -> Value
responseAuthor authors =
[yaml|
data:
hasura_author: *authors
|]