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