mirror of
https://github.com/hasura/graphql-engine.git
synced 2025-01-02 04:25:08 +03:00
9921823915
> ## Description -> This PR allows DC agents to define custom aggregate functions for their scalar types. ### Related Issues -> GDC-189 ### Solution and Design > We added a new property `aggregate_functions` to the scalar types capabilities. This allows the agent author to specify a set of aggregate functions supported by each scalar type, along with the function's result type. During GraphQL schema generation, the custom aggregate functions are available via a new method `getCustomAggregateOperators` on the `Backend` type class. Custom functions are merged with the builtin aggregate functions when building GraphQL schemas for table aggregate fields and for `order_by` operators on array relations. ### Steps to test and verify > • Codec tests for aggregate function capabilities have been added to the unit tests. • Some custom aggregate operators have been added to the reference agent and are used in a new test in `api-tests`. PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6199 GitOrigin-RevId: e9c0d1617af93847c1493671fdbb794f573bde0c
154 lines
4.6 KiB
Haskell
154 lines
4.6 KiB
Haskell
{-# LANGUAGE OverloadedLists #-}
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
module Hasura.Backends.DataConnector.API.V0.OrderBySpec
|
|
( spec,
|
|
genOrderBy,
|
|
genOrderDirection,
|
|
)
|
|
where
|
|
|
|
import Data.Aeson.QQ.Simple (aesonQQ)
|
|
import Data.HashMap.Strict qualified as HashMap
|
|
import Hasura.Backends.DataConnector.API.V0
|
|
import Hasura.Backends.DataConnector.API.V0.AggregateSpec (genSingleColumnAggregate)
|
|
import Hasura.Backends.DataConnector.API.V0.ColumnSpec (genColumnName)
|
|
import Hasura.Backends.DataConnector.API.V0.ExpressionSpec (genExpression)
|
|
import Hasura.Backends.DataConnector.API.V0.RelationshipsSpec (genRelationshipName)
|
|
import Hasura.Generator.Common (defaultRange)
|
|
import Hasura.Prelude
|
|
import Hedgehog
|
|
import Hedgehog.Gen qualified as Gen
|
|
import Language.GraphQL.Draft.Syntax.QQ qualified as G
|
|
import Test.Aeson.Utils (jsonOpenApiProperties, testToFromJSONToSchema)
|
|
import Test.Hspec
|
|
|
|
spec :: Spec
|
|
spec = do
|
|
describe "OrderByTarget" $ do
|
|
describe "OrderByColumn" $
|
|
testToFromJSONToSchema
|
|
(OrderByColumn (ColumnName "test_column"))
|
|
[aesonQQ|
|
|
{ "type": "column",
|
|
"column": "test_column"
|
|
}
|
|
|]
|
|
describe "OrderByStarCountAggregate" $
|
|
testToFromJSONToSchema
|
|
(OrderByStarCountAggregate)
|
|
[aesonQQ|
|
|
{ "type": "star_count_aggregate" }
|
|
|]
|
|
describe "OrderBySingleColumnAggregate" $
|
|
testToFromJSONToSchema
|
|
(OrderBySingleColumnAggregate (SingleColumnAggregate (SingleColumnAggregateFunction [G.name|sum|]) (ColumnName "test_column")))
|
|
[aesonQQ|
|
|
{ "type": "single_column_aggregate",
|
|
"function": "sum",
|
|
"column": "test_column"
|
|
}
|
|
|]
|
|
jsonOpenApiProperties genOrderByTarget
|
|
|
|
describe "OrderByElement" $ do
|
|
testToFromJSONToSchema
|
|
( OrderByElement
|
|
[RelationshipName "relation1", RelationshipName "relation2"]
|
|
(OrderByColumn (ColumnName "my_column_name"))
|
|
Ascending
|
|
)
|
|
[aesonQQ|
|
|
{ "target_path": ["relation1", "relation2"],
|
|
"target": {
|
|
"type": "column",
|
|
"column": "my_column_name"
|
|
},
|
|
"order_direction": "asc"
|
|
}
|
|
|]
|
|
jsonOpenApiProperties genOrderByElement
|
|
|
|
describe "OrderByRelation" $ do
|
|
testToFromJSONToSchema
|
|
( OrderByRelation
|
|
(Just $ And [])
|
|
(HashMap.fromList [(RelationshipName "relationship_name", (OrderByRelation Nothing mempty))])
|
|
)
|
|
[aesonQQ|
|
|
{ "where": {
|
|
"type": "and",
|
|
"expressions": []
|
|
},
|
|
"subrelations": {
|
|
"relationship_name": {
|
|
"subrelations": {}
|
|
}
|
|
}
|
|
}
|
|
|]
|
|
jsonOpenApiProperties genOrderByRelation
|
|
|
|
describe "OrderBy" $ do
|
|
testToFromJSONToSchema
|
|
( OrderBy
|
|
(HashMap.fromList [(RelationshipName "relationship_name", (OrderByRelation Nothing mempty))])
|
|
(OrderByElement [] OrderByStarCountAggregate Ascending :| [])
|
|
)
|
|
[aesonQQ|
|
|
{ "relations": {
|
|
"relationship_name": {
|
|
"subrelations": {}
|
|
}
|
|
},
|
|
"elements": [
|
|
{
|
|
"target_path": [],
|
|
"target": {
|
|
"type": "star_count_aggregate"
|
|
},
|
|
"order_direction": "asc"
|
|
}
|
|
]
|
|
}
|
|
|]
|
|
jsonOpenApiProperties genOrderBy
|
|
|
|
describe "OrderDirection" $ do
|
|
describe "Ascending" $
|
|
testToFromJSONToSchema Ascending [aesonQQ|"asc"|]
|
|
describe "Descending" $
|
|
testToFromJSONToSchema Descending [aesonQQ|"desc"|]
|
|
jsonOpenApiProperties genOrderDirection
|
|
|
|
genOrderBy :: Gen OrderBy
|
|
genOrderBy =
|
|
OrderBy
|
|
<$> (HashMap.fromList <$> Gen.list defaultRange ((,) <$> genRelationshipName <*> genOrderByRelation))
|
|
<*> Gen.nonEmpty defaultRange genOrderByElement
|
|
|
|
genOrderByRelation :: Gen OrderByRelation
|
|
genOrderByRelation =
|
|
OrderByRelation
|
|
<$> Gen.maybe genExpression
|
|
-- Gen.small ensures the recursion will terminate as the size will shrink with each recursion
|
|
<*> Gen.small (HashMap.fromList <$> Gen.list defaultRange ((,) <$> genRelationshipName <*> genOrderByRelation))
|
|
|
|
genOrderByElement :: Gen OrderByElement
|
|
genOrderByElement =
|
|
OrderByElement
|
|
<$> Gen.list defaultRange genRelationshipName
|
|
<*> genOrderByTarget
|
|
<*> genOrderDirection
|
|
|
|
genOrderByTarget :: Gen OrderByTarget
|
|
genOrderByTarget =
|
|
Gen.choice
|
|
[ OrderByColumn <$> genColumnName,
|
|
pure OrderByStarCountAggregate,
|
|
OrderBySingleColumnAggregate <$> genSingleColumnAggregate
|
|
]
|
|
|
|
genOrderDirection :: Gen OrderDirection
|
|
genOrderDirection = Gen.enumBounded
|