Skip to content

Commit

Permalink
feat(tests): Introduce AggregationPredicatesSpec
Browse files Browse the repository at this point in the history
PR-URL: hasura/graphql-engine-mono#5686
GitOrigin-RevId: 85b39ad569180929e5620c45bf9a98ef6ee99d42
  • Loading branch information
plcplc authored and hasura-bot committed Sep 7, 2022
1 parent 8bc34e1 commit d43a30e
Show file tree
Hide file tree
Showing 11 changed files with 568 additions and 17 deletions.
6 changes: 6 additions & 0 deletions server/graphql-engine.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -936,6 +936,8 @@ test-suite graphql-engine-tests
type: exitcode-stdio-1.0
build-depends:
aeson
, aeson-pretty
, aeson-qq
, async
, attoparsec
, base
Expand Down Expand Up @@ -1058,7 +1060,9 @@ test-suite graphql-engine-tests
Hasura.EventingSpec
Hasura.Generator.Common
Hasura.GraphQL.NamespaceSpec
Hasura.GraphQL.Schema.BoolExp.AggregationPredicatesSpec
Hasura.GraphQL.Schema.Build.UpdateSpec
Hasura.GraphQL.Schema.Introspection
Hasura.GraphQL.Schema.RemoteTest
Hasura.IncrementalSpec
Hasura.Metadata.DTO.MetadataDTOSpec
Expand Down Expand Up @@ -1086,11 +1090,13 @@ test-suite graphql-engine-tests
Hasura.SQL.WKTSpec
Hasura.StreamingSubscriptionSuite
Network.HTTP.Client.TransformableSpec
Test.Aeson.Expectation
Test.Aeson.Utils
Test.Backend.Postgres.Delete
Test.Backend.Postgres.Insert
Test.Backend.Postgres.Misc
Test.Backend.Postgres.Update
Test.Hspec.Extended
Test.Parser.Delete
Test.Parser.Expectation
Test.Parser.Field
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ defaultAggregationPredicatesParser aggFns si ti = runMaybeT do
arrayRelationships <&> \rel -> do
relTable <- askTableInfo si (riRTable rel)
relGqlName <- textToName $ relNameToTxt $ riName rel
typeGqlName <- (<> Name.__ <> relGqlName) <$> getTableGQLName relTable
typeGqlName <- (<> Name.__ <> relGqlName <> Name.__ <> Name._aggregate) <$> getTableGQLName ti

