1--
2-- AGGREGATES
3--
4
5-- avoid bit-exact output here because operations may not be bit-exact.
6SET extra_float_digits = 0;
7
8SELECT avg(four) AS avg_1 FROM onek;
9
10SELECT avg(a) AS avg_32 FROM aggtest WHERE a < 100;
11
12-- In 7.1, avg(float4) is computed using float8 arithmetic.
13-- Round the result to 3 digits to avoid platform-specific results.
14
15SELECT avg(b)::numeric(10,3) AS avg_107_943 FROM aggtest;
16
17SELECT avg(gpa) AS avg_3_4 FROM ONLY student;
18
19
20SELECT sum(four) AS sum_1500 FROM onek;
21SELECT sum(a) AS sum_198 FROM aggtest;
22SELECT sum(b) AS avg_431_773 FROM aggtest;
23SELECT sum(gpa) AS avg_6_8 FROM ONLY student;
24
25SELECT max(four) AS max_3 FROM onek;
26SELECT max(a) AS max_100 FROM aggtest;
27SELECT max(aggtest.b) AS max_324_78 FROM aggtest;
28SELECT max(student.gpa) AS max_3_7 FROM student;
29
30SELECT stddev_pop(b) FROM aggtest;
31SELECT stddev_samp(b) FROM aggtest;
32SELECT var_pop(b) FROM aggtest;
33SELECT var_samp(b) FROM aggtest;
34
35SELECT stddev_pop(b::numeric) FROM aggtest;
36SELECT stddev_samp(b::numeric) FROM aggtest;
37SELECT var_pop(b::numeric) FROM aggtest;
38SELECT var_samp(b::numeric) FROM aggtest;
39
40-- population variance is defined for a single tuple, sample variance
41-- is not
42SELECT var_pop(1.0::float8), var_samp(2.0::float8);
43SELECT stddev_pop(3.0::float8), stddev_samp(4.0::float8);
44SELECT var_pop('inf'::float8), var_samp('inf'::float8);
45SELECT stddev_pop('inf'::float8), stddev_samp('inf'::float8);
46SELECT var_pop('nan'::float8), var_samp('nan'::float8);
47SELECT stddev_pop('nan'::float8), stddev_samp('nan'::float8);
48SELECT var_pop(1.0::float4), var_samp(2.0::float4);
49SELECT stddev_pop(3.0::float4), stddev_samp(4.0::float4);
50SELECT var_pop('inf'::float4), var_samp('inf'::float4);
51SELECT stddev_pop('inf'::float4), stddev_samp('inf'::float4);
52SELECT var_pop('nan'::float4), var_samp('nan'::float4);
53SELECT stddev_pop('nan'::float4), stddev_samp('nan'::float4);
54SELECT var_pop(1.0::numeric), var_samp(2.0::numeric);
55SELECT stddev_pop(3.0::numeric), stddev_samp(4.0::numeric);
56SELECT var_pop('inf'::numeric), var_samp('inf'::numeric);
57SELECT stddev_pop('inf'::numeric), stddev_samp('inf'::numeric);
58SELECT var_pop('nan'::numeric), var_samp('nan'::numeric);
59SELECT stddev_pop('nan'::numeric), stddev_samp('nan'::numeric);
60
61-- verify correct results for null and NaN inputs
62select sum(null::int4) from generate_series(1,3);
63select sum(null::int8) from generate_series(1,3);
64select sum(null::numeric) from generate_series(1,3);
65select sum(null::float8) from generate_series(1,3);
66select avg(null::int4) from generate_series(1,3);
67select avg(null::int8) from generate_series(1,3);
68select avg(null::numeric) from generate_series(1,3);
69select avg(null::float8) from generate_series(1,3);
70select sum('NaN'::numeric) from generate_series(1,3);
71select avg('NaN'::numeric) from generate_series(1,3);
72
73-- verify correct results for infinite inputs
74SELECT sum(x::float8), avg(x::float8), var_pop(x::float8)
75FROM (VALUES ('1'), ('infinity')) v(x);
76SELECT sum(x::float8), avg(x::float8), var_pop(x::float8)
77FROM (VALUES ('infinity'), ('1')) v(x);
78SELECT sum(x::float8), avg(x::float8), var_pop(x::float8)
79FROM (VALUES ('infinity'), ('infinity')) v(x);
80SELECT sum(x::float8), avg(x::float8), var_pop(x::float8)
81FROM (VALUES ('-infinity'), ('infinity')) v(x);
82SELECT sum(x::float8), avg(x::float8), var_pop(x::float8)
83FROM (VALUES ('-infinity'), ('-infinity')) v(x);
84SELECT sum(x::numeric), avg(x::numeric), var_pop(x::numeric)
85FROM (VALUES ('1'), ('infinity')) v(x);
86SELECT sum(x::numeric), avg(x::numeric), var_pop(x::numeric)
87FROM (VALUES ('infinity'), ('1')) v(x);
88SELECT sum(x::numeric), avg(x::numeric), var_pop(x::numeric)
89FROM (VALUES ('infinity'), ('infinity')) v(x);
90SELECT sum(x::numeric), avg(x::numeric), var_pop(x::numeric)
91FROM (VALUES ('-infinity'), ('infinity')) v(x);
92SELECT sum(x::numeric), avg(x::numeric), var_pop(x::numeric)
93FROM (VALUES ('-infinity'), ('-infinity')) v(x);
94
95-- test accuracy with a large input offset
96SELECT avg(x::float8), var_pop(x::float8)
97FROM (VALUES (100000003), (100000004), (100000006), (100000007)) v(x);
98SELECT avg(x::float8), var_pop(x::float8)
99FROM (VALUES (7000000000005), (7000000000007)) v(x);
100
101-- SQL2003 binary aggregates
102SELECT regr_count(b, a) FROM aggtest;
103SELECT regr_sxx(b, a) FROM aggtest;
104SELECT regr_syy(b, a) FROM aggtest;
105SELECT regr_sxy(b, a) FROM aggtest;
106SELECT regr_avgx(b, a), regr_avgy(b, a) FROM aggtest;
107SELECT regr_r2(b, a) FROM aggtest;
108SELECT regr_slope(b, a), regr_intercept(b, a) FROM aggtest;
109SELECT covar_pop(b, a), covar_samp(b, a) FROM aggtest;
110SELECT corr(b, a) FROM aggtest;
111
112-- check single-tuple behavior
113SELECT covar_pop(1::float8,2::float8), covar_samp(3::float8,4::float8);
114SELECT covar_pop(1::float8,'inf'::float8), covar_samp(3::float8,'inf'::float8);
115SELECT covar_pop(1::float8,'nan'::float8), covar_samp(3::float8,'nan'::float8);
116
117-- test accum and combine functions directly
118CREATE TABLE regr_test (x float8, y float8);
119INSERT INTO regr_test VALUES (10,150),(20,250),(30,350),(80,540),(100,200);
120SELECT count(*), sum(x), regr_sxx(y,x), sum(y),regr_syy(y,x), regr_sxy(y,x)
121FROM regr_test WHERE x IN (10,20,30,80);
122SELECT count(*), sum(x), regr_sxx(y,x), sum(y),regr_syy(y,x), regr_sxy(y,x)
123FROM regr_test;
124SELECT float8_accum('{4,140,2900}'::float8[], 100);
125SELECT float8_regr_accum('{4,140,2900,1290,83075,15050}'::float8[], 200, 100);
126SELECT count(*), sum(x), regr_sxx(y,x), sum(y),regr_syy(y,x), regr_sxy(y,x)
127FROM regr_test WHERE x IN (10,20,30);
128SELECT count(*), sum(x), regr_sxx(y,x), sum(y),regr_syy(y,x), regr_sxy(y,x)
129FROM regr_test WHERE x IN (80,100);
130SELECT float8_combine('{3,60,200}'::float8[], '{0,0,0}'::float8[]);
131SELECT float8_combine('{0,0,0}'::float8[], '{2,180,200}'::float8[]);
132SELECT float8_combine('{3,60,200}'::float8[], '{2,180,200}'::float8[]);
133SELECT float8_regr_combine('{3,60,200,750,20000,2000}'::float8[],
134                           '{0,0,0,0,0,0}'::float8[]);
135SELECT float8_regr_combine('{0,0,0,0,0,0}'::float8[],
136                           '{2,180,200,740,57800,-3400}'::float8[]);
137SELECT float8_regr_combine('{3,60,200,750,20000,2000}'::float8[],
138                           '{2,180,200,740,57800,-3400}'::float8[]);
139DROP TABLE regr_test;
140
141-- test count, distinct
142SELECT count(four) AS cnt_1000 FROM onek;
143SELECT count(DISTINCT four) AS cnt_4 FROM onek;
144
145select ten, count(*), sum(four) from onek
146group by ten order by ten;
147
148select ten, count(four), sum(DISTINCT four) from onek
149group by ten order by ten;
150
151-- user-defined aggregates
152SELECT newavg(four) AS avg_1 FROM onek;
153SELECT newsum(four) AS sum_1500 FROM onek;
154SELECT newcnt(four) AS cnt_1000 FROM onek;
155SELECT newcnt(*) AS cnt_1000 FROM onek;
156SELECT oldcnt(*) AS cnt_1000 FROM onek;
157SELECT sum2(q1,q2) FROM int8_tbl;
158
159-- test for outer-level aggregates
160
161-- this should work
162select ten, sum(distinct four) from onek a
163group by ten
164having exists (select 1 from onek b where sum(distinct a.four) = b.four);
165
166-- this should fail because subquery has an agg of its own in WHERE
167select ten, sum(distinct four) from onek a
168group by ten
169having exists (select 1 from onek b
170               where sum(distinct a.four + b.four) = b.four);
171
172-- Test handling of sublinks within outer-level aggregates.
173-- Per bug report from Daniel Grace.
174select
175  (select max((select i.unique2 from tenk1 i where i.unique1 = o.unique1)))
176from tenk1 o;
177
178-- Test handling of Params within aggregate arguments in hashed aggregation.
179-- Per bug report from Jeevan Chalke.
180explain (verbose, costs off)
181select s1, s2, sm
182from generate_series(1, 3) s1,
183     lateral (select s2, sum(s1 + s2) sm
184              from generate_series(1, 3) s2 group by s2) ss
185order by 1, 2;
186select s1, s2, sm
187from generate_series(1, 3) s1,
188     lateral (select s2, sum(s1 + s2) sm
189              from generate_series(1, 3) s2 group by s2) ss
190order by 1, 2;
191
192explain (verbose, costs off)
193select array(select sum(x+y) s
194            from generate_series(1,3) y group by y order by s)
195  from generate_series(1,3) x;
196select array(select sum(x+y) s
197            from generate_series(1,3) y group by y order by s)
198  from generate_series(1,3) x;
199
200--
201-- test for bitwise integer aggregates
202--
203CREATE TEMPORARY TABLE bitwise_test(
204  i2 INT2,
205  i4 INT4,
206  i8 INT8,
207  i INTEGER,
208  x INT2,
209  y BIT(4)
210);
211
212-- empty case
213SELECT
214  BIT_AND(i2) AS "?",
215  BIT_OR(i4)  AS "?",
216  BIT_XOR(i8) AS "?"
217FROM bitwise_test;
218
219COPY bitwise_test FROM STDIN NULL 'null';
2201	1	1	1	1	B0101
2213	3	3	null	2	B0100
2227	7	7	3	4	B1100
223\.
224
225SELECT
226  BIT_AND(i2) AS "1",
227  BIT_AND(i4) AS "1",
228  BIT_AND(i8) AS "1",
229  BIT_AND(i)  AS "?",
230  BIT_AND(x)  AS "0",
231  BIT_AND(y)  AS "0100",
232
233  BIT_OR(i2)  AS "7",
234  BIT_OR(i4)  AS "7",
235  BIT_OR(i8)  AS "7",
236  BIT_OR(i)   AS "?",
237  BIT_OR(x)   AS "7",
238  BIT_OR(y)   AS "1101",
239
240  BIT_XOR(i2) AS "5",
241  BIT_XOR(i4) AS "5",
242  BIT_XOR(i8) AS "5",
243  BIT_XOR(i)  AS "?",
244  BIT_XOR(x)  AS "7",
245  BIT_XOR(y)  AS "1101"
246FROM bitwise_test;
247
248--
249-- test boolean aggregates
250--
251-- first test all possible transition and final states
252
253SELECT
254  -- boolean and transitions
255  -- null because strict
256  booland_statefunc(NULL, NULL)  IS NULL AS "t",
257  booland_statefunc(TRUE, NULL)  IS NULL AS "t",
258  booland_statefunc(FALSE, NULL) IS NULL AS "t",
259  booland_statefunc(NULL, TRUE)  IS NULL AS "t",
260  booland_statefunc(NULL, FALSE) IS NULL AS "t",
261  -- and actual computations
262  booland_statefunc(TRUE, TRUE) AS "t",
263  NOT booland_statefunc(TRUE, FALSE) AS "t",
264  NOT booland_statefunc(FALSE, TRUE) AS "t",
265  NOT booland_statefunc(FALSE, FALSE) AS "t";
266
267SELECT
268  -- boolean or transitions
269  -- null because strict
270  boolor_statefunc(NULL, NULL)  IS NULL AS "t",
271  boolor_statefunc(TRUE, NULL)  IS NULL AS "t",
272  boolor_statefunc(FALSE, NULL) IS NULL AS "t",
273  boolor_statefunc(NULL, TRUE)  IS NULL AS "t",
274  boolor_statefunc(NULL, FALSE) IS NULL AS "t",
275  -- actual computations
276  boolor_statefunc(TRUE, TRUE) AS "t",
277  boolor_statefunc(TRUE, FALSE) AS "t",
278  boolor_statefunc(FALSE, TRUE) AS "t",
279  NOT boolor_statefunc(FALSE, FALSE) AS "t";
280
281CREATE TEMPORARY TABLE bool_test(
282  b1 BOOL,
283  b2 BOOL,
284  b3 BOOL,
285  b4 BOOL);
286
287-- empty case
288SELECT
289  BOOL_AND(b1)   AS "n",
290  BOOL_OR(b3)    AS "n"
291FROM bool_test;
292
293COPY bool_test FROM STDIN NULL 'null';
294TRUE	null	FALSE	null
295FALSE	TRUE	null	null
296null	TRUE	FALSE	null
297\.
298
299SELECT
300  BOOL_AND(b1)     AS "f",
301  BOOL_AND(b2)     AS "t",
302  BOOL_AND(b3)     AS "f",
303  BOOL_AND(b4)     AS "n",
304  BOOL_AND(NOT b2) AS "f",
305  BOOL_AND(NOT b3) AS "t"
306FROM bool_test;
307
308SELECT
309  EVERY(b1)     AS "f",
310  EVERY(b2)     AS "t",
311  EVERY(b3)     AS "f",
312  EVERY(b4)     AS "n",
313  EVERY(NOT b2) AS "f",
314  EVERY(NOT b3) AS "t"
315FROM bool_test;
316
317SELECT
318  BOOL_OR(b1)      AS "t",
319  BOOL_OR(b2)      AS "t",
320  BOOL_OR(b3)      AS "f",
321  BOOL_OR(b4)      AS "n",
322  BOOL_OR(NOT b2)  AS "f",
323  BOOL_OR(NOT b3)  AS "t"
324FROM bool_test;
325
326--
327-- Test cases that should be optimized into indexscans instead of
328-- the generic aggregate implementation.
329--
330
331-- Basic cases
332explain (costs off)
333  select min(unique1) from tenk1;
334select min(unique1) from tenk1;
335explain (costs off)
336  select max(unique1) from tenk1;
337select max(unique1) from tenk1;
338explain (costs off)
339  select max(unique1) from tenk1 where unique1 < 42;
340select max(unique1) from tenk1 where unique1 < 42;
341explain (costs off)
342  select max(unique1) from tenk1 where unique1 > 42;
343select max(unique1) from tenk1 where unique1 > 42;
344
345-- the planner may choose a generic aggregate here if parallel query is
346-- enabled, since that plan will be parallel safe and the "optimized"
347-- plan, which has almost identical cost, will not be.  we want to test
348-- the optimized plan, so temporarily disable parallel query.
349begin;
350set local max_parallel_workers_per_gather = 0;
351explain (costs off)
352  select max(unique1) from tenk1 where unique1 > 42000;
353select max(unique1) from tenk1 where unique1 > 42000;
354rollback;
355
356-- multi-column index (uses tenk1_thous_tenthous)
357explain (costs off)
358  select max(tenthous) from tenk1 where thousand = 33;
359select max(tenthous) from tenk1 where thousand = 33;
360explain (costs off)
361  select min(tenthous) from tenk1 where thousand = 33;
362select min(tenthous) from tenk1 where thousand = 33;
363
364-- check parameter propagation into an indexscan subquery
365explain (costs off)
366  select f1, (select min(unique1) from tenk1 where unique1 > f1) AS gt
367    from int4_tbl;
368select f1, (select min(unique1) from tenk1 where unique1 > f1) AS gt
369  from int4_tbl;
370
371-- check some cases that were handled incorrectly in 8.3.0
372explain (costs off)
373  select distinct max(unique2) from tenk1;
374select distinct max(unique2) from tenk1;
375explain (costs off)
376  select max(unique2) from tenk1 order by 1;
377select max(unique2) from tenk1 order by 1;
378explain (costs off)
379  select max(unique2) from tenk1 order by max(unique2);
380select max(unique2) from tenk1 order by max(unique2);
381explain (costs off)
382  select max(unique2) from tenk1 order by max(unique2)+1;
383select max(unique2) from tenk1 order by max(unique2)+1;
384explain (costs off)
385  select max(unique2), generate_series(1,3) as g from tenk1 order by g desc;
386select max(unique2), generate_series(1,3) as g from tenk1 order by g desc;
387
388-- interesting corner case: constant gets optimized into a seqscan
389explain (costs off)
390  select max(100) from tenk1;
391select max(100) from tenk1;
392
393-- try it on an inheritance tree
394create table minmaxtest(f1 int);
395create table minmaxtest1() inherits (minmaxtest);
396create table minmaxtest2() inherits (minmaxtest);
397create table minmaxtest3() inherits (minmaxtest);
398create index minmaxtesti on minmaxtest(f1);
399create index minmaxtest1i on minmaxtest1(f1);
400create index minmaxtest2i on minmaxtest2(f1 desc);
401create index minmaxtest3i on minmaxtest3(f1) where f1 is not null;
402
403insert into minmaxtest values(11), (12);
404insert into minmaxtest1 values(13), (14);
405insert into minmaxtest2 values(15), (16);
406insert into minmaxtest3 values(17), (18);
407
408explain (costs off)
409  select min(f1), max(f1) from minmaxtest;
410select min(f1), max(f1) from minmaxtest;
411
412-- DISTINCT doesn't do anything useful here, but it shouldn't fail
413explain (costs off)
414  select distinct min(f1), max(f1) from minmaxtest;
415select distinct min(f1), max(f1) from minmaxtest;
416
417drop table minmaxtest cascade;
418
419-- check for correct detection of nested-aggregate errors
420select max(min(unique1)) from tenk1;
421select (select max(min(unique1)) from int8_tbl) from tenk1;
422
423--
424-- Test removal of redundant GROUP BY columns
425--
426
427create temp table t1 (a int, b int, c int, d int, primary key (a, b));
428create temp table t2 (x int, y int, z int, primary key (x, y));
429create temp table t3 (a int, b int, c int, primary key(a, b) deferrable);
430
431-- Non-primary-key columns can be removed from GROUP BY
432explain (costs off) select * from t1 group by a,b,c,d;
433
434-- No removal can happen if the complete PK is not present in GROUP BY
435explain (costs off) select a,c from t1 group by a,c,d;
436
437-- Test removal across multiple relations
438explain (costs off) select *
439from t1 inner join t2 on t1.a = t2.x and t1.b = t2.y
440group by t1.a,t1.b,t1.c,t1.d,t2.x,t2.y,t2.z;
441
442-- Test case where t1 can be optimized but not t2
443explain (costs off) select t1.*,t2.x,t2.z
444from t1 inner join t2 on t1.a = t2.x and t1.b = t2.y
445group by t1.a,t1.b,t1.c,t1.d,t2.x,t2.z;
446
447-- Cannot optimize when PK is deferrable
448explain (costs off) select * from t3 group by a,b,c;
449
450create temp table t1c () inherits (t1);
451
452-- Ensure we don't remove any columns when t1 has a child table
453explain (costs off) select * from t1 group by a,b,c,d;
454
455-- Okay to remove columns if we're only querying the parent.
456explain (costs off) select * from only t1 group by a,b,c,d;
457
458create temp table p_t1 (
459  a int,
460  b int,
461  c int,
462  d int,
463  primary key(a,b)
464) partition by list(a);
465create temp table p_t1_1 partition of p_t1 for values in(1);
466create temp table p_t1_2 partition of p_t1 for values in(2);
467
468-- Ensure we can remove non-PK columns for partitioned tables.
469explain (costs off) select * from p_t1 group by a,b,c,d;
470
471drop table t1 cascade;
472drop table t2;
473drop table t3;
474drop table p_t1;
475
476--
477-- Test GROUP BY matching of join columns that are type-coerced due to USING
478--
479
480create temp table t1(f1 int, f2 bigint);
481create temp table t2(f1 bigint, f22 bigint);
482
483select f1 from t1 left join t2 using (f1) group by f1;
484select f1 from t1 left join t2 using (f1) group by t1.f1;
485select t1.f1 from t1 left join t2 using (f1) group by t1.f1;
486-- only this one should fail:
487select t1.f1 from t1 left join t2 using (f1) group by f1;
488
489drop table t1, t2;
490
491--
492-- Test combinations of DISTINCT and/or ORDER BY
493--
494
495select array_agg(a order by b)
496  from (values (1,4),(2,3),(3,1),(4,2)) v(a,b);
497select array_agg(a order by a)
498  from (values (1,4),(2,3),(3,1),(4,2)) v(a,b);
499select array_agg(a order by a desc)
500  from (values (1,4),(2,3),(3,1),(4,2)) v(a,b);
501select array_agg(b order by a desc)
502  from (values (1,4),(2,3),(3,1),(4,2)) v(a,b);
503
504select array_agg(distinct a)
505  from (values (1),(2),(1),(3),(null),(2)) v(a);
506select array_agg(distinct a order by a)
507  from (values (1),(2),(1),(3),(null),(2)) v(a);
508select array_agg(distinct a order by a desc)
509  from (values (1),(2),(1),(3),(null),(2)) v(a);
510select array_agg(distinct a order by a desc nulls last)
511  from (values (1),(2),(1),(3),(null),(2)) v(a);
512
513-- multi-arg aggs, strict/nonstrict, distinct/order by
514
515select aggfstr(a,b,c)
516  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c);
517select aggfns(a,b,c)
518  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c);
519
520select aggfstr(distinct a,b,c)
521  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
522       generate_series(1,3) i;
523select aggfns(distinct a,b,c)
524  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
525       generate_series(1,3) i;
526
527select aggfstr(distinct a,b,c order by b)
528  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
529       generate_series(1,3) i;
530select aggfns(distinct a,b,c order by b)
531  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
532       generate_series(1,3) i;
533
534-- test specific code paths
535
536select aggfns(distinct a,a,c order by c using ~<~,a)
537  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
538       generate_series(1,2) i;
539select aggfns(distinct a,a,c order by c using ~<~)
540  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
541       generate_series(1,2) i;
542select aggfns(distinct a,a,c order by a)
543  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
544       generate_series(1,2) i;
545select aggfns(distinct a,b,c order by a,c using ~<~,b)
546  from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
547       generate_series(1,2) i;
548
549-- check node I/O via view creation and usage, also deparsing logic
550
551create view agg_view1 as
552  select aggfns(a,b,c)
553    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c);
554
555select * from agg_view1;
556select pg_get_viewdef('agg_view1'::regclass);
557
558create or replace view agg_view1 as
559  select aggfns(distinct a,b,c)
560    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
561         generate_series(1,3) i;
562
563select * from agg_view1;
564select pg_get_viewdef('agg_view1'::regclass);
565
566create or replace view agg_view1 as
567  select aggfns(distinct a,b,c order by b)
568    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
569         generate_series(1,3) i;
570
571select * from agg_view1;
572select pg_get_viewdef('agg_view1'::regclass);
573
574create or replace view agg_view1 as
575  select aggfns(a,b,c order by b+1)
576    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c);
577
578select * from agg_view1;
579select pg_get_viewdef('agg_view1'::regclass);
580
581create or replace view agg_view1 as
582  select aggfns(a,a,c order by b)
583    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c);
584
585select * from agg_view1;
586select pg_get_viewdef('agg_view1'::regclass);
587
588create or replace view agg_view1 as
589  select aggfns(a,b,c order by c using ~<~)
590    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c);
591
592select * from agg_view1;
593select pg_get_viewdef('agg_view1'::regclass);
594
595create or replace view agg_view1 as
596  select aggfns(distinct a,b,c order by a,c using ~<~,b)
597    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
598         generate_series(1,2) i;
599
600select * from agg_view1;
601select pg_get_viewdef('agg_view1'::regclass);
602
603drop view agg_view1;
604
605-- incorrect DISTINCT usage errors
606
607select aggfns(distinct a,b,c order by i)
608  from (values (1,1,'foo')) v(a,b,c), generate_series(1,2) i;
609select aggfns(distinct a,b,c order by a,b+1)
610  from (values (1,1,'foo')) v(a,b,c), generate_series(1,2) i;
611select aggfns(distinct a,b,c order by a,b,i,c)
612  from (values (1,1,'foo')) v(a,b,c), generate_series(1,2) i;
613select aggfns(distinct a,a,c order by a,b)
614  from (values (1,1,'foo')) v(a,b,c), generate_series(1,2) i;
615
616-- string_agg tests
617select string_agg(a,',') from (values('aaaa'),('bbbb'),('cccc')) g(a);
618select string_agg(a,',') from (values('aaaa'),(null),('bbbb'),('cccc')) g(a);
619select string_agg(a,'AB') from (values(null),(null),('bbbb'),('cccc')) g(a);
620select string_agg(a,',') from (values(null),(null)) g(a);
621
622-- check some implicit casting cases, as per bug #5564
623select string_agg(distinct f1, ',' order by f1) from varchar_tbl;  -- ok
624select string_agg(distinct f1::text, ',' order by f1) from varchar_tbl;  -- not ok
625select string_agg(distinct f1, ',' order by f1::text) from varchar_tbl;  -- not ok
626select string_agg(distinct f1::text, ',' order by f1::text) from varchar_tbl;  -- ok
627
628-- string_agg bytea tests
629create table bytea_test_table(v bytea);
630
631select string_agg(v, '') from bytea_test_table;
632
633insert into bytea_test_table values(decode('ff','hex'));
634
635select string_agg(v, '') from bytea_test_table;
636
637insert into bytea_test_table values(decode('aa','hex'));
638
639select string_agg(v, '') from bytea_test_table;
640select string_agg(v, NULL) from bytea_test_table;
641select string_agg(v, decode('ee', 'hex')) from bytea_test_table;
642
643drop table bytea_test_table;
644
645-- FILTER tests
646
647select min(unique1) filter (where unique1 > 100) from tenk1;
648
649select sum(1/ten) filter (where ten > 0) from tenk1;
650
651select ten, sum(distinct four) filter (where four::text ~ '123') from onek a
652group by ten;
653
654select ten, sum(distinct four) filter (where four > 10) from onek a
655group by ten
656having exists (select 1 from onek b where sum(distinct a.four) = b.four);
657
658select max(foo COLLATE "C") filter (where (bar collate "POSIX") > '0')
659from (values ('a', 'b')) AS v(foo,bar);
660
661-- outer reference in FILTER (PostgreSQL extension)
662select (select count(*)
663        from (values (1)) t0(inner_c))
664from (values (2),(3)) t1(outer_c); -- inner query is aggregation query
665select (select count(*) filter (where outer_c <> 0)
666        from (values (1)) t0(inner_c))
667from (values (2),(3)) t1(outer_c); -- outer query is aggregation query
668select (select count(inner_c) filter (where outer_c <> 0)
669        from (values (1)) t0(inner_c))
670from (values (2),(3)) t1(outer_c); -- inner query is aggregation query
671select
672  (select max((select i.unique2 from tenk1 i where i.unique1 = o.unique1))
673     filter (where o.unique1 < 10))
674from tenk1 o;					-- outer query is aggregation query
675
676-- subquery in FILTER clause (PostgreSQL extension)
677select sum(unique1) FILTER (WHERE
678  unique1 IN (SELECT unique1 FROM onek where unique1 < 100)) FROM tenk1;
679
680-- exercise lots of aggregate parts with FILTER
681select aggfns(distinct a,b,c order by a,c using ~<~,b) filter (where a > 1)
682    from (values (1,3,'foo'),(0,null,null),(2,2,'bar'),(3,1,'baz')) v(a,b,c),
683    generate_series(1,2) i;
684
685-- check handling of bare boolean Var in FILTER
686select max(0) filter (where b1) from bool_test;
687select (select max(0) filter (where b1)) from bool_test;
688
689-- check for correct detection of nested-aggregate errors in FILTER
690select max(unique1) filter (where sum(ten) > 0) from tenk1;
691select (select max(unique1) filter (where sum(ten) > 0) from int8_tbl) from tenk1;
692select max(unique1) filter (where bool_or(ten > 0)) from tenk1;
693select (select max(unique1) filter (where bool_or(ten > 0)) from int8_tbl) from tenk1;
694
695
696-- ordered-set aggregates
697
698select p, percentile_cont(p) within group (order by x::float8)
699from generate_series(1,5) x,
700     (values (0::float8),(0.1),(0.25),(0.4),(0.5),(0.6),(0.75),(0.9),(1)) v(p)
701group by p order by p;
702
703select p, percentile_cont(p order by p) within group (order by x)  -- error
704from generate_series(1,5) x,
705     (values (0::float8),(0.1),(0.25),(0.4),(0.5),(0.6),(0.75),(0.9),(1)) v(p)
706group by p order by p;
707
708select p, sum() within group (order by x::float8)  -- error
709from generate_series(1,5) x,
710     (values (0::float8),(0.1),(0.25),(0.4),(0.5),(0.6),(0.75),(0.9),(1)) v(p)
711group by p order by p;
712
713select p, percentile_cont(p,p)  -- error
714from generate_series(1,5) x,
715     (values (0::float8),(0.1),(0.25),(0.4),(0.5),(0.6),(0.75),(0.9),(1)) v(p)
716group by p order by p;
717
718select percentile_cont(0.5) within group (order by b) from aggtest;
719select percentile_cont(0.5) within group (order by b), sum(b) from aggtest;
720select percentile_cont(0.5) within group (order by thousand) from tenk1;
721select percentile_disc(0.5) within group (order by thousand) from tenk1;
722select rank(3) within group (order by x)
723from (values (1),(1),(2),(2),(3),(3),(4)) v(x);
724select cume_dist(3) within group (order by x)
725from (values (1),(1),(2),(2),(3),(3),(4)) v(x);
726select percent_rank(3) within group (order by x)
727from (values (1),(1),(2),(2),(3),(3),(4),(5)) v(x);
728select dense_rank(3) within group (order by x)
729from (values (1),(1),(2),(2),(3),(3),(4)) v(x);
730
731select percentile_disc(array[0,0.1,0.25,0.5,0.75,0.9,1]) within group (order by thousand)
732from tenk1;
733select percentile_cont(array[0,0.25,0.5,0.75,1]) within group (order by thousand)
734from tenk1;
735select percentile_disc(array[[null,1,0.5],[0.75,0.25,null]]) within group (order by thousand)
736from tenk1;
737select percentile_cont(array[0,1,0.25,0.75,0.5,1,0.3,0.32,0.35,0.38,0.4]) within group (order by x)
738from generate_series(1,6) x;
739
740select ten, mode() within group (order by string4) from tenk1 group by ten;
741
742select percentile_disc(array[0.25,0.5,0.75]) within group (order by x)
743from unnest('{fred,jim,fred,jack,jill,fred,jill,jim,jim,sheila,jim,sheila}'::text[]) u(x);
744
745-- check collation propagates up in suitable cases:
746select pg_collation_for(percentile_disc(1) within group (order by x collate "POSIX"))
747  from (values ('fred'),('jim')) v(x);
748
749-- ordered-set aggs created with CREATE AGGREGATE
750select test_rank(3) within group (order by x)
751from (values (1),(1),(2),(2),(3),(3),(4)) v(x);
752select test_percentile_disc(0.5) within group (order by thousand) from tenk1;
753
754-- ordered-set aggs can't use ungrouped vars in direct args:
755select rank(x) within group (order by x) from generate_series(1,5) x;
756
757-- outer-level agg can't use a grouped arg of a lower level, either:
758select array(select percentile_disc(a) within group (order by x)
759               from (values (0.3),(0.7)) v(a) group by a)
760  from generate_series(1,5) g(x);
761
762-- agg in the direct args is a grouping violation, too:
763select rank(sum(x)) within group (order by x) from generate_series(1,5) x;
764
765-- hypothetical-set type unification and argument-count failures:
766select rank(3) within group (order by x) from (values ('fred'),('jim')) v(x);
767select rank(3) within group (order by stringu1,stringu2) from tenk1;
768select rank('fred') within group (order by x) from generate_series(1,5) x;
769select rank('adam'::text collate "C") within group (order by x collate "POSIX")
770  from (values ('fred'),('jim')) v(x);
771-- hypothetical-set type unification successes:
772select rank('adam'::varchar) within group (order by x) from (values ('fred'),('jim')) v(x);
773select rank('3') within group (order by x) from generate_series(1,5) x;
774
775-- divide by zero check
776select percent_rank(0) within group (order by x) from generate_series(1,0) x;
777
778-- deparse and multiple features:
779create view aggordview1 as
780select ten,
781       percentile_disc(0.5) within group (order by thousand) as p50,
782       percentile_disc(0.5) within group (order by thousand) filter (where hundred=1) as px,
783       rank(5,'AZZZZ',50) within group (order by hundred, string4 desc, hundred)
784  from tenk1
785 group by ten order by ten;
786
787select pg_get_viewdef('aggordview1');
788select * from aggordview1 order by ten;
789drop view aggordview1;
790
791-- variadic aggregates
792select least_agg(q1,q2) from int8_tbl;
793select least_agg(variadic array[q1,q2]) from int8_tbl;
794
795select cleast_agg(q1,q2) from int8_tbl;
796select cleast_agg(4.5,f1) from int4_tbl;
797select cleast_agg(variadic array[4.5,f1]) from int4_tbl;
798select pg_typeof(cleast_agg(variadic array[4.5,f1])) from int4_tbl;
799
800-- test aggregates with common transition functions share the same states
801begin work;
802
803create type avg_state as (total bigint, count bigint);
804
805create or replace function avg_transfn(state avg_state, n int) returns avg_state as
806$$
807declare new_state avg_state;
808begin
809	raise notice 'avg_transfn called with %', n;
810	if state is null then
811		if n is not null then
812			new_state.total := n;
813			new_state.count := 1;
814			return new_state;
815		end if;
816		return null;
817	elsif n is not null then
818		state.total := state.total + n;
819		state.count := state.count + 1;
820		return state;
821	end if;
822
823	return null;
824end
825$$ language plpgsql;
826
827create function avg_finalfn(state avg_state) returns int4 as
828$$
829begin
830	if state is null then
831		return NULL;
832	else
833		return state.total / state.count;
834	end if;
835end
836$$ language plpgsql;
837
838create function sum_finalfn(state avg_state) returns int4 as
839$$
840begin
841	if state is null then
842		return NULL;
843	else
844		return state.total;
845	end if;
846end
847$$ language plpgsql;
848
849create aggregate my_avg(int4)
850(
851   stype = avg_state,
852   sfunc = avg_transfn,
853   finalfunc = avg_finalfn
854);
855
856create aggregate my_sum(int4)
857(
858   stype = avg_state,
859   sfunc = avg_transfn,
860   finalfunc = sum_finalfn
861);
862
863-- aggregate state should be shared as aggs are the same.
864select my_avg(one),my_avg(one) from (values(1),(3)) t(one);
865
866-- aggregate state should be shared as transfn is the same for both aggs.
867select my_avg(one),my_sum(one) from (values(1),(3)) t(one);
868
869-- same as previous one, but with DISTINCT, which requires sorting the input.
870select my_avg(distinct one),my_sum(distinct one) from (values(1),(3),(1)) t(one);
871
872-- shouldn't share states due to the distinctness not matching.
873select my_avg(distinct one),my_sum(one) from (values(1),(3)) t(one);
874
875-- shouldn't share states due to the filter clause not matching.
876select my_avg(one) filter (where one > 1),my_sum(one) from (values(1),(3)) t(one);
877
878-- this should not share the state due to different input columns.
879select my_avg(one),my_sum(two) from (values(1,2),(3,4)) t(one,two);
880
881-- exercise cases where OSAs share state
882select
883  percentile_cont(0.5) within group (order by a),
884  percentile_disc(0.5) within group (order by a)
885from (values(1::float8),(3),(5),(7)) t(a);
886
887select
888  percentile_cont(0.25) within group (order by a),
889  percentile_disc(0.5) within group (order by a)
890from (values(1::float8),(3),(5),(7)) t(a);
891
892-- these can't share state currently
893select
894  rank(4) within group (order by a),
895  dense_rank(4) within group (order by a)
896from (values(1),(3),(5),(7)) t(a);
897
898-- test that aggs with the same sfunc and initcond share the same agg state
899create aggregate my_sum_init(int4)
900(
901   stype = avg_state,
902   sfunc = avg_transfn,
903   finalfunc = sum_finalfn,
904   initcond = '(10,0)'
905);
906
907create aggregate my_avg_init(int4)
908(
909   stype = avg_state,
910   sfunc = avg_transfn,
911   finalfunc = avg_finalfn,
912   initcond = '(10,0)'
913);
914
915create aggregate my_avg_init2(int4)
916(
917   stype = avg_state,
918   sfunc = avg_transfn,
919   finalfunc = avg_finalfn,
920   initcond = '(4,0)'
921);
922
923-- state should be shared if INITCONDs are matching
924select my_sum_init(one),my_avg_init(one) from (values(1),(3)) t(one);
925
926-- Varying INITCONDs should cause the states not to be shared.
927select my_sum_init(one),my_avg_init2(one) from (values(1),(3)) t(one);
928
929rollback;
930
931-- test aggregate state sharing to ensure it works if one aggregate has a
932-- finalfn and the other one has none.
933begin work;
934
935create or replace function sum_transfn(state int4, n int4) returns int4 as
936$$
937declare new_state int4;
938begin
939	raise notice 'sum_transfn called with %', n;
940	if state is null then
941		if n is not null then
942			new_state := n;
943			return new_state;
944		end if;
945		return null;
946	elsif n is not null then
947		state := state + n;
948		return state;
949	end if;
950
951	return null;
952end
953$$ language plpgsql;
954
955create function halfsum_finalfn(state int4) returns int4 as
956$$
957begin
958	if state is null then
959		return NULL;
960	else
961		return state / 2;
962	end if;
963end
964$$ language plpgsql;
965
966create aggregate my_sum(int4)
967(
968   stype = int4,
969   sfunc = sum_transfn
970);
971
972create aggregate my_half_sum(int4)
973(
974   stype = int4,
975   sfunc = sum_transfn,
976   finalfunc = halfsum_finalfn
977);
978
979-- Agg state should be shared even though my_sum has no finalfn
980select my_sum(one),my_half_sum(one) from (values(1),(2),(3),(4)) t(one);
981
982rollback;
983
984
985-- test that the aggregate transition logic correctly handles
986-- transition / combine functions returning NULL
987
988-- First test the case of a normal transition function returning NULL
989BEGIN;
990CREATE FUNCTION balkifnull(int8, int4)
991RETURNS int8
992STRICT
993LANGUAGE plpgsql AS $$
994BEGIN
995    IF $1 IS NULL THEN
996       RAISE 'erroneously called with NULL argument';
997    END IF;
998    RETURN NULL;
999END$$;
1000
1001CREATE AGGREGATE balk(int4)
1002(
1003    SFUNC = balkifnull(int8, int4),
1004    STYPE = int8,
1005    PARALLEL = SAFE,
1006    INITCOND = '0'
1007);
1008
1009SELECT balk(hundred) FROM tenk1;
1010
1011ROLLBACK;
1012
1013-- Secondly test the case of a parallel aggregate combiner function
1014-- returning NULL. For that use normal transition function, but a
1015-- combiner function returning NULL.
1016BEGIN;
1017CREATE FUNCTION balkifnull(int8, int8)
1018RETURNS int8
1019PARALLEL SAFE
1020STRICT
1021LANGUAGE plpgsql AS $$
1022BEGIN
1023    IF $1 IS NULL THEN
1024       RAISE 'erroneously called with NULL argument';
1025    END IF;
1026    RETURN NULL;
1027END$$;
1028
1029CREATE AGGREGATE balk(int4)
1030(
1031    SFUNC = int4_sum(int8, int4),
1032    STYPE = int8,
1033    COMBINEFUNC = balkifnull(int8, int8),
1034    PARALLEL = SAFE,
1035    INITCOND = '0'
1036);
1037
1038-- force use of parallelism
1039ALTER TABLE tenk1 set (parallel_workers = 4);
1040SET LOCAL parallel_setup_cost=0;
1041SET LOCAL max_parallel_workers_per_gather=4;
1042
1043EXPLAIN (COSTS OFF) SELECT balk(hundred) FROM tenk1;
1044SELECT balk(hundred) FROM tenk1;
1045
1046ROLLBACK;
1047
1048-- test coverage for aggregate combine/serial/deserial functions
1049BEGIN;
1050
1051SET parallel_setup_cost = 0;
1052SET parallel_tuple_cost = 0;
1053SET min_parallel_table_scan_size = 0;
1054SET max_parallel_workers_per_gather = 4;
1055SET parallel_leader_participation = off;
1056SET enable_indexonlyscan = off;
1057
1058-- variance(int4) covers numeric_poly_combine
1059-- sum(int8) covers int8_avg_combine
1060-- regr_count(float8, float8) covers int8inc_float8_float8 and aggregates with > 1 arg
1061EXPLAIN (COSTS OFF, VERBOSE)
1062SELECT variance(unique1::int4), sum(unique1::int8), regr_count(unique1::float8, unique1::float8)
1063FROM (SELECT * FROM tenk1
1064      UNION ALL SELECT * FROM tenk1
1065      UNION ALL SELECT * FROM tenk1
1066      UNION ALL SELECT * FROM tenk1) u;
1067
1068SELECT variance(unique1::int4), sum(unique1::int8), regr_count(unique1::float8, unique1::float8)
1069FROM (SELECT * FROM tenk1
1070      UNION ALL SELECT * FROM tenk1
1071      UNION ALL SELECT * FROM tenk1
1072      UNION ALL SELECT * FROM tenk1) u;
1073
1074-- variance(int8) covers numeric_combine
1075-- avg(numeric) covers numeric_avg_combine
1076EXPLAIN (COSTS OFF, VERBOSE)
1077SELECT variance(unique1::int8), avg(unique1::numeric)
1078FROM (SELECT * FROM tenk1
1079      UNION ALL SELECT * FROM tenk1
1080      UNION ALL SELECT * FROM tenk1
1081      UNION ALL SELECT * FROM tenk1) u;
1082
1083SELECT variance(unique1::int8), avg(unique1::numeric)
1084FROM (SELECT * FROM tenk1
1085      UNION ALL SELECT * FROM tenk1
1086      UNION ALL SELECT * FROM tenk1
1087      UNION ALL SELECT * FROM tenk1) u;
1088
1089ROLLBACK;
1090
1091-- test coverage for dense_rank
1092SELECT dense_rank(x) WITHIN GROUP (ORDER BY x) FROM (VALUES (1),(1),(2),(2),(3),(3)) v(x) GROUP BY (x) ORDER BY 1;
1093
1094
1095-- Ensure that the STRICT checks for aggregates does not take NULLness
1096-- of ORDER BY columns into account. See bug report around
1097-- 2a505161-2727-2473-7c46-591ed108ac52@email.cz
1098SELECT min(x ORDER BY y) FROM (VALUES(1, NULL)) AS d(x,y);
1099SELECT min(x ORDER BY y) FROM (VALUES(1, 2)) AS d(x,y);
1100
1101-- check collation-sensitive matching between grouping expressions
1102select v||'a', case v||'a' when 'aa' then 1 else 0 end, count(*)
1103  from unnest(array['a','b']) u(v)
1104 group by v||'a' order by 1;
1105select v||'a', case when v||'a' = 'aa' then 1 else 0 end, count(*)
1106  from unnest(array['a','b']) u(v)
1107 group by v||'a' order by 1;
1108
1109-- Make sure that generation of HashAggregate for uniqification purposes
1110-- does not lead to array overflow due to unexpected duplicate hash keys
1111-- see CAFeeJoKKu0u+A_A9R9316djW-YW3-+Gtgvy3ju655qRHR3jtdA@mail.gmail.com
1112set enable_memoize to off;
1113explain (costs off)
1114  select 1 from tenk1
1115   where (hundred, thousand) in (select twothousand, twothousand from onek);
1116reset enable_memoize;
1117
1118--
1119-- Hash Aggregation Spill tests
1120--
1121
1122set enable_sort=false;
1123set work_mem='64kB';
1124
1125select unique1, count(*), sum(twothousand) from tenk1
1126group by unique1
1127having sum(fivethous) > 4975
1128order by sum(twothousand);
1129
1130set work_mem to default;
1131set enable_sort to default;
1132
1133--
1134-- Compare results between plans using sorting and plans using hash
1135-- aggregation. Force spilling in both cases by setting work_mem low.
1136--
1137
1138set work_mem='64kB';
1139
1140create table agg_data_2k as
1141select g from generate_series(0, 1999) g;
1142analyze agg_data_2k;
1143
1144create table agg_data_20k as
1145select g from generate_series(0, 19999) g;
1146analyze agg_data_20k;
1147
1148-- Produce results with sorting.
1149
1150set enable_hashagg = false;
1151
1152set jit_above_cost = 0;
1153
1154explain (costs off)
1155select g%10000 as c1, sum(g::numeric) as c2, count(*) as c3
1156  from agg_data_20k group by g%10000;
1157
1158create table agg_group_1 as
1159select g%10000 as c1, sum(g::numeric) as c2, count(*) as c3
1160  from agg_data_20k group by g%10000;
1161
1162create table agg_group_2 as
1163select * from
1164  (values (100), (300), (500)) as r(a),
1165  lateral (
1166    select (g/2)::numeric as c1,
1167           array_agg(g::numeric) as c2,
1168	   count(*) as c3
1169    from agg_data_2k
1170    where g < r.a
1171    group by g/2) as s;
1172
1173set jit_above_cost to default;
1174
1175create table agg_group_3 as
1176select (g/2)::numeric as c1, sum(7::int4) as c2, count(*) as c3
1177  from agg_data_2k group by g/2;
1178
1179create table agg_group_4 as
1180select (g/2)::numeric as c1, array_agg(g::numeric) as c2, count(*) as c3
1181  from agg_data_2k group by g/2;
1182
1183-- Produce results with hash aggregation
1184
1185set enable_hashagg = true;
1186set enable_sort = false;
1187
1188set jit_above_cost = 0;
1189
1190explain (costs off)
1191select g%10000 as c1, sum(g::numeric) as c2, count(*) as c3
1192  from agg_data_20k group by g%10000;
1193
1194create table agg_hash_1 as
1195select g%10000 as c1, sum(g::numeric) as c2, count(*) as c3
1196  from agg_data_20k group by g%10000;
1197
1198create table agg_hash_2 as
1199select * from
1200  (values (100), (300), (500)) as r(a),
1201  lateral (
1202    select (g/2)::numeric as c1,
1203           array_agg(g::numeric) as c2,
1204	   count(*) as c3
1205    from agg_data_2k
1206    where g < r.a
1207    group by g/2) as s;
1208
1209set jit_above_cost to default;
1210
1211create table agg_hash_3 as
1212select (g/2)::numeric as c1, sum(7::int4) as c2, count(*) as c3
1213  from agg_data_2k group by g/2;
1214
1215create table agg_hash_4 as
1216select (g/2)::numeric as c1, array_agg(g::numeric) as c2, count(*) as c3
1217  from agg_data_2k group by g/2;
1218
1219set enable_sort = true;
1220set work_mem to default;
1221
1222-- Compare group aggregation results to hash aggregation results
1223
1224(select * from agg_hash_1 except select * from agg_group_1)
1225  union all
1226(select * from agg_group_1 except select * from agg_hash_1);
1227
1228(select * from agg_hash_2 except select * from agg_group_2)
1229  union all
1230(select * from agg_group_2 except select * from agg_hash_2);
1231
1232(select * from agg_hash_3 except select * from agg_group_3)
1233  union all
1234(select * from agg_group_3 except select * from agg_hash_3);
1235
1236(select * from agg_hash_4 except select * from agg_group_4)
1237  union all
1238(select * from agg_group_4 except select * from agg_hash_4);
1239
1240drop table agg_group_1;
1241drop table agg_group_2;
1242drop table agg_group_3;
1243drop table agg_group_4;
1244drop table agg_hash_1;
1245drop table agg_hash_2;
1246drop table agg_hash_3;
1247drop table agg_hash_4;
1248