graphql-engine/server/src-test/Hasura/Backends/Postgres/Execute/PrepareSpec.hs
Samir Talwar 40617719ef server: Remove the Show instance from QErr and anything that touches it.
We only use these `Show` instances in error messages (where we call
`show` explicitly anyway) and test cases (in which Hspec requires `Show
a` for any `a` in an assertion).

This removes the instance in favor of a custom `showQErr` function
(which serializes the error to JSON). It is then used in certain error
message production which previously called `show` on a `QErr`.

There are two places where we serialize a QErr and then construct a new
QErr from the resulting string. Instead, we modify the existing QErr to
add extra information.

An orphan `Show QErr` instance is retained for tests so that we can have
nice test failure messages.

This is preparation for future changes in which the error message within
`QErr` will not be exposed directly, and therefore will not have a
`Show` instance. That said, it feels like a sensible kind of cleanup
anyway.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4897
GitOrigin-RevId: 8f79f7a356f0aea571156f39aefac242bf751f3a
2022-07-01 11:48:26 +00:00

111 lines
4.2 KiB
Haskell

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Hasura.Backends.Postgres.Execute.PrepareSpec
( spec,
)
where
import Control.Monad.Except (MonadError)
import Control.Monad.State (MonadState, StateT, evalStateT)
import Data.Aeson.Extended qualified as J (encodeToStrictText)
import Data.Foldable (for_)
import Data.HashMap.Strict qualified as HashMap
import Data.Text.NonEmpty (mkNonEmptyTextUnsafe)
import Hasura.Backends.Postgres.Execute.Prepare
import Hasura.Backends.Postgres.SQL.DML qualified as S
import Hasura.Backends.Postgres.SQL.Types (PGScalarType (..))
import Hasura.Backends.Postgres.SQL.Value
import Hasura.Base.Error (QErr)
import Hasura.Base.Error.TestInstances ()
import Hasura.GraphQL.Parser.Variable (VariableInfo (..))
import Hasura.RQL.IR.Value (UnpreparedValue (..))
import Hasura.RQL.Types.Column (ColumnType (..), ColumnValue (..))
import Hasura.SQL.Backend (BackendType (..), PostgresKind (..))
import Hasura.SQL.Types (CollectableType (..))
import Hasura.Session
( BackendOnlyFieldAccess (..),
UserInfo (..),
mkRoleNameSafe,
mkSessionVariablesText,
)
import Language.GraphQL.Draft.Syntax.QQ qualified as G
import Test.Hspec (Expectation, Spec, describe, it, shouldBe)
import Prelude
newtype Test x = Test (StateT PlanningSt (Either QErr) x)
deriving newtype (Functor, Applicative, Monad)
deriving newtype (MonadState PlanningSt, MonadError QErr)
yields :: (Eq x, Show x) => Test x -> x -> Expectation
yields (Test program) answer = evalStateT program initPlanningSt `shouldBe` Right answer
spec :: Spec
spec = do
let role = mkRoleNameSafe $ mkNonEmptyTextUnsafe "admin"
userInfo =
UserInfo
{ _uiRole = role,
_uiBackendOnlyFieldAccess = BOFAAllowed,
_uiSession = mkSessionVariablesText do
HashMap.fromList
[ ("foo", "123"),
("bar", "string_two")
]
}
describe "UVSession" do
describe "prepareWithPlan" do
it "returns the correct session variable" do
prepareWithPlan userInfo UVSession `yields` S.SEPrep 1
describe "prepareWithoutPlan" do
it "returns the session variable" do
prepareWithoutPlan userInfo UVSession
`yields` S.SELit (J.encodeToStrictText (_uiSession userInfo))
describe "UVLiteral" do
describe "prepareWithPlan / prepareWithoutPlan" do
it "handles literals in the same way" do
let examples = [S.SEPrep 1, S.SENull, S.SELit "hello"]
for_ examples \x -> do
prepareWithPlan userInfo (UVLiteral x) `yields` x
prepareWithoutPlan userInfo (UVLiteral x) `yields` x
describe "UVParameter" do
let vi = VIRequired [G.name|foo|]
let cv = ColumnValue (ColumnScalar @('Postgres 'Vanilla) PGInteger) (PGValInteger 3)
describe "prepareWithPlan" do
it "returns the indexed paramemter for PGArray" do
let cvArray = ColumnValue (ColumnScalar $ PGArray PGInteger) (PGValArray [PGValInteger 1])
prepareWithPlan userInfo (UVParameter (Just vi) cvArray)
`yields` S.SETyAnn (S.SEPrep 2) (S.TypeAnn "integer[]")
it "returns the indexed parameter for PGInteger" do
-- The variable becomes prepared var (2) because that is the first
-- available parameter index. See 'getVarArgNum'.
prepareWithPlan userInfo (UVParameter (Just vi) cv)
`yields` S.SETyAnn (S.SEPrep 2) (S.TypeAnn "integer")
describe "prepareWithoutPlan" do
it "returns the literal value" do
-- When preparing _without_ a plan, we just inline the value.
prepareWithoutPlan userInfo (UVParameter (Just vi) cv)
`yields` S.SETyAnn (S.SELit "3") (S.TypeAnn "integer")
describe "UVSessionVar" do
let sv = UVSessionVar (CollectableTypeScalar PGInteger) "foo"
describe "prepareWithPlan" do
it "prepares the session variable and accessor" do
prepareWithPlan userInfo sv
`yields` S.SETyAnn (S.SEOpApp (S.SQLOp "->>") [S.SEPrep 1, S.SELit "foo"]) (S.TypeAnn "integer")
describe "prepareWithoutPlan" do
it "inlines the result" do
prepareWithoutPlan userInfo sv
`yields` S.SETyAnn (S.SELit "123") (S.TypeAnn "integer")