-- We only make a field for aggregations over a relation if at least
-- some aggregation predicates are callable.
Expand Down Expand Up @@ -102,7 +102,7 @@ defaultAggregationPredicatesParser aggFns si ti = runMaybeT do
G.Name ->
(InputFieldsParser n [AggregationPredicate b (UnpreparedValue b)]) ->
(InputFieldsParser n (Maybe (AggregationPredicatesImplementation b (UnpreparedValue b))))
relAggregateField rel typeGqlName relGqlName =
relAggregateField rel relGqlName typeGqlName =
P.fieldOptional (relGqlName <> Name.__ <> Name._aggregate) Nothing
. P.object typeGqlName Nothing
. fmap (AggregationPredicatesImplementation rel)
Expand Down
2 changes: 1 addition & 1 deletion server/src-lib/Hasura/RQL/Types/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ data SourceInfo b = SourceInfo
{ _siName :: SourceName,
_siTables :: TableCache b,
_siFunctions :: FunctionCache b,
_siConfiguration :: SourceConfig b,
_siConfiguration :: ~(SourceConfig b),
_siQueryTagsConfig :: Maybe QueryTagsConfig,
_siCustomization :: SourceCustomization
}
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,306 @@
{-# LANGUAGE QuasiQuotes #-}

-- | This module contain unit tests of the schema of the default implementation
-- of aggregation predicates.
module Hasura.GraphQL.Schema.BoolExp.AggregationPredicatesSpec (spec) where

import Data.Aeson.QQ (aesonQQ)
import Data.HashMap.Strict qualified as HM
import Data.Text.NonEmpty (nonEmptyTextQQ)
import Hasura.Backends.Postgres.Instances.Schema ()
import Hasura.Backends.Postgres.SQL.Types
( PGScalarType (PGInteger, PGText),
QualifiedTable,
)
import Hasura.Backends.Postgres.SQL.Value (PGScalarValue (..))
import Hasura.GraphQL.Parser.Internal.Input (ifParser)
import Hasura.GraphQL.Schema.BoolExp.AggregationPredicates
( ArgumentsSignature (..),
FunctionSignature (..),
defaultAggregationPredicatesParser,
)
import Hasura.GraphQL.Schema.Introspection (queryInputFieldsParserIntrospection)
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp (OpExpG (AEQ))
import Hasura.RQL.IR.BoolExp.AggregationPredicates
import Hasura.RQL.IR.Value (UnpreparedValue (UVParameter))
import Hasura.RQL.Types.Column (ColumnType (ColumnScalar), ColumnValue (..))
import Hasura.RQL.Types.Common (InsertOrder (..), RelName (..), RelType (..), SourceName (..))
import Hasura.RQL.Types.Relationships.Local (RelInfo (..))
import Hasura.RQL.Types.Source (SourceInfo (..))
import Hasura.RQL.Types.SourceCustomization (SourceCustomization (SourceCustomization))
import Hasura.RQL.Types.Table
( TableCoreInfoG (_tciName),
TableInfo (_tiCoreInfo),
)
import Hasura.SQL.Backend (BackendType (Postgres), PostgresKind (Vanilla))
import Language.GraphQL.Draft.Syntax qualified as G
import Language.GraphQL.Draft.Syntax.QQ qualified as G
import Test.Aeson.Expectation (shouldBeSubsetOf)
import Test.Hspec
import Test.Hspec.Extended
import Test.Parser.Field qualified as GQL
import Test.Parser.Internal
( ColumnInfoBuilder
( ColumnInfoBuilder,
cibIsPrimaryKey,
cibName,
cibNullable,
cibType
),
TableInfoBuilder (columns, relations),
buildTableInfo,
mkTable,
tableInfoBuilder,
)
import Test.Parser.Monad
( ParserTest (runParserTest),
notImplementedYet,
runSchemaTest,
)
import Type.Reflection (Typeable, typeRep)

{- Notes:
AggregationPredicates are defined as a standalone feature. It should be possible
to test them without reference to an existing backend.
We cannot do that however, since backends have the closed datakind `BackendType`.
-}

newtype Unshowable a = Unshowable {unUnshowable :: a}
deriving (Eq, Ord)

instance Typeable a => Show (Unshowable a) where
show _ = "Unshowable<" ++ show (typeRep @a) ++ ">"

spec :: Spec
spec = do
describe "Aggregation Predicates Schema Parsers" do
describe "When no aggregation functions are given" do
it "Yields no parsers" do
let maybeParser =
runSchemaTest $
defaultAggregationPredicatesParser @('Postgres 'Vanilla) @_ @_ @ParserTest
[]
sourceInfo
albumTableInfo
(Unshowable maybeParser) `shouldSatisfy` (isNothing . unUnshowable)

describe "When some aggregation functions are given" do
let maybeParser =
runSchemaTest $
defaultAggregationPredicatesParser @('Postgres 'Vanilla) @_ @_ @ParserTest
[ FunctionSignature
{ fnName = "count",
fnGQLName = [G.name|count|],
fnArguments = ArgumentsStar,
fnReturnType = PGInteger
}
]
sourceInfo
albumTableInfo

it "Positively yields a parser" do
(Unshowable maybeParser) `shouldSatisfy` (isJust . unUnshowable)

dependentSpec maybeParser $ do
it "Defines the expected GraphQL types" \parser -> do
introspectionResult <-
queryInputFieldsParserIntrospection
parser
[GQL.field|
__schema {
types {
name
fields {
name
type { name }
}
inputFields {
name
type { name }
}
}
} |]

let expectedTopLevel =
[aesonQQ|
{ "types": [
{
"name": "album_tracks_aggregate",
"fields": null,
"inputFields": [
{
"name": "count",
"type": {
"name": "album_tracks_aggregate_count"
}
}
]
}
]
}
|]
let expectedCountType =
[aesonQQ|
{ "types": [
{
"name": "album_tracks_aggregate_count",
"fields": null,
"inputFields": [
{
"name": "arguments",
"type": {
"name": null
}
},
{
"name": "distinct",
"type": {
"name": "Boolean"
}
},
{
"name": "filter",
"type": {
"name": "track_bool_exp"
}
},
{
"name": "predicate",
"type": {
"name": null
}
}
]
}
]
}
|]

expectedTopLevel `shouldBeSubsetOf` introspectionResult
expectedCountType `shouldBeSubsetOf` introspectionResult

it "Parses an example field" \parser -> do
let input =
[GQL.inputfields|
tracks_aggregate: {
count: {
arguments: [],
predicate: {_eq : 42 },
distinct: true
}
}
|]
actual <- runParserTest $ ifParser parser input

let expected :: [AggregationPredicatesImplementation ('Postgres 'Vanilla) (UnpreparedValue ('Postgres 'Vanilla))]
expected =
[ AggregationPredicatesImplementation
{ aggRelation = tracksRel,
aggPredicates =
[ AggregationPredicate
{ aggPredFunctionName = "count",
aggPredArguments = AggregationPredicateArgumentsStar,
aggPredDistinct = True,
aggPredFilter = Nothing,
aggPredPredicate =
[ AEQ
True
( UVParameter
Nothing
( ColumnValue
{ cvType = ColumnScalar PGInteger,
cvValue = PGValInteger 42
}
)
)
]
}
]
}
]

actual `shouldBe` expected
where
albumTableInfo :: TableInfo ('Postgres 'Vanilla)
albumTableInfo =
buildTableInfo
( (tableInfoBuilder (mkTable "album"))
{ columns =
[ ColumnInfoBuilder
{ cibName = "id",
cibType = ColumnScalar PGInteger,
cibNullable = False,
cibIsPrimaryKey = True
},
ColumnInfoBuilder
{ cibName = "title",
cibType = ColumnScalar PGText,
cibNullable = False,
cibIsPrimaryKey = False
}
],
relations = [tracksRel]
}
)

trackTableInfo :: TableInfo ('Postgres 'Vanilla)
trackTableInfo =
buildTableInfo
( (tableInfoBuilder (mkTable "track"))
{ columns =
[ ColumnInfoBuilder
{ cibName = "id",
cibType = ColumnScalar PGInteger,
cibNullable = False,
cibIsPrimaryKey = True
},
ColumnInfoBuilder
{ cibName = "title",
cibType = ColumnScalar PGText,
cibNullable = False,
cibIsPrimaryKey = False
},
ColumnInfoBuilder
{ cibName = "duration_seconds",
cibType = ColumnScalar PGInteger,
cibNullable = False,
cibIsPrimaryKey = False
},
ColumnInfoBuilder
{ cibName = "album_id",
cibType = ColumnScalar PGInteger,
cibNullable = False,
cibIsPrimaryKey = False
}
]
}
)

tracksRel :: RelInfo ('Postgres 'Vanilla)
tracksRel =
RelInfo
{ riName = RelName [nonEmptyTextQQ|tracks|],
riType = ArrRel,
riMapping = HM.fromList [("id", "album_id")],
riRTable = (mkTable "track"),
riIsManual = False,
riInsertOrder = AfterParent
}

sourceInfo :: SourceInfo ('Postgres 'Vanilla)
sourceInfo =
SourceInfo
{ _siName = SNDefault,
_siTables = makeTableCache [albumTableInfo, trackTableInfo],
_siFunctions = mempty,
_siConfiguration = notImplementedYet "SourceConfig",
_siQueryTagsConfig = Nothing,
_siCustomization = SourceCustomization Nothing Nothing Nothing
}

makeTableCache :: [TableInfo ('Postgres 'Vanilla)] -> HashMap QualifiedTable (TableInfo ('Postgres 'Vanilla))
makeTableCache tables = HM.fromList [(_tciName $ _tiCoreInfo ti, ti) | ti <- tables]
Loading

0 comments on commit d43a30e

Please sign in to comment.