mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-18 13:02:11 +03:00
5c06eb7a3e
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5930 GitOrigin-RevId: 8c11387fa8556c3cdf8c92a0924ae53d31b953a5
30 lines
960 B
Haskell
30 lines
960 B
Haskell
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
module Hasura.Backends.DataConnector.API.V0.ScalarSpec (spec, genType) where
|
|
|
|
import Data.Aeson.QQ.Simple (aesonQQ)
|
|
import Hasura.Backends.DataConnector.API.V0.Scalar
|
|
import Hasura.Generator.Common (defaultRange, genArbitraryAlphaNumText)
|
|
import Hasura.Prelude
|
|
import Hedgehog
|
|
import Hedgehog.Gen qualified as Gen
|
|
import Test.Aeson.Utils
|
|
import Test.Hspec
|
|
|
|
spec :: Spec
|
|
spec = do
|
|
describe "Type" $ 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 genType
|
|
|
|
genType :: MonadGen m => m ScalarType
|
|
genType =
|
|
Gen.choice [pure StringTy, pure NumberTy, pure BoolTy, CustomTy <$> genArbitraryAlphaNumText defaultRange]
|