graphql-engine/server/src-test/Hasura/Backends/DataConnector/API/V0/AggregateSpec.hs
David Overton 9921823915 GDC-189 custom aggregations
>

## 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
2022-10-27 00:44:06 +00:00

78 lines
2.3 KiB
Haskell

{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE QuasiQuotes #-}
module Hasura.Backends.DataConnector.API.V0.AggregateSpec
( spec,
genAggregate,
genSingleColumnAggregate,
)
where
import Data.Aeson.QQ.Simple (aesonQQ)
import Hasura.Backends.DataConnector.API.V0
import Hasura.Backends.DataConnector.API.V0.ColumnSpec (genColumnName)
import Hasura.Prelude
import Hedgehog
import Hedgehog.Gen qualified as Gen
import Language.GraphQL.Draft.Generator (genName)
import Language.GraphQL.Draft.Syntax.QQ qualified as G
import Test.Aeson.Utils (jsonOpenApiProperties, testToFromJSONToSchema)
import Test.Hspec
spec :: Spec
spec = do
describe "Aggregate" $ do
describe "SingleColumn" $ do
testToFromJSONToSchema
(SingleColumn $ SingleColumnAggregate (SingleColumnAggregateFunction [G.name|avg|]) (ColumnName "my_column_name"))
[aesonQQ|
{ "type": "single_column",
"function": "avg",
"column": "my_column_name"
}
|]
describe "ColumnCount" $ do
testToFromJSONToSchema
(ColumnCount $ ColumnCountAggregate (ColumnName "my_column_name") True)
[aesonQQ|
{ "type": "column_count",
"column": "my_column_name",
"distinct": true
}
|]
describe "StarCount" $ do
testToFromJSONToSchema
(StarCount)
[aesonQQ|
{ "type": "star_count"
}
|]
jsonOpenApiProperties genAggregate
describe "SingleColumnAggregateFunction" $ do
testToFromJSONToSchema (SingleColumnAggregateFunction [G.name|avg|]) [aesonQQ|"avg"|]
jsonOpenApiProperties genSingleColumnAggregateFunction
genAggregate :: Gen Aggregate
genAggregate =
Gen.choice
[ SingleColumn <$> genSingleColumnAggregate,
ColumnCount <$> genColumnCountAggregate,
pure StarCount
]
genSingleColumnAggregate :: Gen SingleColumnAggregate
genSingleColumnAggregate =
SingleColumnAggregate
<$> genSingleColumnAggregateFunction
<*> genColumnName
genColumnCountAggregate :: Gen ColumnCountAggregate
genColumnCountAggregate =
ColumnCountAggregate
<$> genColumnName
<*> Gen.bool
genSingleColumnAggregateFunction :: Gen SingleColumnAggregateFunction
genSingleColumnAggregateFunction = SingleColumnAggregateFunction <$> genName