graphql/tests/Test/DirectiveSpec.hs

97 lines
2.9 KiB
Haskell
Raw Normal View History

{- This Source Code Form is subject to the terms of the Mozilla Public License,
v. 2.0. If a copy of the MPL was not distributed with this file, You can
obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Test.DirectiveSpec
( spec
) where
import Data.Aeson (object, (.=))
import qualified Data.Aeson as Aeson
import qualified Data.HashMap.Strict as HashMap
import Language.GraphQL
2020-06-19 10:53:41 +02:00
import Language.GraphQL.Type
2020-05-24 13:51:00 +02:00
import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec (Spec, describe, it, shouldBe)
import Text.RawString.QQ (r)
2020-05-14 09:17:14 +02:00
experimentalResolver :: Schema IO
experimentalResolver = Schema
{ query = queryType, mutation = Nothing, subscription = Nothing }
2020-05-14 09:17:14 +02:00
where
queryType = Out.ObjectType "Query" Nothing []
2020-05-14 09:17:14 +02:00
$ HashMap.singleton "experimentalField"
$ Out.ValueResolver (Out.Field Nothing (Out.NamedScalarType int) mempty)
$ pure $ Int 5
emptyObject :: Aeson.Value
emptyObject = object
[ "data" .= object []
]
spec :: Spec
spec =
describe "Directive executor" $ do
it "should be able to @skip fields" $ do
2020-05-14 09:17:14 +02:00
let sourceQuery = [r|
{
experimentalField @skip(if: true)
}
|]
2020-05-14 09:17:14 +02:00
actual <- graphql experimentalResolver sourceQuery
actual `shouldBe` emptyObject
it "should not skip fields if @skip is false" $ do
2020-05-14 09:17:14 +02:00
let sourceQuery = [r|
{
experimentalField @skip(if: false)
}
|]
expected = object
[ "data" .= object
[ "experimentalField" .= (5 :: Int)
]
]
2020-05-14 09:17:14 +02:00
actual <- graphql experimentalResolver sourceQuery
actual `shouldBe` expected
it "should skip fields if @include is false" $ do
2020-05-14 09:17:14 +02:00
let sourceQuery = [r|
{
experimentalField @include(if: false)
}
|]
2020-05-14 09:17:14 +02:00
actual <- graphql experimentalResolver sourceQuery
actual `shouldBe` emptyObject
it "should be able to @skip a fragment spread" $ do
2020-05-14 09:17:14 +02:00
let sourceQuery = [r|
{
...experimentalFragment @skip(if: true)
}
fragment experimentalFragment on ExperimentalType {
experimentalField
}
|]
2020-05-14 09:17:14 +02:00
actual <- graphql experimentalResolver sourceQuery
actual `shouldBe` emptyObject
it "should be able to @skip an inline fragment" $ do
2020-05-14 09:17:14 +02:00
let sourceQuery = [r|
{
... on ExperimentalType @skip(if: true) {
experimentalField
}
}
|]
2020-05-14 09:17:14 +02:00
actual <- graphql experimentalResolver sourceQuery
actual `shouldBe` emptyObject