2022-08-02 15:51:48 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
|
2022-08-11 18:03:04 +03:00
|
|
|
-- who tests the test framework?
|
2022-08-02 15:51:48 +03:00
|
|
|
module Test.Quoter.YamlSpec (spec) where
|
|
|
|
|
|
|
|
import Data.Aeson qualified as Aeson
|
|
|
|
import Data.Aeson.KeyMap qualified as KM
|
|
|
|
import GHC.Generics
|
|
|
|
import Harness.Quoter.Yaml (interpolateYaml, yaml)
|
|
|
|
import Harness.TestEnvironment
|
2022-08-03 17:18:43 +03:00
|
|
|
import Hasura.Prelude
|
2022-08-02 15:51:48 +03:00
|
|
|
import Test.Hspec
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- test datatype we will use to insert some yaml
|
|
|
|
data MakeSomeYaml = MakeSomeYaml
|
|
|
|
{ msyString :: String,
|
|
|
|
msyBool :: Bool,
|
|
|
|
msyNumber :: Int,
|
|
|
|
msyArray :: [MakeSomeYaml]
|
|
|
|
}
|
|
|
|
deriving stock (Generic)
|
|
|
|
deriving anyclass (Aeson.ToJSON)
|
|
|
|
|
|
|
|
-- ** Preamble
|
|
|
|
|
|
|
|
spec :: SpecWith TestEnvironment
|
|
|
|
spec = describe "Yaml quasiquoters" $ do
|
|
|
|
describe "yaml quoter" $ do
|
|
|
|
it "Interpolates a simple value using a Yaml anchor" $ const do
|
|
|
|
let interpolatedValue = (100 :: Int)
|
|
|
|
let input =
|
|
|
|
[yaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: *interpolatedValue
|
|
|
|
|]
|
|
|
|
let expected =
|
|
|
|
[yaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: 100
|
|
|
|
|]
|
|
|
|
input `shouldBe` expected
|
|
|
|
|
|
|
|
it "Interpolates a complex value using a Yaml anchor" $ const do
|
|
|
|
let complexValue =
|
|
|
|
MakeSomeYaml
|
|
|
|
{ msyString = "hello",
|
|
|
|
msyNumber = 100,
|
|
|
|
msyBool = True,
|
|
|
|
msyArray = []
|
|
|
|
}
|
|
|
|
let expected =
|
|
|
|
Aeson.Object
|
|
|
|
( KM.fromList
|
|
|
|
[ ("type", Aeson.String "thing"),
|
|
|
|
("complex", Aeson.toJSON complexValue)
|
|
|
|
]
|
|
|
|
)
|
|
|
|
|
|
|
|
let input =
|
|
|
|
[yaml|
|
|
|
|
type: thing
|
|
|
|
complex: *complexValue
|
|
|
|
|]
|
|
|
|
input `shouldBe` expected
|
|
|
|
|
|
|
|
it "Interpolates a key using a Yaml anchor" $ const do
|
|
|
|
let interpolatedValue = ("limit" :: String)
|
|
|
|
let input =
|
|
|
|
[yaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
*interpolatedValue: 100
|
|
|
|
|]
|
|
|
|
let expected =
|
|
|
|
[yaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: 100
|
|
|
|
|]
|
|
|
|
input `shouldBe` expected
|
|
|
|
|
|
|
|
describe "interpolateYaml quoter" $ do
|
|
|
|
it "Copes with input that contains lots of single quotes" $ const do
|
|
|
|
let interpolateValue = ("hello" :: String)
|
|
|
|
let input =
|
|
|
|
[interpolateYaml|
|
|
|
|
errors:
|
|
|
|
- extensions:
|
|
|
|
code: validation-failed
|
|
|
|
path: $.selectionSet.hasura_author.selectionSet.notPresentCol
|
|
|
|
message: |-
|
|
|
|
field 'notPresentCol' not found in type: '#{interpolateValue}_author'
|
|
|
|
|]
|
|
|
|
let expected =
|
|
|
|
[interpolateYaml|
|
|
|
|
errors:
|
|
|
|
- extensions:
|
|
|
|
code: validation-failed
|
|
|
|
path: $.selectionSet.hasura_author.selectionSet.notPresentCol
|
|
|
|
message: |-
|
|
|
|
field 'notPresentCol' not found in type: 'hello_author'
|
|
|
|
|]
|
|
|
|
|
|
|
|
input `shouldBe` expected
|
|
|
|
|
|
|
|
it "Interpolates a Haskell value as expected" $ const do
|
|
|
|
let interpolatedValue = (100 :: Int)
|
|
|
|
let input :: Aeson.Value
|
|
|
|
input =
|
|
|
|
[interpolateYaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: #{interpolatedValue}
|
|
|
|
|]
|
|
|
|
let expected :: Aeson.Value
|
|
|
|
expected =
|
|
|
|
[yaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: 100
|
|
|
|
|]
|
|
|
|
input `shouldBe` expected
|
|
|
|
|
|
|
|
it "Interpolates a Haskell expression as expected" $ const do
|
|
|
|
let input :: Aeson.Value
|
|
|
|
input =
|
|
|
|
[interpolateYaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: #{ (1 + 2 + 3 :: Int) }
|
|
|
|
|]
|
|
|
|
let expected :: Aeson.Value
|
|
|
|
expected =
|
|
|
|
[yaml|
|
|
|
|
type: pg_create_select_permission
|
|
|
|
args:
|
|
|
|
limit: 6
|
|
|
|
|]
|
|
|
|
input `shouldBe` expected
|
2022-08-15 20:16:33 +03:00
|
|
|
|
|
|
|
it "Interpolation does not fail when parsing a '*'" $ const do
|
|
|
|
let input :: Aeson.Value
|
|
|
|
input =
|
|
|
|
[interpolateYaml|
|
|
|
|
"*"
|
|
|
|
|]
|
|
|
|
expected =
|
|
|
|
[yaml|
|
|
|
|
"*"
|
|
|
|
|]
|
|
|
|
input `shouldBe` expected
|