graphql-engine/server/src-test/Hasura/Backends/DataConnector/API/V0/ScalarSpec.hs
David Overton 1934e929da Fix flaky round-trip unit tests
Fix bug in round-trip JSON tests for several of the data connectors API types.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6914
GitOrigin-RevId: 07499628a01c45a4fbac2a3672aac2225f27a068
2022-11-17 00:57:19 +00:00

36 lines
1.1 KiB
Haskell

{-# LANGUAGE QuasiQuotes #-}
module Hasura.Backends.DataConnector.API.V0.ScalarSpec (spec, genScalarType) where
import Data.Aeson.QQ.Simple (aesonQQ)
import Hasura.Backends.DataConnector.API.V0.Scalar
import Hasura.Generator.Common (defaultRange, genArbitraryAlphaNumTextExcluding)
import Hasura.Prelude
import Hedgehog
import Hedgehog.Gen qualified as Gen
import Test.Aeson.Utils
import Test.Hspec
spec :: Spec
spec = do
describe "ScalarType" $ do
describe "StringTy" $
testToFromJSONToSchema StringTy [aesonQQ|"string"|]
describe "NumberTy" $
testToFromJSONToSchema NumberTy [aesonQQ|"number"|]
describe "BoolTy" $
testToFromJSONToSchema BoolTy [aesonQQ|"bool"|]
describe "CustomTy" $
testToFromJSONToSchema (CustomTy "foo") [aesonQQ|"foo"|]
jsonOpenApiProperties genScalarType
genScalarType :: (MonadGen m, GenBase m ~ Identity) => m ScalarType
genScalarType =
Gen.choice
[ pure StringTy,
pure NumberTy,
pure BoolTy,
CustomTy
<$> genArbitraryAlphaNumTextExcluding ["string", "number", "bool"] defaultRange
]