work on docs
[pspp] / src / language / stats / ctables.c
1 /* PSPP - a program for statistical analysis.
2    Copyright (C) 2021 Free Software Foundation, Inc.
3
4    This program is free software: you can redistribute it and/or modify
5    it under the terms of the GNU General Public License as published by
6    the Free Software Foundation, either version 3 of the License, or
7    (at your option) any later version.
8
9    This program is distributed in the hope that it will be useful,
10    but WITHOUT ANY WARRANTY; without even the implied warranty of
11    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12    GNU General Public License for more details.
13
14    You should have received a copy of the GNU General Public License
15    along with this program.  If not, see <http://www.gnu.org/licenses/>. */
16
17 #include <config.h>
18
19 #include <math.h>
20 #include <errno.h>
21
22 #include "data/casegrouper.h"
23 #include "data/casereader.h"
24 #include "data/casewriter.h"
25 #include "data/data-in.h"
26 #include "data/data-out.h"
27 #include "data/dataset.h"
28 #include "data/dictionary.h"
29 #include "data/mrset.h"
30 #include "data/subcase.h"
31 #include "data/value-labels.h"
32 #include "language/command.h"
33 #include "language/dictionary/split-file.h"
34 #include "language/lexer/format-parser.h"
35 #include "language/lexer/lexer.h"
36 #include "language/lexer/token.h"
37 #include "language/lexer/variable-parser.h"
38 #include "libpspp/array.h"
39 #include "libpspp/assertion.h"
40 #include "libpspp/hash-functions.h"
41 #include "libpspp/hmap.h"
42 #include "libpspp/i18n.h"
43 #include "libpspp/message.h"
44 #include "libpspp/string-array.h"
45 #include "math/mode.h"
46 #include "math/moments.h"
47 #include "math/percentiles.h"
48 #include "math/sort.h"
49 #include "output/pivot-table.h"
50
51 #include "gl/minmax.h"
52 #include "gl/xalloc.h"
53
54 #include "gettext.h"
55 #define _(msgid) gettext (msgid)
56 #define N_(msgid) (msgid)
57
58 enum ctables_vlabel
59   {
60     CTVL_NONE = SETTINGS_VALUE_SHOW_DEFAULT,
61     CTVL_NAME = SETTINGS_VALUE_SHOW_VALUE,
62     CTVL_LABEL = SETTINGS_VALUE_SHOW_LABEL,
63     CTVL_BOTH = SETTINGS_VALUE_SHOW_BOTH,
64   };
65
66 /* XXX:
67    - unweighted summaries (U*)
68    - lower confidence limits (*.LCL)
69    - upper confidence limits (*.UCL)
70    - standard error (*.SE)
71  */
72
73 enum ctables_summary_function
74   {
75 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) ENUM,
76 #include "ctables.inc"
77 #undef S
78   };
79
80 enum {
81 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) +1
82   N_CTSF_FUNCTIONS =
83 #include "ctables.inc"
84 #undef S
85 };
86
87 static bool ctables_summary_function_is_count (enum ctables_summary_function);
88
89 enum ctables_domain_type
90   {
91     /* Within a section, where stacked variables divide one section from
92        another. */
93     CTDT_TABLE,                  /* All layers of a whole section. */
94     CTDT_LAYER,                  /* One layer within a section. */
95     CTDT_LAYERROW,               /* Row in one layer within a section. */
96     CTDT_LAYERCOL,               /* Column in one layer within a section. */
97
98     /* Within a subtable, where a subtable pairs an innermost row variable with
99        an innermost column variable within a single layer.  */
100     CTDT_SUBTABLE,               /* Whole subtable. */
101     CTDT_ROW,                    /* Row within a subtable. */
102     CTDT_COL,                    /* Column within a subtable. */
103 #define N_CTDTS 7
104   };
105
106 struct ctables_domain
107   {
108     struct hmap_node node;
109
110     const struct ctables_cell *example;
111
112     size_t sequence;
113     double d_valid;             /* Dictionary weight. */
114     double d_count;
115     double d_total;
116     double e_valid;             /* Effective weight */
117     double e_count;
118     double e_total;
119     double u_valid;             /* Unweighted. */
120     double u_count;
121     double u_total;
122     struct ctables_sum *sums;
123   };
124
125 struct ctables_sum
126   {
127     double e_sum;
128     double u_sum;
129   };
130
131 enum ctables_summary_variant
132   {
133     CSV_CELL,
134     CSV_TOTAL
135 #define N_CSVS 2
136   };
137
138 struct ctables_cell
139   {
140     /* In struct ctables_section's 'cells' hmap.  Indexed by all the values in
141        all the axes (except the scalar variable, if any). */
142     struct hmap_node node;
143
144     /* The domains that contain this cell. */
145     uint32_t omit_domains;
146     struct ctables_domain *domains[N_CTDTS];
147
148     bool hide;
149
150     bool postcompute;
151     enum ctables_summary_variant sv;
152
153     struct ctables_cell_axis
154       {
155         struct ctables_cell_value
156           {
157             const struct ctables_category *category;
158             union value value;
159           }
160         *cvs;
161         int leaf;
162       }
163     axes[PIVOT_N_AXES];
164
165     union ctables_summary *summaries;
166
167     //char *name;
168   };
169
170 struct ctables
171   {
172     const struct dictionary *dict;
173     struct pivot_table_look *look;
174
175     /* CTABLES has a number of extra formats that we implement via custom
176        currency specifications on an alternate fmt_settings. */
177 #define CTEF_NEGPAREN FMT_CCA
178 #define CTEF_NEQUAL   FMT_CCB
179 #define CTEF_PAREN    FMT_CCC
180 #define CTEF_PCTPAREN FMT_CCD
181     struct fmt_settings ctables_formats;
182
183     /* If this is NULL, zeros are displayed using the normal print format.
184        Otherwise, this string is displayed. */
185     char *zero;
186
187     /* If this is NULL, missing values are displayed using the normal print
188        format.  Otherwise, this string is displayed. */
189     char *missing;
190
191     /* Indexed by variable dictionary index. */
192     enum ctables_vlabel *vlabels;
193
194     struct hmap postcomputes;   /* Contains "struct ctables_postcompute"s. */
195
196     bool mrsets_count_duplicates; /* MRSETS. */
197     bool smissing_listwise;       /* SMISSING. */
198     struct variable *e_weight;    /* WEIGHT. */
199     int hide_threshold;           /* HIDESMALLCOUNTS. */
200
201     struct ctables_table **tables;
202     size_t n_tables;
203   };
204
205 static struct ctables_postcompute *ctables_find_postcompute (struct ctables *,
206                                                              const char *name);
207
208 struct ctables_postcompute
209   {
210     struct hmap_node hmap_node; /* In struct ctables's 'pcompute' hmap. */
211     char *name;                 /* Name, without leading &. */
212
213     struct msg_location *location; /* Location of definition. */
214     struct ctables_pcexpr *expr;
215     char *label;
216     struct ctables_summary_spec_set *specs;
217     bool hide_source_cats;
218   };
219
220 struct ctables_pcexpr
221   {
222     /* Precedence table:
223
224        ()
225        **
226        -
227        * /
228        - +
229     */
230     enum ctables_postcompute_op
231       {
232         /* Terminals. */
233         CTPO_CONSTANT,          /* 5 */
234         CTPO_CAT_NUMBER,        /* [5] */
235         CTPO_CAT_STRING,        /* ["STRING"] */
236         CTPO_CAT_NRANGE,        /* [LO THRU 5] */
237         CTPO_CAT_SRANGE,        /* ["A" THRU "B"] */
238         CTPO_CAT_MISSING,       /* MISSING */
239         CTPO_CAT_OTHERNM,       /* OTHERNM */
240         CTPO_CAT_SUBTOTAL,      /* SUBTOTAL */
241         CTPO_CAT_TOTAL,         /* TOTAL */
242
243         /* Nonterminals. */
244         CTPO_ADD,
245         CTPO_SUB,
246         CTPO_MUL,
247         CTPO_DIV,
248         CTPO_POW,
249         CTPO_NEG,
250       }
251     op;
252
253     union
254       {
255         /* CTPO_CAT_NUMBER. */
256         double number;
257
258         /* CTPO_CAT_STRING, in dictionary encoding. */
259         struct substring string;
260
261         /* CTPO_CAT_NRANGE. */
262         double nrange[2];
263
264         /* CTPO_CAT_SRANGE. */
265         struct substring srange[2];
266
267         /* CTPO_CAT_SUBTOTAL. */
268         size_t subtotal_index;
269
270         /* Two elements: CTPO_ADD, CTPO_SUB, CTPO_MUL, CTPO_DIV, CTPO_POW.
271            One element: CTPO_NEG. */
272         struct ctables_pcexpr *subs[2];
273       };
274
275     /* Source location. */
276     struct msg_location *location;
277   };
278
279 static void ctables_pcexpr_destroy (struct ctables_pcexpr *);
280 static struct ctables_pcexpr *ctables_pcexpr_allocate_binary (
281   enum ctables_postcompute_op, struct ctables_pcexpr *sub0,
282   struct ctables_pcexpr *sub1);
283
284 struct ctables_summary_spec_set
285   {
286     struct ctables_summary_spec *specs;
287     size_t n;
288     size_t allocated;
289
290     /* The variable to which the summary specs are applied. */
291     struct variable *var;
292
293     /* Whether the variable to which the summary specs are applied is a scale
294        variable for the purpose of summarization.
295
296        (VALIDN and TOTALN act differently for summarizing scale and categorical
297        variables.) */
298     bool is_scale;
299
300     /* If any of these optional additional scale variables are missing, then
301        treat 'var' as if it's missing too.  This is for implementing
302        SMISSING=LISTWISE. */
303     struct variable **listwise_vars;
304     size_t n_listwise_vars;
305   };
306
307 static void ctables_summary_spec_set_clone (struct ctables_summary_spec_set *,
308                                             const struct ctables_summary_spec_set *);
309 static void ctables_summary_spec_set_uninit (struct ctables_summary_spec_set *);
310
311 /* A nested sequence of variables, e.g. a > b > c. */
312 struct ctables_nest
313   {
314     struct variable **vars;
315     size_t n;
316     size_t scale_idx;
317     size_t *domains[N_CTDTS];
318     size_t n_domains[N_CTDTS];
319     size_t group_head;
320
321     struct ctables_summary_spec_set specs[N_CSVS];
322   };
323
324 /* A stack of nestings, e.g. nest1 + nest2 + ... + nestN. */
325 struct ctables_stack
326   {
327     struct ctables_nest *nests;
328     size_t n;
329   };
330
331 static void ctables_stack_uninit (struct ctables_stack *);
332
333 struct ctables_value
334   {
335     struct hmap_node node;
336     union value value;
337     int leaf;
338   };
339
340 struct ctables_occurrence
341   {
342     struct hmap_node node;
343     union value value;
344   };
345
346 struct ctables_section
347   {
348     /* Settings. */
349     struct ctables_table *table;
350     struct ctables_nest *nests[PIVOT_N_AXES];
351
352     /* Data. */
353     struct hmap *occurrences[PIVOT_N_AXES]; /* "struct ctables_occurrence"s. */
354     struct hmap cells;            /* Contains "struct ctables_cell"s. */
355     struct hmap domains[N_CTDTS]; /* Contains "struct ctables_domain"s. */
356   };
357
358 static void ctables_section_uninit (struct ctables_section *);
359
360 struct ctables_table
361   {
362     struct ctables *ctables;
363     struct ctables_axis *axes[PIVOT_N_AXES];
364     struct ctables_stack stacks[PIVOT_N_AXES];
365     struct ctables_section *sections;
366     size_t n_sections;
367     enum pivot_axis_type summary_axis;
368     struct ctables_summary_spec_set summary_specs;
369     struct variable **sum_vars;
370     size_t n_sum_vars;
371
372     enum pivot_axis_type slabels_axis;
373     bool slabels_visible;
374
375     /* The innermost category labels for axis 'a' appear on axis label_axis[a].
376
377        Most commonly, label_axis[a] == a, and in particular we always have
378        label_axis{PIVOT_AXIS_LAYER] == PIVOT_AXIS_LAYER.
379
380        If ROWLABELS or COLLABELS is specified, then one of
381        label_axis[PIVOT_AXIS_ROW] or label_axis[PIVOT_AXIS_COLUMN] can be the
382        opposite axis or PIVOT_AXIS_LAYER.  Only one of them will differ.
383
384        If any category labels are moved, then 'clabels_example' is one of the
385        variables being moved (and it is otherwise NULL).  All of the variables
386        being moved have the same width, value labels, and categories, so this
387        example variable can be used to find those out.
388
389        The remaining members in this group are relevant only if category labels
390        are moved.
391
392        'clabels_values_map' holds a "struct ctables_value" for all the values
393        that appear in all of the variables in the moved categories.  It is
394        accumulated as the data is read.  Once the data is fully read, its
395        sorted values are put into 'clabels_values' and 'n_clabels_values'.
396     */
397     enum pivot_axis_type label_axis[PIVOT_N_AXES];
398     enum pivot_axis_type clabels_from_axis;
399     const struct variable *clabels_example;
400     struct hmap clabels_values_map;
401     struct ctables_value **clabels_values;
402     size_t n_clabels_values;
403
404     /* Indexed by variable dictionary index. */
405     struct ctables_categories **categories;
406     size_t n_categories;
407
408     double cilevel;
409
410     char *caption;
411     char *corner;
412     char *title;
413
414     struct ctables_chisq *chisq;
415     struct ctables_pairwise *pairwise;
416   };
417
418 struct ctables_categories
419   {
420     size_t n_refs;
421     struct ctables_category *cats;
422     size_t n_cats;
423     bool show_empty;
424   };
425
426 struct ctables_category
427   {
428     enum ctables_category_type
429       {
430         /* Explicit category lists. */
431         CCT_NUMBER,
432         CCT_STRING,
433         CCT_NRANGE,             /* Numerical range. */
434         CCT_SRANGE,             /* String range. */
435         CCT_MISSING,
436         CCT_OTHERNM,
437         CCT_POSTCOMPUTE,
438
439         /* Totals and subtotals. */
440         CCT_SUBTOTAL,
441         CCT_TOTAL,
442
443         /* Implicit category lists. */
444         CCT_VALUE,
445         CCT_LABEL,
446         CCT_FUNCTION,
447
448         /* For contributing to TOTALN. */
449         CCT_EXCLUDED_MISSING,
450       }
451     type;
452
453     struct ctables_category *subtotal;
454
455     bool hide;
456
457     union
458       {
459         double number;           /* CCT_NUMBER. */
460         struct substring string; /* CCT_STRING, in dictionary encoding. */
461         double nrange[2];        /* CCT_NRANGE. */
462         struct substring srange[2]; /* CCT_SRANGE. */
463
464         struct
465           {
466             char *total_label;      /* CCT_SUBTOTAL, CCT_TOTAL. */
467             bool hide_subcategories; /* CCT_SUBTOTAL. */
468           };
469
470         /* CCT_POSTCOMPUTE. */
471         struct
472           {
473             const struct ctables_postcompute *pc;
474             enum fmt_type parse_format;
475           };
476
477         /* CCT_VALUE, CCT_LABEL, CCT_FUNCTION. */
478         struct
479           {
480             bool include_missing;
481             bool sort_ascending;
482
483             /* CCT_FUNCTION. */
484             enum ctables_summary_function sort_function;
485             struct variable *sort_var;
486             double percentile;
487           };
488       };
489
490     /* Source location.  This is null for CCT_TOTAL, CCT_VALUE, CCT_LABEL,
491        CCT_FUNCTION, CCT_EXCLUDED_MISSING. */
492     struct msg_location *location;
493   };
494
495 static void
496 ctables_category_uninit (struct ctables_category *cat)
497 {
498   if (!cat)
499     return;
500
501   msg_location_destroy (cat->location);
502   switch (cat->type)
503     {
504     case CCT_NUMBER:
505     case CCT_NRANGE:
506     case CCT_MISSING:
507     case CCT_OTHERNM:
508     case CCT_POSTCOMPUTE:
509       break;
510
511     case CCT_STRING:
512       ss_dealloc (&cat->string);
513       break;
514
515     case CCT_SRANGE:
516       ss_dealloc (&cat->srange[0]);
517       ss_dealloc (&cat->srange[1]);
518       break;
519
520     case CCT_SUBTOTAL:
521     case CCT_TOTAL:
522       free (cat->total_label);
523       break;
524
525     case CCT_VALUE:
526     case CCT_LABEL:
527     case CCT_FUNCTION:
528       break;
529
530     case CCT_EXCLUDED_MISSING:
531       break;
532     }
533 }
534
535 static bool
536 nullable_substring_equal (const struct substring *a,
537                           const struct substring *b)
538 {
539   return !a->string ? !b->string : b->string && ss_equals (*a, *b);
540 }
541
542 static bool
543 ctables_category_equal (const struct ctables_category *a,
544                         const struct ctables_category *b)
545 {
546   if (a->type != b->type)
547     return false;
548
549   switch (a->type)
550     {
551     case CCT_NUMBER:
552       return a->number == b->number;
553
554     case CCT_STRING:
555       return ss_equals (a->string, b->string);
556
557     case CCT_NRANGE:
558       return a->nrange[0] == b->nrange[0] && a->nrange[1] == b->nrange[1];
559
560     case CCT_SRANGE:
561       return (nullable_substring_equal (&a->srange[0], &b->srange[0])
562               && nullable_substring_equal (&a->srange[1], &b->srange[1]));
563
564     case CCT_MISSING:
565     case CCT_OTHERNM:
566       return true;
567
568     case CCT_POSTCOMPUTE:
569       return a->pc == b->pc;
570
571     case CCT_SUBTOTAL:
572     case CCT_TOTAL:
573       return !strcmp (a->total_label, b->total_label);
574
575     case CCT_VALUE:
576     case CCT_LABEL:
577     case CCT_FUNCTION:
578       return (a->include_missing == b->include_missing
579               && a->sort_ascending == b->sort_ascending
580               && a->sort_function == b->sort_function
581               && a->sort_var == b->sort_var
582               && a->percentile == b->percentile);
583
584     case CCT_EXCLUDED_MISSING:
585       return true;
586     }
587
588   NOT_REACHED ();
589 }
590
591 static void
592 ctables_categories_unref (struct ctables_categories *c)
593 {
594   if (!c)
595     return;
596
597   assert (c->n_refs > 0);
598   if (--c->n_refs)
599     return;
600
601   for (size_t i = 0; i < c->n_cats; i++)
602     ctables_category_uninit (&c->cats[i]);
603   free (c->cats);
604   free (c);
605 }
606
607 static bool
608 ctables_categories_equal (const struct ctables_categories *a,
609                           const struct ctables_categories *b)
610 {
611   if (a->n_cats != b->n_cats || a->show_empty != b->show_empty)
612     return false;
613
614   for (size_t i = 0; i < a->n_cats; i++)
615     if (!ctables_category_equal (&a->cats[i], &b->cats[i]))
616       return false;
617
618   return true;
619 }
620
621 /* Chi-square test (SIGTEST). */
622 struct ctables_chisq
623   {
624     double alpha;
625     bool include_mrsets;
626     bool all_visible;
627   };
628
629 /* Pairwise comparison test (COMPARETEST). */
630 struct ctables_pairwise
631   {
632     enum { PROP, MEAN } type;
633     double alpha[2];
634     bool include_mrsets;
635     bool meansvariance_allcats;
636     bool all_visible;
637     enum { BONFERRONI = 1, BH } adjust;
638     bool merge;
639     bool apa_style;
640     bool show_sig;
641   };
642
643 struct ctables_axis
644   {
645     enum ctables_axis_op
646       {
647         /* Terminals. */
648         CTAO_VAR,
649
650         /* Nonterminals. */
651         CTAO_STACK,             /* + */
652         CTAO_NEST,              /* > */
653       }
654     op;
655
656     union
657       {
658         /* Terminals. */
659         struct
660           {
661             struct variable *var;
662             bool scale;
663             struct ctables_summary_spec_set specs[N_CSVS];
664           };
665
666         /* Nonterminals. */
667         struct ctables_axis *subs[2];
668       };
669
670     struct msg_location *loc;
671   };
672
673 static void ctables_axis_destroy (struct ctables_axis *);
674
675 enum ctables_format
676   {
677     CTF_COUNT,
678     CTF_PERCENT,
679     CTF_GENERAL
680   };
681
682 enum ctables_function_availability
683   {
684     CTFA_ALL,                /* Any variables. */
685     CTFA_SCALE,              /* Only scale variables, totals, and subtotals. */
686     //CTFA_MRSETS,             /* Only multiple-response sets */
687   };
688
689 struct ctables_summary_spec
690   {
691     enum ctables_summary_function function;
692     double percentile;          /* CTSF_PTILE only. */
693     char *label;
694
695     struct fmt_spec format;
696     bool is_ctables_format;       /* Is 'format' one of CTEF_*? */
697
698     size_t axis_idx;
699     size_t sum_var_idx;
700   };
701
702 static void
703 ctables_summary_spec_clone (struct ctables_summary_spec *dst,
704                             const struct ctables_summary_spec *src)
705 {
706   *dst = *src;
707   dst->label = xstrdup_if_nonnull (src->label);
708 }
709
710 static void
711 ctables_summary_spec_uninit (struct ctables_summary_spec *s)
712 {
713   if (s)
714     free (s->label);
715 }
716
717 static void
718 ctables_summary_spec_set_clone (struct ctables_summary_spec_set *dst,
719                                 const struct ctables_summary_spec_set *src)
720 {
721   struct ctables_summary_spec *specs
722     = (src->n ? xnmalloc (src->n, sizeof *specs) : NULL);
723   for (size_t i = 0; i < src->n; i++)
724     ctables_summary_spec_clone (&specs[i], &src->specs[i]);
725
726   *dst = (struct ctables_summary_spec_set) {
727     .specs = specs,
728     .n = src->n,
729     .allocated = src->n,
730     .var = src->var,
731     .is_scale = src->is_scale,
732   };
733 }
734
735 static void
736 ctables_summary_spec_set_uninit (struct ctables_summary_spec_set *set)
737 {
738   for (size_t i = 0; i < set->n; i++)
739     ctables_summary_spec_uninit (&set->specs[i]);
740   free (set->listwise_vars);
741   free (set->specs);
742 }
743
744 static bool
745 parse_col_width (struct lexer *lexer, const char *name, double *width)
746 {
747   lex_match (lexer, T_EQUALS);
748   if (lex_match_id (lexer, "DEFAULT"))
749     *width = SYSMIS;
750   else if (lex_force_num_range_closed (lexer, name, 0, DBL_MAX))
751     {
752       *width = lex_number (lexer);
753       lex_get (lexer);
754     }
755   else
756     return false;
757
758   return true;
759 }
760
761 static bool
762 parse_bool (struct lexer *lexer, bool *b)
763 {
764   if (lex_match_id (lexer, "NO"))
765     *b = false;
766   else if (lex_match_id (lexer, "YES"))
767     *b = true;
768   else
769     {
770       lex_error_expecting (lexer, "YES", "NO");
771       return false;
772     }
773   return true;
774 }
775
776 static enum ctables_function_availability
777 ctables_function_availability (enum ctables_summary_function f)
778 {
779   static enum ctables_function_availability availability[] = {
780 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) [ENUM] = AVAILABILITY,
781 #include "ctables.inc"
782 #undef S
783   };
784
785   return availability[f];
786 }
787
788 static bool
789 ctables_summary_function_is_count (enum ctables_summary_function f)
790 {
791   return f == CTSF_COUNT || f == CTSF_ECOUNT || f == CTSF_UCOUNT;
792 }
793
794 static bool
795 parse_ctables_summary_function (struct lexer *lexer,
796                                 enum ctables_summary_function *f)
797 {
798   struct pair
799     {
800       enum ctables_summary_function function;
801       struct substring name;
802     };
803   static struct pair names[] = {
804 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) \
805     { ENUM, SS_LITERAL_INITIALIZER (NAME) },
806 #include "ctables.inc"
807     /* The .COUNT suffix may be omitted. */
808     S(CTSF_ROWPCT_COUNT, "ROWPCT", _, _, _)
809     S(CTSF_COLPCT_COUNT, "COLPCT", _, _, _)
810     S(CTSF_TABLEPCT_COUNT, "TABLEPCT", _, _, _)
811     S(CTSF_SUBTABLEPCT_COUNT, "SUBTABLEPCT", _, _, _)
812     S(CTSF_LAYERPCT_COUNT, "LAYERPCT", _, _, _)
813     S(CTSF_LAYERROWPCT_COUNT, "LAYERROWPCT", _, _, _)
814     S(CTSF_LAYERCOLPCT_COUNT, "LAYERCOLPCT", _, _, _)
815 #undef S
816   };
817
818   if (!lex_force_id (lexer))
819     return false;
820
821   for (size_t i = 0; i < sizeof names / sizeof *names; i++)
822     if (ss_equals_case (names[i].name, lex_tokss (lexer)))
823       {
824         *f = names[i].function;
825         lex_get (lexer);
826         return true;
827       }
828
829   lex_error (lexer, _("Expecting summary function name."));
830   return false;
831 }
832
833 static void
834 ctables_axis_destroy (struct ctables_axis *axis)
835 {
836   if (!axis)
837     return;
838
839   switch (axis->op)
840     {
841     case CTAO_VAR:
842       for (size_t i = 0; i < N_CSVS; i++)
843         ctables_summary_spec_set_uninit (&axis->specs[i]);
844       break;
845
846     case CTAO_STACK:
847     case CTAO_NEST:
848       ctables_axis_destroy (axis->subs[0]);
849       ctables_axis_destroy (axis->subs[1]);
850       break;
851     }
852   msg_location_destroy (axis->loc);
853   free (axis);
854 }
855
856 static struct ctables_axis *
857 ctables_axis_new_nonterminal (enum ctables_axis_op op,
858                               struct ctables_axis *sub0,
859                               struct ctables_axis *sub1,
860                               struct lexer *lexer, int start_ofs)
861 {
862   struct ctables_axis *axis = xmalloc (sizeof *axis);
863   *axis = (struct ctables_axis) {
864     .op = op,
865     .subs = { sub0, sub1 },
866     .loc = lex_ofs_location (lexer, start_ofs, lex_ofs (lexer) - 1),
867   };
868   return axis;
869 }
870
871 struct ctables_axis_parse_ctx
872   {
873     struct lexer *lexer;
874     struct dictionary *dict;
875     struct ctables *ct;
876     struct ctables_table *t;
877   };
878
879 static struct fmt_spec
880 ctables_summary_default_format (enum ctables_summary_function function,
881                                 const struct variable *var)
882 {
883   static const enum ctables_format default_formats[] = {
884 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) [ENUM] = FORMAT,
885 #include "ctables.inc"
886 #undef S
887   };
888   switch (default_formats[function])
889     {
890     case CTF_COUNT:
891       return (struct fmt_spec) { .type = FMT_F, .w = 40 };
892
893     case CTF_PERCENT:
894       return (struct fmt_spec) { .type = FMT_PCT, .w = 40, .d = 1 };
895
896     case CTF_GENERAL:
897       return *var_get_print_format (var);
898
899     default:
900       NOT_REACHED ();
901     }
902 }
903
904 static struct pivot_value *
905 ctables_summary_label (const struct ctables_summary_spec *spec, double cilevel)
906 {
907   if (!spec->label)
908     {
909       static const char *default_labels[] = {
910 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) [ENUM] = LABEL,
911 #include "ctables.inc"
912 #undef S
913       };
914
915       return (spec->function == CTSF_PTILE
916               ? pivot_value_new_text_format (N_("Percentile %.2f"),
917                                              spec->percentile)
918               : pivot_value_new_text (default_labels[spec->function]));
919     }
920   else
921     {
922       struct substring in = ss_cstr (spec->label);
923       struct substring target = ss_cstr (")CILEVEL");
924
925       struct string out = DS_EMPTY_INITIALIZER;
926       for (;;)
927         {
928           size_t chunk = ss_find_substring (in, target);
929           ds_put_substring (&out, ss_head (in, chunk));
930           ss_advance (&in, chunk);
931           if (!in.length)
932             return pivot_value_new_user_text_nocopy (ds_steal_cstr (&out));
933           
934           ss_advance (&in, target.length);
935           ds_put_format (&out, "%g", cilevel);
936         }
937     }
938 }
939
940 static const char *
941 ctables_summary_function_name (enum ctables_summary_function function)
942 {
943   static const char *names[] = {
944 #define S(ENUM, NAME, LABEL, FORMAT, AVAILABILITY) [ENUM] = NAME,
945 #include "ctables.inc"
946 #undef S
947   };
948   return names[function];
949 }
950
951 static bool
952 add_summary_spec (struct ctables_axis *axis,
953                   enum ctables_summary_function function, double percentile,
954                   const char *label, const struct fmt_spec *format,
955                   bool is_ctables_format, const struct msg_location *loc,
956                   enum ctables_summary_variant sv)
957 {
958   if (axis->op == CTAO_VAR)
959     {
960       const char *function_name = ctables_summary_function_name (function);
961       const char *var_name = var_get_name (axis->var);
962       switch (ctables_function_availability (function))
963         {
964 #if 0
965         case CTFA_MRSETS:
966           msg_at (SE, loc, _("Summary function %s applies only to multiple "
967                              "response sets."), function_name);
968           msg_at (SN, axis->loc, _("'%s' is not a multiple response set."),
969                   var_name);
970           return false;
971 #endif
972
973         case CTFA_SCALE:
974           if (!axis->scale && sv != CSV_TOTAL)
975             {
976               msg_at (SE, loc,
977                       _("Summary function %s applies only to scale variables."),
978                       function_name);
979               msg_at (SN, axis->loc, _("'%s' is not a scale variable."),
980                       var_name);
981               return false;
982             }
983           break;
984
985         case CTFA_ALL:
986           break;
987         }
988
989       struct ctables_summary_spec_set *set = &axis->specs[sv];
990       if (set->n >= set->allocated)
991         set->specs = x2nrealloc (set->specs, &set->allocated,
992                                  sizeof *set->specs);
993
994       struct ctables_summary_spec *dst = &set->specs[set->n++];
995       *dst = (struct ctables_summary_spec) {
996         .function = function,
997         .percentile = percentile,
998         .label = xstrdup_if_nonnull (label),
999         .format = (format ? *format
1000                    : ctables_summary_default_format (function, axis->var)),
1001         .is_ctables_format = is_ctables_format,
1002       };
1003       return true;
1004     }
1005   else
1006     {
1007       for (size_t i = 0; i < 2; i++)
1008         if (!add_summary_spec (axis->subs[i], function, percentile, label,
1009                                format, is_ctables_format, loc, sv))
1010           return false;
1011       return true;
1012     }
1013 }
1014
1015 static struct ctables_axis *ctables_axis_parse_stack (
1016   struct ctables_axis_parse_ctx *);
1017
1018
1019 static struct ctables_axis *
1020 ctables_axis_parse_primary (struct ctables_axis_parse_ctx *ctx)
1021 {
1022   if (lex_match (ctx->lexer, T_LPAREN))
1023     {
1024       struct ctables_axis *sub = ctables_axis_parse_stack (ctx);
1025       if (!sub || !lex_force_match (ctx->lexer, T_RPAREN))
1026         {
1027           ctables_axis_destroy (sub);
1028           return NULL;
1029         }
1030       return sub;
1031     }
1032
1033   if (!lex_force_id (ctx->lexer))
1034     return NULL;
1035
1036   int start_ofs = lex_ofs (ctx->lexer);
1037   struct variable *var = parse_variable (ctx->lexer, ctx->dict);
1038   if (!var)
1039     return NULL;
1040
1041   struct ctables_axis *axis = xmalloc (sizeof *axis);
1042   *axis = (struct ctables_axis) { .op = CTAO_VAR, .var = var };
1043
1044   axis->scale = (lex_match_phrase (ctx->lexer, "[S]") ? true
1045                  : lex_match_phrase (ctx->lexer, "[C]") ? false
1046                  : var_get_measure (var) == MEASURE_SCALE);
1047   axis->loc = lex_ofs_location (ctx->lexer, start_ofs,
1048                                 lex_ofs (ctx->lexer) - 1);
1049   if (axis->scale && var_is_alpha (var))
1050     {
1051       msg_at (SE, axis->loc, _("Cannot use string variable %s as a scale "
1052                                "variable."),
1053               var_get_name (var));
1054       ctables_axis_destroy (axis);
1055       return NULL;
1056     }
1057
1058   return axis;
1059 }
1060
1061 static bool
1062 has_digit (const char *s)
1063 {
1064   return s[strcspn (s, "0123456789")] != '\0';
1065 }
1066
1067 static bool
1068 parse_ctables_format_specifier (struct lexer *lexer, struct fmt_spec *format,
1069                                 bool *is_ctables_format)
1070 {
1071   char type[FMT_TYPE_LEN_MAX + 1];
1072   if (!parse_abstract_format_specifier__ (lexer, type, &format->w, &format->d))
1073     return false;
1074
1075   if (!strcasecmp (type, "NEGPAREN"))
1076     format->type = CTEF_NEGPAREN;
1077   else if (!strcasecmp (type, "NEQUAL"))
1078     format->type = CTEF_NEQUAL;
1079   else if (!strcasecmp (type, "PAREN"))
1080     format->type = CTEF_PAREN;
1081   else if (!strcasecmp (type, "PCTPAREN"))
1082     format->type = CTEF_PCTPAREN;
1083   else
1084     {
1085       *is_ctables_format = false;
1086       return (parse_format_specifier (lexer, format)
1087               && fmt_check_output (format)
1088               && fmt_check_type_compat (format, VAL_NUMERIC));
1089     }
1090
1091   lex_get (lexer);
1092   if (format->w < 2)
1093     {
1094       lex_next_error (lexer, -1, -1,
1095                       _("Output format %s requires width 2 or greater."), type);
1096       return false;
1097     }
1098   else if (format->d > format->w - 1)
1099     {
1100       lex_next_error (lexer, -1, -1, _("Output format %s requires width "
1101                                        "greater than decimals."), type);
1102       return false;
1103     }
1104   else
1105     {
1106       *is_ctables_format = true;
1107       return true;
1108     }
1109 }
1110
1111 static struct ctables_axis *
1112 ctables_axis_parse_postfix (struct ctables_axis_parse_ctx *ctx)
1113 {
1114   struct ctables_axis *sub = ctables_axis_parse_primary (ctx);
1115   if (!sub || !lex_match (ctx->lexer, T_LBRACK))
1116     return sub;
1117
1118   enum ctables_summary_variant sv = CSV_CELL;
1119   for (;;)
1120     {
1121       int start_ofs = lex_ofs (ctx->lexer);
1122
1123       /* Parse function. */
1124       enum ctables_summary_function function;
1125       if (!parse_ctables_summary_function (ctx->lexer, &function))
1126         goto error;
1127
1128       /* Parse percentile. */
1129       double percentile = 0;
1130       if (function == CTSF_PTILE)
1131         {
1132           if (!lex_force_num_range_closed (ctx->lexer, "PTILE", 0, 100))
1133             goto error;
1134           percentile = lex_number (ctx->lexer);
1135           lex_get (ctx->lexer);
1136         }
1137
1138       /* Parse label. */
1139       char *label = NULL;
1140       if (lex_is_string (ctx->lexer))
1141         {
1142           label = ss_xstrdup (lex_tokss (ctx->lexer));
1143           lex_get (ctx->lexer);
1144         }
1145
1146       /* Parse format. */
1147       struct fmt_spec format;
1148       const struct fmt_spec *formatp;
1149       bool is_ctables_format = false;
1150       if (lex_token (ctx->lexer) == T_ID
1151           && has_digit (lex_tokcstr (ctx->lexer)))
1152         {
1153           if (!parse_ctables_format_specifier (ctx->lexer, &format,
1154                                                &is_ctables_format))
1155             {
1156               free (label);
1157               goto error;
1158             }
1159           formatp = &format;
1160         }
1161       else
1162         formatp = NULL;
1163
1164       struct msg_location *loc = lex_ofs_location (ctx->lexer, start_ofs,
1165                                                    lex_ofs (ctx->lexer) - 1);
1166       add_summary_spec (sub, function, percentile, label, formatp,
1167                         is_ctables_format, loc, sv);
1168       free (label);
1169       msg_location_destroy (loc);
1170
1171       lex_match (ctx->lexer, T_COMMA);
1172       if (sv == CSV_CELL && lex_match_id (ctx->lexer, "TOTALS"))
1173         {
1174           if (!lex_force_match (ctx->lexer, T_LBRACK))
1175             goto error;
1176           sv = CSV_TOTAL;
1177         }
1178       else if (lex_match (ctx->lexer, T_RBRACK))
1179         {
1180           if (sv == CSV_TOTAL && !lex_force_match (ctx->lexer, T_RBRACK))
1181             goto error;
1182           return sub;
1183         }
1184     }
1185
1186 error:
1187   ctables_axis_destroy (sub);
1188   return NULL;
1189 }
1190
1191 static const struct ctables_axis *
1192 find_scale (const struct ctables_axis *axis)
1193 {
1194   if (!axis)
1195     return NULL;
1196   else if (axis->op == CTAO_VAR)
1197     return axis->scale ? axis : NULL;
1198   else
1199     {
1200       for (size_t i = 0; i < 2; i++)
1201         {
1202           const struct ctables_axis *scale = find_scale (axis->subs[i]);
1203           if (scale)
1204             return scale;
1205         }
1206       return NULL;
1207     }
1208 }
1209
1210 static const struct ctables_axis *
1211 find_categorical_summary_spec (const struct ctables_axis *axis)
1212 {
1213   if (!axis)
1214     return NULL;
1215   else if (axis->op == CTAO_VAR)
1216     return !axis->scale && axis->specs[CSV_CELL].n ? axis : NULL;
1217   else
1218     {
1219       for (size_t i = 0; i < 2; i++)
1220         {
1221           const struct ctables_axis *sum
1222             = find_categorical_summary_spec (axis->subs[i]);
1223           if (sum)
1224             return sum;
1225         }
1226       return NULL;
1227     }
1228 }
1229
1230 static struct ctables_axis *
1231 ctables_axis_parse_nest (struct ctables_axis_parse_ctx *ctx)
1232 {
1233   int start_ofs = lex_ofs (ctx->lexer);
1234   struct ctables_axis *lhs = ctables_axis_parse_postfix (ctx);
1235   if (!lhs)
1236     return NULL;
1237
1238   while (lex_match (ctx->lexer, T_GT))
1239     {
1240       struct ctables_axis *rhs = ctables_axis_parse_postfix (ctx);
1241       if (!rhs)
1242         return NULL;
1243
1244       struct ctables_axis *nest = ctables_axis_new_nonterminal (
1245         CTAO_NEST, lhs, rhs, ctx->lexer, start_ofs);
1246
1247       const struct ctables_axis *outer_scale = find_scale (lhs);
1248       const struct ctables_axis *inner_scale = find_scale (rhs);
1249       if (outer_scale && inner_scale)
1250         {
1251           msg_at (SE, nest->loc, _("Cannot nest scale variables."));
1252           msg_at (SN, outer_scale->loc, _("This is an outer scale variable."));
1253           msg_at (SN, inner_scale->loc, _("This is an inner scale variable."));
1254           ctables_axis_destroy (nest);
1255           return NULL;
1256         }
1257
1258       const struct ctables_axis *outer_sum = find_categorical_summary_spec (lhs);
1259       if (outer_sum)
1260         {
1261           msg_at (SE, nest->loc,
1262                   _("Summaries may only be requested for categorical variables "
1263                     "at the innermost nesting level."));
1264           msg_at (SN, outer_sum->loc,
1265                   _("This outer categorical variable has a summary."));
1266           ctables_axis_destroy (nest);
1267           return NULL;
1268         }
1269
1270       lhs = nest;
1271     }
1272
1273   return lhs;
1274 }
1275
1276 static struct ctables_axis *
1277 ctables_axis_parse_stack (struct ctables_axis_parse_ctx *ctx)
1278 {
1279   int start_ofs = lex_ofs (ctx->lexer);
1280   struct ctables_axis *lhs = ctables_axis_parse_nest (ctx);
1281   if (!lhs)
1282     return NULL;
1283
1284   while (lex_match (ctx->lexer, T_PLUS))
1285     {
1286       struct ctables_axis *rhs = ctables_axis_parse_nest (ctx);
1287       if (!rhs)
1288         return NULL;
1289
1290       lhs = ctables_axis_new_nonterminal (CTAO_STACK, lhs, rhs,
1291                                           ctx->lexer, start_ofs);
1292     }
1293
1294   return lhs;
1295 }
1296
1297 static bool
1298 ctables_axis_parse (struct lexer *lexer, struct dictionary *dict,
1299                     struct ctables *ct, struct ctables_table *t,
1300                     enum pivot_axis_type a)
1301 {
1302   if (lex_token (lexer) == T_BY
1303       || lex_token (lexer) == T_SLASH
1304       || lex_token (lexer) == T_ENDCMD)
1305     return true;
1306
1307   struct ctables_axis_parse_ctx ctx = {
1308     .lexer = lexer,
1309     .dict = dict,
1310     .ct = ct,
1311     .t = t
1312   };
1313   t->axes[a] = ctables_axis_parse_stack (&ctx);
1314   return t->axes[a] != NULL;
1315 }
1316
1317 static void
1318 ctables_chisq_destroy (struct ctables_chisq *chisq)
1319 {
1320   free (chisq);
1321 }
1322
1323 static void
1324 ctables_pairwise_destroy (struct ctables_pairwise *pairwise)
1325 {
1326   free (pairwise);
1327 }
1328
1329 static void
1330 ctables_table_destroy (struct ctables_table *t)
1331 {
1332   if (!t)
1333     return;
1334
1335   for (size_t i = 0; i < t->n_sections; i++)
1336     ctables_section_uninit (&t->sections[i]);
1337   free (t->sections);
1338
1339   for (size_t i = 0; i < t->n_categories; i++)
1340     ctables_categories_unref (t->categories[i]);
1341   free (t->categories);
1342
1343   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
1344     {
1345       ctables_axis_destroy (t->axes[a]);
1346       ctables_stack_uninit (&t->stacks[a]);
1347     }
1348   free (t->summary_specs.specs);
1349
1350   struct ctables_value *ctv, *next_ctv;
1351   HMAP_FOR_EACH_SAFE (ctv, next_ctv, struct ctables_value, node,
1352                       &t->clabels_values_map)
1353     {
1354       value_destroy (&ctv->value, var_get_width (t->clabels_example));
1355       hmap_delete (&t->clabels_values_map, &ctv->node);
1356       free (ctv);
1357     }
1358   hmap_destroy (&t->clabels_values_map);
1359   free (t->clabels_values);
1360
1361   free (t->sum_vars);
1362   free (t->caption);
1363   free (t->corner);
1364   free (t->title);
1365   ctables_chisq_destroy (t->chisq);
1366   ctables_pairwise_destroy (t->pairwise);
1367   free (t);
1368 }
1369
1370 static void
1371 ctables_destroy (struct ctables *ct)
1372 {
1373   if (!ct)
1374     return;
1375
1376   struct ctables_postcompute *pc, *next_pc;
1377   HMAP_FOR_EACH_SAFE (pc, next_pc, struct ctables_postcompute, hmap_node,
1378                       &ct->postcomputes)
1379     {
1380       free (pc->name);
1381       msg_location_destroy (pc->location);
1382       ctables_pcexpr_destroy (pc->expr);
1383       free (pc->label);
1384       if (pc->specs)
1385         {
1386           ctables_summary_spec_set_uninit (pc->specs);
1387           free (pc->specs);
1388         }
1389       hmap_delete (&ct->postcomputes, &pc->hmap_node);
1390       free (pc);
1391     }
1392
1393   fmt_settings_uninit (&ct->ctables_formats);
1394   pivot_table_look_unref (ct->look);
1395   free (ct->zero);
1396   free (ct->missing);
1397   free (ct->vlabels);
1398   for (size_t i = 0; i < ct->n_tables; i++)
1399     ctables_table_destroy (ct->tables[i]);
1400   free (ct->tables);
1401   free (ct);
1402 }
1403
1404 static struct ctables_category
1405 cct_nrange (double low, double high)
1406 {
1407   return (struct ctables_category) {
1408     .type = CCT_NRANGE,
1409     .nrange = { low, high }
1410   };
1411 }
1412
1413 static struct ctables_category
1414 cct_srange (struct substring low, struct substring high)
1415 {
1416   return (struct ctables_category) {
1417     .type = CCT_SRANGE,
1418     .srange = { low, high }
1419   };
1420 }
1421
1422 static bool
1423 ctables_table_parse_subtotal (struct lexer *lexer, bool hide_subcategories,
1424                               struct ctables_category *cat)
1425 {
1426   char *total_label;
1427   if (lex_match (lexer, T_EQUALS))
1428     {
1429       if (!lex_force_string (lexer))
1430         return false;
1431
1432       total_label = ss_xstrdup (lex_tokss (lexer));
1433       lex_get (lexer);
1434     }
1435   else
1436     total_label = xstrdup (_("Subtotal"));
1437
1438   *cat = (struct ctables_category) {
1439     .type = CCT_SUBTOTAL,
1440     .hide_subcategories = hide_subcategories,
1441     .total_label = total_label
1442   };
1443   return true;
1444 }
1445
1446 static struct substring
1447 parse_substring (struct lexer *lexer, struct dictionary *dict)
1448 {
1449   struct substring s = recode_substring_pool (
1450     dict_get_encoding (dict), "UTF-8", lex_tokss (lexer), NULL);
1451   ss_rtrim (&s, ss_cstr (" "));
1452   lex_get (lexer);
1453   return s;
1454 }
1455
1456 static bool
1457 ctables_table_parse_explicit_category (struct lexer *lexer,
1458                                        struct dictionary *dict,
1459                                        struct ctables *ct,
1460                                        struct ctables_category *cat)
1461 {
1462   if (lex_match_id (lexer, "OTHERNM"))
1463     *cat = (struct ctables_category) { .type = CCT_OTHERNM };
1464   else if (lex_match_id (lexer, "MISSING"))
1465     *cat = (struct ctables_category) { .type = CCT_MISSING };
1466   else if (lex_match_id (lexer, "SUBTOTAL"))
1467     return ctables_table_parse_subtotal (lexer, false, cat);
1468   else if (lex_match_id (lexer, "HSUBTOTAL"))
1469     return ctables_table_parse_subtotal (lexer, true, cat);
1470   else if (lex_match_id (lexer, "LO"))
1471     {
1472       if (!lex_force_match_id (lexer, "THRU"))
1473         return false;
1474       if (lex_is_string (lexer))
1475         {
1476           struct substring sr0 = { .string = NULL };
1477           struct substring sr1 = parse_substring (lexer, dict);
1478           *cat = cct_srange (sr0, sr1);
1479         }
1480       else if (lex_force_num (lexer))
1481         {
1482           *cat = cct_nrange (-DBL_MAX, lex_number (lexer));
1483           lex_get (lexer);
1484         }
1485       else
1486         return false;
1487     }
1488   else if (lex_is_number (lexer))
1489     {
1490       double number = lex_number (lexer);
1491       lex_get (lexer);
1492       if (lex_match_id (lexer, "THRU"))
1493         {
1494           if (lex_match_id (lexer, "HI"))
1495             *cat = cct_nrange (number, DBL_MAX);
1496           else
1497             {
1498               if (!lex_force_num (lexer))
1499                 return false;
1500               *cat = cct_nrange (number, lex_number (lexer));
1501               lex_get (lexer);
1502             }
1503         }
1504       else
1505         *cat = (struct ctables_category) {
1506           .type = CCT_NUMBER,
1507           .number = number
1508         };
1509     }
1510   else if (lex_is_string (lexer))
1511     {
1512       struct substring s = parse_substring (lexer, dict);
1513       if (lex_match_id (lexer, "THRU"))
1514         {
1515           if (lex_match_id (lexer, "HI"))
1516             {
1517               struct substring sr1 = { .string = NULL };
1518               *cat = cct_srange (s, sr1);
1519             }
1520           else
1521             {
1522               if (!lex_force_string (lexer))
1523                 {
1524                   ss_dealloc (&s);
1525                   return false;
1526                 }
1527               struct substring sr1 = parse_substring (lexer, dict);
1528               *cat = cct_srange (s, sr1);
1529             }
1530         }
1531       else
1532         *cat = (struct ctables_category) { .type = CCT_STRING, .string = s };
1533     }
1534   else if (lex_match (lexer, T_AND))
1535     {
1536       if (!lex_force_id (lexer))
1537         return false;
1538       struct ctables_postcompute *pc = ctables_find_postcompute (
1539         ct, lex_tokcstr (lexer));
1540       if (!pc)
1541         {
1542           struct msg_location *loc = lex_get_location (lexer, -1, 0);
1543           msg_at (SE, loc, _("Unknown postcompute &%s."),
1544                   lex_tokcstr (lexer));
1545           msg_location_destroy (loc);
1546           return false;
1547         }
1548       lex_get (lexer);
1549
1550       *cat = (struct ctables_category) { .type = CCT_POSTCOMPUTE, .pc = pc };
1551     }
1552   else
1553     {
1554       lex_error (lexer, NULL);
1555       return false;
1556     }
1557
1558   return true;
1559 }
1560
1561 static bool
1562 parse_category_string (struct msg_location *location,
1563                        struct substring s, const struct dictionary *dict,
1564                        enum fmt_type format, double *n)
1565 {
1566   union value v;
1567   char *error = data_in (s, dict_get_encoding (dict), format,
1568                          settings_get_fmt_settings (), &v, 0, NULL);
1569   if (error)
1570     {
1571       msg_at (SE, location,
1572               _("Failed to parse category specification as format %s: %s."),
1573               fmt_name (format), error);
1574       free (error);
1575       return false;
1576     }
1577
1578   *n = v.f;
1579   return true;
1580 }
1581
1582 static struct ctables_category *
1583 ctables_find_category_for_postcompute__ (const struct ctables_categories *cats,
1584                                          const struct ctables_pcexpr *e)
1585 {
1586   struct ctables_category *best = NULL;
1587   size_t n_subtotals = 0;
1588   for (size_t i = 0; i < cats->n_cats; i++)
1589     {
1590       struct ctables_category *cat = &cats->cats[i];
1591       switch (e->op)
1592         {
1593         case CTPO_CAT_NUMBER:
1594           if (cat->type == CCT_NUMBER && cat->number == e->number)
1595             best = cat;
1596           break;
1597
1598         case CTPO_CAT_STRING:
1599           if (cat->type == CCT_STRING && ss_equals (cat->string, e->string))
1600             best = cat;
1601           break;
1602
1603         case CTPO_CAT_NRANGE:
1604           if (cat->type == CCT_NRANGE
1605               && cat->nrange[0] == e->nrange[0]
1606               && cat->nrange[1] == e->nrange[1])
1607             best = cat;
1608           break;
1609
1610         case CTPO_CAT_SRANGE:
1611           if (cat->type == CCT_SRANGE
1612               && nullable_substring_equal (&cat->srange[0], &e->srange[0])
1613               && nullable_substring_equal (&cat->srange[1], &e->srange[1]))
1614             best = cat;
1615           break;
1616
1617         case CTPO_CAT_MISSING:
1618           if (cat->type == CCT_MISSING)
1619             best = cat;
1620           break;
1621
1622         case CTPO_CAT_OTHERNM:
1623           if (cat->type == CCT_OTHERNM)
1624             best = cat;
1625           break;
1626
1627         case CTPO_CAT_SUBTOTAL:
1628           if (cat->type == CCT_SUBTOTAL)
1629             {
1630               n_subtotals++;
1631               if (e->subtotal_index == n_subtotals)
1632                 return cat;
1633               else if (e->subtotal_index == 0)
1634                 best = cat;
1635             }
1636           break;
1637
1638         case CTPO_CAT_TOTAL:
1639           if (cat->type == CCT_TOTAL)
1640             return cat;
1641           break;
1642
1643         case CTPO_CONSTANT:
1644         case CTPO_ADD:
1645         case CTPO_SUB:
1646         case CTPO_MUL:
1647         case CTPO_DIV:
1648         case CTPO_POW:
1649         case CTPO_NEG:
1650           NOT_REACHED ();
1651         }
1652     }
1653   if (e->op == CTPO_CAT_SUBTOTAL && e->subtotal_index == 0 && n_subtotals > 1)
1654     return NULL;
1655   return best;
1656 }
1657
1658 static struct ctables_category *
1659 ctables_find_category_for_postcompute (const struct dictionary *dict,
1660                                        const struct ctables_categories *cats,
1661                                        enum fmt_type parse_format,
1662                                        const struct ctables_pcexpr *e)
1663 {
1664   if (parse_format != FMT_F)
1665     {
1666       if (e->op == CTPO_CAT_STRING)
1667         {
1668           double number;
1669           if (!parse_category_string (e->location, e->string, dict,
1670                                       parse_format, &number))
1671             return NULL;
1672
1673           struct ctables_pcexpr e2 = {
1674             .op = CTPO_CAT_NUMBER,
1675             .number = number,
1676             .location = e->location,
1677           };
1678           return ctables_find_category_for_postcompute__ (cats, &e2);
1679         }
1680       else if (e->op == CTPO_CAT_SRANGE)
1681         {
1682           double nrange[2];
1683           if (!e->srange[0].string)
1684             nrange[0] = -DBL_MAX;
1685           else if (!parse_category_string (e->location, e->srange[0], dict,
1686                                            parse_format, &nrange[0]))
1687             return NULL;
1688
1689           if (!e->srange[1].string)
1690             nrange[1] = DBL_MAX;
1691           else if (!parse_category_string (e->location, e->srange[1], dict,
1692                                            parse_format, &nrange[1]))
1693             return NULL;
1694
1695           struct ctables_pcexpr e2 = {
1696             .op = CTPO_CAT_NRANGE,
1697             .nrange = { nrange[0], nrange[1] },
1698             .location = e->location,
1699           };
1700           return ctables_find_category_for_postcompute__ (cats, &e2);
1701         }
1702     }
1703   return ctables_find_category_for_postcompute__ (cats, e);
1704 }
1705
1706 static bool
1707 ctables_recursive_check_postcompute (struct dictionary *dict,
1708                                      const struct ctables_pcexpr *e,
1709                                      struct ctables_category *pc_cat,
1710                                      const struct ctables_categories *cats,
1711                                      const struct msg_location *cats_location)
1712 {
1713   switch (e->op)
1714     {
1715     case CTPO_CAT_NUMBER:
1716     case CTPO_CAT_STRING:
1717     case CTPO_CAT_NRANGE:
1718     case CTPO_CAT_SRANGE:
1719     case CTPO_CAT_MISSING:
1720     case CTPO_CAT_OTHERNM:
1721     case CTPO_CAT_SUBTOTAL:
1722     case CTPO_CAT_TOTAL:
1723       {
1724         struct ctables_category *cat = ctables_find_category_for_postcompute (
1725           dict, cats, pc_cat->parse_format, e);
1726         if (!cat)
1727           {
1728             if (e->op == CTPO_CAT_SUBTOTAL && e->subtotal_index == 0)
1729               {
1730                 size_t n_subtotals = 0;
1731                 for (size_t i = 0; i < cats->n_cats; i++)
1732                   n_subtotals += cats->cats[i].type == CCT_SUBTOTAL;
1733                 if (n_subtotals > 1)
1734                   {
1735                     msg_at (SE, cats_location,
1736                             ngettext ("These categories include %zu instance "
1737                                       "of SUBTOTAL or HSUBTOTAL, so references "
1738                                       "from computed categories must refer to "
1739                                       "subtotals by position, "
1740                                       "e.g. SUBTOTAL[1].",
1741                                       "These categories include %zu instances "
1742                                       "of SUBTOTAL or HSUBTOTAL, so references "
1743                                       "from computed categories must refer to "
1744                                       "subtotals by position, "
1745                                       "e.g. SUBTOTAL[1].",
1746                                       n_subtotals),
1747                             n_subtotals);
1748                     msg_at (SN, e->location,
1749                             _("This is the reference that lacks a position."));
1750                     return NULL;
1751                   }
1752               }
1753
1754             msg_at (SE, pc_cat->location,
1755                     _("Computed category &%s references a category not included "
1756                       "in the category list."),
1757                     pc_cat->pc->name);
1758             msg_at (SN, e->location, _("This is the missing category."));
1759             if (e->op == CTPO_CAT_SUBTOTAL)
1760               msg_at (SN, cats_location,
1761                       _("To fix the problem, add subtotals to the "
1762                         "list of categories here."));
1763             else if (e->op == CTPO_CAT_TOTAL)
1764               msg (SN, _("To fix the problem, add TOTAL=YES to the variable's "
1765                          "CATEGORIES specification."));
1766             else
1767               msg_at (SN, cats_location,
1768                       _("To fix the problem, add the missing category to the "
1769                         "list of categories here."));
1770             return false;
1771           }
1772         if (pc_cat->pc->hide_source_cats)
1773           cat->hide = true;
1774         return true;
1775       }
1776
1777     case CTPO_CONSTANT:
1778       return true;
1779
1780     case CTPO_ADD:
1781     case CTPO_SUB:
1782     case CTPO_MUL:
1783     case CTPO_DIV:
1784     case CTPO_POW:
1785     case CTPO_NEG:
1786       for (size_t i = 0; i < 2; i++)
1787         if (e->subs[i] && !ctables_recursive_check_postcompute (
1788               dict, e->subs[i], pc_cat, cats, cats_location))
1789           return false;
1790       return true;
1791     }
1792
1793   NOT_REACHED ();
1794 }
1795
1796 static bool
1797 all_strings (struct variable **vars, size_t n_vars,
1798              const struct ctables_category *cat)
1799 {
1800   for (size_t j = 0; j < n_vars; j++)
1801     if (var_is_numeric (vars[j]))
1802       {
1803         msg_at (SE, cat->location,
1804                 _("This category specification may be applied only to string "
1805                   "variables, but this subcommand tries to apply it to "
1806                   "numeric variable %s."),
1807                 var_get_name (vars[j]));
1808         return false;
1809       }
1810   return true;
1811 }
1812
1813 static bool
1814 ctables_table_parse_categories (struct lexer *lexer, struct dictionary *dict,
1815                                 struct ctables *ct, struct ctables_table *t)
1816 {
1817   if (!lex_match_id (lexer, "VARIABLES"))
1818     return false;
1819   lex_match (lexer, T_EQUALS);
1820
1821   struct variable **vars;
1822   size_t n_vars;
1823   if (!parse_variables (lexer, dict, &vars, &n_vars, PV_NO_SCRATCH))
1824     return false;
1825
1826   const struct fmt_spec *common_format = var_get_print_format (vars[0]);
1827   for (size_t i = 1; i < n_vars; i++)
1828     {
1829       const struct fmt_spec *f = var_get_print_format (vars[i]);
1830       if (f->type != common_format->type)
1831         {
1832           common_format = NULL;
1833           break;
1834         }
1835     }
1836   bool parse_strings
1837     = (common_format
1838        && (fmt_get_category (common_format->type)
1839            & (FMT_CAT_DATE | FMT_CAT_TIME | FMT_CAT_DATE_COMPONENT)));
1840
1841   struct ctables_categories *c = xmalloc (sizeof *c);
1842   *c = (struct ctables_categories) { .n_refs = n_vars, .show_empty = true };
1843   for (size_t i = 0; i < n_vars; i++)
1844     {
1845       struct ctables_categories **cp
1846         = &t->categories[var_get_dict_index (vars[i])];
1847       ctables_categories_unref (*cp);
1848       *cp = c;
1849     }
1850
1851   size_t allocated_cats = 0;
1852   int cats_start_ofs = -1;
1853   int cats_end_ofs = -1;
1854   if (lex_match (lexer, T_LBRACK))
1855     {
1856       cats_start_ofs = lex_ofs (lexer);
1857       do
1858         {
1859           if (c->n_cats >= allocated_cats)
1860             c->cats = x2nrealloc (c->cats, &allocated_cats, sizeof *c->cats);
1861
1862           int start_ofs = lex_ofs (lexer);
1863           struct ctables_category *cat = &c->cats[c->n_cats];
1864           if (!ctables_table_parse_explicit_category (lexer, dict, ct, cat))
1865             goto error;
1866           cat->location = lex_ofs_location (lexer, start_ofs, lex_ofs (lexer) - 1);
1867           c->n_cats++;
1868
1869           lex_match (lexer, T_COMMA);
1870         }
1871       while (!lex_match (lexer, T_RBRACK));
1872       cats_end_ofs = lex_ofs (lexer) - 1;
1873     }
1874
1875   struct ctables_category cat = {
1876     .type = CCT_VALUE,
1877     .include_missing = false,
1878     .sort_ascending = true,
1879   };
1880   bool show_totals = false;
1881   char *total_label = NULL;
1882   bool totals_before = false;
1883   while (lex_token (lexer) != T_SLASH && lex_token (lexer) != T_ENDCMD)
1884     {
1885       if (!c->n_cats && lex_match_id (lexer, "ORDER"))
1886         {
1887           lex_match (lexer, T_EQUALS);
1888           if (lex_match_id (lexer, "A"))
1889             cat.sort_ascending = true;
1890           else if (lex_match_id (lexer, "D"))
1891             cat.sort_ascending = false;
1892           else
1893             {
1894               lex_error_expecting (lexer, "A", "D");
1895               goto error;
1896             }
1897         }
1898       else if (!c->n_cats && lex_match_id (lexer, "KEY"))
1899         {
1900           lex_match (lexer, T_EQUALS);
1901           if (lex_match_id (lexer, "VALUE"))
1902             cat.type = CCT_VALUE;
1903           else if (lex_match_id (lexer, "LABEL"))
1904             cat.type = CCT_LABEL;
1905           else
1906             {
1907               cat.type = CCT_FUNCTION;
1908               if (!parse_ctables_summary_function (lexer, &cat.sort_function))
1909                 goto error;
1910
1911               if (lex_match (lexer, T_LPAREN))
1912                 {
1913                   cat.sort_var = parse_variable (lexer, dict);
1914                   if (!cat.sort_var)
1915                     goto error;
1916
1917                   if (cat.sort_function == CTSF_PTILE)
1918                     {
1919                       lex_match (lexer, T_COMMA);
1920                       if (!lex_force_num_range_closed (lexer, "PTILE", 0, 100))
1921                         goto error;
1922                       cat.percentile = lex_number (lexer);
1923                       lex_get (lexer);
1924                     }
1925
1926                   if (!lex_force_match (lexer, T_RPAREN))
1927                     goto error;
1928                 }
1929               else if (ctables_function_availability (cat.sort_function)
1930                        == CTFA_SCALE)
1931                 {
1932                   bool UNUSED b = lex_force_match (lexer, T_LPAREN);
1933                   goto error;
1934                 }
1935             }
1936         }
1937       else if (!c->n_cats && lex_match_id (lexer, "MISSING"))
1938         {
1939           lex_match (lexer, T_EQUALS);
1940           if (lex_match_id (lexer, "INCLUDE"))
1941             cat.include_missing = true;
1942           else if (lex_match_id (lexer, "EXCLUDE"))
1943             cat.include_missing = false;
1944           else
1945             {
1946               lex_error_expecting (lexer, "INCLUDE", "EXCLUDE");
1947               goto error;
1948             }
1949         }
1950       else if (lex_match_id (lexer, "TOTAL"))
1951         {
1952           lex_match (lexer, T_EQUALS);
1953           if (!parse_bool (lexer, &show_totals))
1954             goto error;
1955         }
1956       else if (lex_match_id (lexer, "LABEL"))
1957         {
1958           lex_match (lexer, T_EQUALS);
1959           if (!lex_force_string (lexer))
1960             goto error;
1961           free (total_label);
1962           total_label = ss_xstrdup (lex_tokss (lexer));
1963           lex_get (lexer);
1964         }
1965       else if (lex_match_id (lexer, "POSITION"))
1966         {
1967           lex_match (lexer, T_EQUALS);
1968           if (lex_match_id (lexer, "BEFORE"))
1969             totals_before = true;
1970           else if (lex_match_id (lexer, "AFTER"))
1971             totals_before = false;
1972           else
1973             {
1974               lex_error_expecting (lexer, "BEFORE", "AFTER");
1975               goto error;
1976             }
1977         }
1978       else if (lex_match_id (lexer, "EMPTY"))
1979         {
1980           lex_match (lexer, T_EQUALS);
1981           if (lex_match_id (lexer, "INCLUDE"))
1982             c->show_empty = true;
1983           else if (lex_match_id (lexer, "EXCLUDE"))
1984             c->show_empty = false;
1985           else
1986             {
1987               lex_error_expecting (lexer, "INCLUDE", "EXCLUDE");
1988               goto error;
1989             }
1990         }
1991       else
1992         {
1993           if (!c->n_cats)
1994             lex_error_expecting (lexer, "ORDER", "KEY", "MISSING",
1995                                  "TOTAL", "LABEL", "POSITION", "EMPTY");
1996           else
1997             lex_error_expecting (lexer, "TOTAL", "LABEL", "POSITION", "EMPTY");
1998           goto error;
1999         }
2000     }
2001
2002   if (!c->n_cats)
2003     {
2004       if (c->n_cats >= allocated_cats)
2005         c->cats = x2nrealloc (c->cats, &allocated_cats, sizeof *c->cats);
2006       c->cats[c->n_cats++] = cat;
2007     }
2008
2009   if (show_totals)
2010     {
2011       if (c->n_cats >= allocated_cats)
2012         c->cats = x2nrealloc (c->cats, &allocated_cats, sizeof *c->cats);
2013
2014       struct ctables_category *totals;
2015       if (totals_before)
2016         {
2017           insert_element (c->cats, c->n_cats, sizeof *c->cats, 0);
2018           totals = &c->cats[0];
2019         }
2020       else
2021         totals = &c->cats[c->n_cats];
2022       c->n_cats++;
2023
2024       *totals = (struct ctables_category) {
2025         .type = CCT_TOTAL,
2026         .total_label = total_label ? total_label : xstrdup (_("Total")),
2027       };
2028     }
2029
2030   struct ctables_category *subtotal = NULL;
2031   for (size_t i = totals_before ? 0 : c->n_cats;
2032        totals_before ? i < c->n_cats : i-- > 0;
2033        totals_before ? i++ : 0)
2034     {
2035       struct ctables_category *cat = &c->cats[i];
2036       switch (cat->type)
2037         {
2038         case CCT_NUMBER:
2039         case CCT_STRING:
2040         case CCT_NRANGE:
2041         case CCT_SRANGE:
2042         case CCT_MISSING:
2043         case CCT_OTHERNM:
2044           cat->subtotal = subtotal;
2045           break;
2046
2047         case CCT_POSTCOMPUTE:
2048           break;
2049
2050         case CCT_SUBTOTAL:
2051           subtotal = cat;
2052           break;
2053
2054         case CCT_TOTAL:
2055         case CCT_VALUE:
2056         case CCT_LABEL:
2057         case CCT_FUNCTION:
2058         case CCT_EXCLUDED_MISSING:
2059           break;
2060         }
2061     }
2062
2063   if (cats_start_ofs != -1)
2064     {
2065       for (size_t i = 0; i < c->n_cats; i++)
2066         {
2067           struct ctables_category *cat = &c->cats[i];
2068           switch (cat->type)
2069             {
2070             case CCT_POSTCOMPUTE:
2071               cat->parse_format = parse_strings ? common_format->type : FMT_F;
2072               struct msg_location *cats_location
2073                 = lex_ofs_location (lexer, cats_start_ofs, cats_end_ofs);
2074               bool ok = ctables_recursive_check_postcompute (
2075                 dict, cat->pc->expr, cat, c, cats_location);
2076               msg_location_destroy (cats_location);
2077               if (!ok)
2078                 goto error;
2079               break;
2080
2081             case CCT_NUMBER:
2082             case CCT_NRANGE:
2083               for (size_t j = 0; j < n_vars; j++)
2084                 if (var_is_alpha (vars[j]))
2085                   {
2086                     msg_at (SE, cat->location,
2087                             _("This category specification may be applied "
2088                               "only to numeric variables, but this "
2089                               "subcommand tries to apply it to string "
2090                               "variable %s."),
2091                             var_get_name (vars[j]));
2092                     goto error;
2093                   }
2094               break;
2095
2096             case CCT_STRING:
2097               if (parse_strings)
2098                 {
2099                   double n;
2100                   if (!parse_category_string (cat->location, cat->string, dict,
2101                                               common_format->type, &n))
2102                     goto error;
2103
2104                   ss_dealloc (&cat->string);
2105
2106                   cat->type = CCT_NUMBER;
2107                   cat->number = n;
2108                 }
2109               else if (!all_strings (vars, n_vars, cat))
2110                 goto error;
2111               break;
2112
2113             case CCT_SRANGE:
2114               if (parse_strings)
2115                 {
2116                   double n[2];
2117
2118                   if (!cat->srange[0].string)
2119                     n[0] = -DBL_MAX;
2120                   else if (!parse_category_string (cat->location,
2121                                                    cat->srange[0], dict,
2122                                                    common_format->type, &n[0]))
2123                     goto error;
2124
2125                   if (!cat->srange[1].string)
2126                     n[1] = DBL_MAX;
2127                   else if (!parse_category_string (cat->location,
2128                                                    cat->srange[1], dict,
2129                                                    common_format->type, &n[1]))
2130                     goto error;
2131
2132                   ss_dealloc (&cat->srange[0]);
2133                   ss_dealloc (&cat->srange[1]);
2134
2135                   cat->type = CCT_NRANGE;
2136                   cat->nrange[0] = n[0];
2137                   cat->nrange[1] = n[1];
2138                 }
2139               else if (!all_strings (vars, n_vars, cat))
2140                 goto error;
2141               break;
2142
2143             case CCT_MISSING:
2144             case CCT_OTHERNM:
2145             case CCT_SUBTOTAL:
2146             case CCT_TOTAL:
2147             case CCT_VALUE:
2148             case CCT_LABEL:
2149             case CCT_FUNCTION:
2150             case CCT_EXCLUDED_MISSING:
2151               break;
2152             }
2153         }
2154     }
2155
2156   free (vars);
2157   return true;
2158
2159 error:
2160   free (vars);
2161   return false;
2162 }
2163
2164 static void
2165 ctables_nest_uninit (struct ctables_nest *nest)
2166 {
2167   free (nest->vars);
2168   for (enum ctables_summary_variant sv = 0; sv < N_CSVS; sv++)
2169     ctables_summary_spec_set_uninit (&nest->specs[sv]);
2170   for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
2171     free (nest->domains[dt]);
2172 }
2173
2174 static void
2175 ctables_stack_uninit (struct ctables_stack *stack)
2176 {
2177   if (stack)
2178     {
2179       for (size_t i = 0; i < stack->n; i++)
2180         ctables_nest_uninit (&stack->nests[i]);
2181       free (stack->nests);
2182     }
2183 }
2184
2185 static struct ctables_stack
2186 nest_fts (struct ctables_stack s0, struct ctables_stack s1)
2187 {
2188   if (!s0.n)
2189     return s1;
2190   else if (!s1.n)
2191     return s0;
2192
2193   struct ctables_stack stack = { .nests = xnmalloc (s0.n, s1.n * sizeof *stack.nests) };
2194   for (size_t i = 0; i < s0.n; i++)
2195     for (size_t j = 0; j < s1.n; j++)
2196       {
2197         const struct ctables_nest *a = &s0.nests[i];
2198         const struct ctables_nest *b = &s1.nests[j];
2199
2200         size_t allocate = a->n + b->n;
2201         struct variable **vars = xnmalloc (allocate, sizeof *vars);
2202         size_t n = 0;
2203         for (size_t k = 0; k < a->n; k++)
2204           vars[n++] = a->vars[k];
2205         for (size_t k = 0; k < b->n; k++)
2206           vars[n++] = b->vars[k];
2207         assert (n == allocate);
2208
2209         const struct ctables_nest *summary_src;
2210         if (!a->specs[CSV_CELL].var)
2211           summary_src = b;
2212         else if (!b->specs[CSV_CELL].var)
2213           summary_src = a;
2214         else
2215           NOT_REACHED ();
2216
2217         struct ctables_nest *new = &stack.nests[stack.n++];
2218         *new = (struct ctables_nest) {
2219           .vars = vars,
2220           .scale_idx = (a->scale_idx != SIZE_MAX ? a->scale_idx
2221                         : b->scale_idx != SIZE_MAX ? a->n + b->scale_idx
2222                         : SIZE_MAX),
2223           .n = n,
2224         };
2225         for (enum ctables_summary_variant sv = 0; sv < N_CSVS; sv++)
2226           ctables_summary_spec_set_clone (&new->specs[sv], &summary_src->specs[sv]);
2227       }
2228   ctables_stack_uninit (&s0);
2229   ctables_stack_uninit (&s1);
2230   return stack;
2231 }
2232
2233 static struct ctables_stack
2234 stack_fts (struct ctables_stack s0, struct ctables_stack s1)
2235 {
2236   struct ctables_stack stack = { .nests = xnmalloc (s0.n + s1.n, sizeof *stack.nests) };
2237   for (size_t i = 0; i < s0.n; i++)
2238     stack.nests[stack.n++] = s0.nests[i];
2239   for (size_t i = 0; i < s1.n; i++)
2240     {
2241       stack.nests[stack.n] = s1.nests[i];
2242       stack.nests[stack.n].group_head += s0.n;
2243       stack.n++;
2244     }
2245   assert (stack.n == s0.n + s1.n);
2246   free (s0.nests);
2247   free (s1.nests);
2248   return stack;
2249 }
2250
2251 static struct ctables_stack
2252 var_fts (const struct ctables_axis *a)
2253 {
2254   struct variable **vars = xmalloc (sizeof *vars);
2255   *vars = a->var;
2256
2257   struct ctables_nest *nest = xmalloc (sizeof *nest);
2258   *nest = (struct ctables_nest) {
2259     .vars = vars,
2260     .n = 1,
2261     .scale_idx = a->scale ? 0 : SIZE_MAX,
2262   };
2263   if (a->specs[CSV_CELL].n || a->scale)
2264     for (enum ctables_summary_variant sv = 0; sv < N_CSVS; sv++)
2265       {
2266         ctables_summary_spec_set_clone (&nest->specs[sv], &a->specs[sv]);
2267         nest->specs[sv].var = a->var;
2268         nest->specs[sv].is_scale = a->scale;
2269       }
2270   return (struct ctables_stack) { .nests = nest, .n = 1 };
2271 }
2272
2273 static struct ctables_stack
2274 enumerate_fts (enum pivot_axis_type axis_type, const struct ctables_axis *a)
2275 {
2276   if (!a)
2277     return (struct ctables_stack) { .n = 0 };
2278
2279   switch (a->op)
2280     {
2281     case CTAO_VAR:
2282       return var_fts (a);
2283
2284     case CTAO_STACK:
2285       return stack_fts (enumerate_fts (axis_type, a->subs[0]),
2286                         enumerate_fts (axis_type, a->subs[1]));
2287
2288     case CTAO_NEST:
2289       /* This should consider any of the scale variables found in the result to
2290          be linked to each other listwise for SMISSING=LISTWISE. */
2291       return nest_fts (enumerate_fts (axis_type, a->subs[0]),
2292                        enumerate_fts (axis_type, a->subs[1]));
2293     }
2294
2295   NOT_REACHED ();
2296 }
2297
2298 union ctables_summary
2299   {
2300     /* COUNT, VALIDN, TOTALN. */
2301     double count;
2302
2303     /* MINIMUM, MAXIMUM, RANGE. */
2304     struct
2305       {
2306         double min;
2307         double max;
2308       };
2309
2310     /* MEAN, SEMEAN, STDDEV, SUM, VARIANCE, *.SUM. */
2311     struct moments1 *moments;
2312
2313     /* MEDIAN, MODE, PTILE. */
2314     struct
2315       {
2316         struct casewriter *writer;
2317         double ovalid;
2318         double ovalue;
2319       };
2320
2321     /* XXX multiple response */
2322   };
2323
2324 static void
2325 ctables_summary_init (union ctables_summary *s,
2326                       const struct ctables_summary_spec *ss)
2327 {
2328   switch (ss->function)
2329     {
2330     case CTSF_COUNT:
2331     case CTSF_ECOUNT:
2332     case CTSF_ROWPCT_COUNT:
2333     case CTSF_COLPCT_COUNT:
2334     case CTSF_TABLEPCT_COUNT:
2335     case CTSF_SUBTABLEPCT_COUNT:
2336     case CTSF_LAYERPCT_COUNT:
2337     case CTSF_LAYERROWPCT_COUNT:
2338     case CTSF_LAYERCOLPCT_COUNT:
2339     case CTSF_ROWPCT_VALIDN:
2340     case CTSF_COLPCT_VALIDN:
2341     case CTSF_TABLEPCT_VALIDN:
2342     case CTSF_SUBTABLEPCT_VALIDN:
2343     case CTSF_LAYERPCT_VALIDN:
2344     case CTSF_LAYERROWPCT_VALIDN:
2345     case CTSF_LAYERCOLPCT_VALIDN:
2346     case CTSF_ROWPCT_TOTALN:
2347     case CTSF_COLPCT_TOTALN:
2348     case CTSF_TABLEPCT_TOTALN:
2349     case CTSF_SUBTABLEPCT_TOTALN:
2350     case CTSF_LAYERPCT_TOTALN:
2351     case CTSF_LAYERROWPCT_TOTALN:
2352     case CTSF_LAYERCOLPCT_TOTALN:
2353     case CTSF_MISSING:
2354     case CSTF_TOTALN:
2355     case CTSF_ETOTALN:
2356     case CTSF_VALIDN:
2357     case CTSF_EVALIDN:
2358     case CTSF_UCOUNT:
2359     case CTSF_UROWPCT_COUNT:
2360     case CTSF_UCOLPCT_COUNT:
2361     case CTSF_UTABLEPCT_COUNT:
2362     case CTSF_USUBTABLEPCT_COUNT:
2363     case CTSF_ULAYERPCT_COUNT:
2364     case CTSF_ULAYERROWPCT_COUNT:
2365     case CTSF_ULAYERCOLPCT_COUNT:
2366     case CTSF_UROWPCT_VALIDN:
2367     case CTSF_UCOLPCT_VALIDN:
2368     case CTSF_UTABLEPCT_VALIDN:
2369     case CTSF_USUBTABLEPCT_VALIDN:
2370     case CTSF_ULAYERPCT_VALIDN:
2371     case CTSF_ULAYERROWPCT_VALIDN:
2372     case CTSF_ULAYERCOLPCT_VALIDN:
2373     case CTSF_UROWPCT_TOTALN:
2374     case CTSF_UCOLPCT_TOTALN:
2375     case CTSF_UTABLEPCT_TOTALN:
2376     case CTSF_USUBTABLEPCT_TOTALN:
2377     case CTSF_ULAYERPCT_TOTALN:
2378     case CTSF_ULAYERROWPCT_TOTALN:
2379     case CTSF_ULAYERCOLPCT_TOTALN:
2380     case CTSF_UMISSING:
2381     case CSTF_UTOTALN:
2382     case CTSF_UVALIDN:
2383       s->count = 0;
2384       break;
2385
2386     case CTSF_ROW_ID:
2387     case CTSF_COL_ID:
2388     case CTSF_TABLE_ID:
2389     case CTSF_SUBTABLE_ID:
2390     case CTSF_LAYER_ID:
2391     case CTSF_LAYERROW_ID:
2392     case CTSF_LAYERCOL_ID:
2393       break;
2394
2395     case CTSF_MAXIMUM:
2396     case CTSF_MINIMUM:
2397     case CTSF_RANGE:
2398       s->min = s->max = SYSMIS;
2399       break;
2400
2401     case CTSF_MEAN:
2402     case CTSF_SEMEAN:
2403     case CTSF_STDDEV:
2404     case CTSF_SUM:
2405     case CTSF_VARIANCE:
2406     case CTSF_ROWPCT_SUM:
2407     case CTSF_COLPCT_SUM:
2408     case CTSF_TABLEPCT_SUM:
2409     case CTSF_SUBTABLEPCT_SUM:
2410     case CTSF_LAYERPCT_SUM:
2411     case CTSF_LAYERROWPCT_SUM:
2412     case CTSF_LAYERCOLPCT_SUM:
2413     case CTSF_UMEAN:
2414     case CTSF_USEMEAN:
2415     case CTSF_USTDDEV:
2416     case CTSF_USUM:
2417     case CTSF_UVARIANCE:
2418     case CTSF_UROWPCT_SUM:
2419     case CTSF_UCOLPCT_SUM:
2420     case CTSF_UTABLEPCT_SUM:
2421     case CTSF_USUBTABLEPCT_SUM:
2422     case CTSF_ULAYERPCT_SUM:
2423     case CTSF_ULAYERROWPCT_SUM:
2424     case CTSF_ULAYERCOLPCT_SUM:
2425       s->moments = moments1_create (MOMENT_VARIANCE);
2426       break;
2427
2428     case CTSF_MEDIAN:
2429     case CTSF_MODE:
2430     case CTSF_PTILE:
2431     case CTSF_UMEDIAN:
2432     case CTSF_UMODE:
2433     case CTSF_UPTILE:
2434       {
2435         struct caseproto *proto = caseproto_create ();
2436         proto = caseproto_add_width (proto, 0);
2437         proto = caseproto_add_width (proto, 0);
2438
2439         struct subcase ordering;
2440         subcase_init (&ordering, 0, 0, SC_ASCEND);
2441         s->writer = sort_create_writer (&ordering, proto);
2442         subcase_uninit (&ordering);
2443         caseproto_unref (proto);
2444
2445         s->ovalid = 0;
2446         s->ovalue = SYSMIS;
2447       }
2448       break;
2449     }
2450 }
2451
2452 static void
2453 ctables_summary_uninit (union ctables_summary *s,
2454                         const struct ctables_summary_spec *ss)
2455 {
2456   switch (ss->function)
2457     {
2458     case CTSF_COUNT:
2459     case CTSF_ECOUNT:
2460     case CTSF_ROWPCT_COUNT:
2461     case CTSF_COLPCT_COUNT:
2462     case CTSF_TABLEPCT_COUNT:
2463     case CTSF_SUBTABLEPCT_COUNT:
2464     case CTSF_LAYERPCT_COUNT:
2465     case CTSF_LAYERROWPCT_COUNT:
2466     case CTSF_LAYERCOLPCT_COUNT:
2467     case CTSF_ROWPCT_VALIDN:
2468     case CTSF_COLPCT_VALIDN:
2469     case CTSF_TABLEPCT_VALIDN:
2470     case CTSF_SUBTABLEPCT_VALIDN:
2471     case CTSF_LAYERPCT_VALIDN:
2472     case CTSF_LAYERROWPCT_VALIDN:
2473     case CTSF_LAYERCOLPCT_VALIDN:
2474     case CTSF_ROWPCT_TOTALN:
2475     case CTSF_COLPCT_TOTALN:
2476     case CTSF_TABLEPCT_TOTALN:
2477     case CTSF_SUBTABLEPCT_TOTALN:
2478     case CTSF_LAYERPCT_TOTALN:
2479     case CTSF_LAYERROWPCT_TOTALN:
2480     case CTSF_LAYERCOLPCT_TOTALN:
2481     case CTSF_MISSING:
2482     case CSTF_TOTALN:
2483     case CTSF_ETOTALN:
2484     case CTSF_VALIDN:
2485     case CTSF_EVALIDN:
2486     case CTSF_UCOUNT:
2487     case CTSF_UROWPCT_COUNT:
2488     case CTSF_UCOLPCT_COUNT:
2489     case CTSF_UTABLEPCT_COUNT:
2490     case CTSF_USUBTABLEPCT_COUNT:
2491     case CTSF_ULAYERPCT_COUNT:
2492     case CTSF_ULAYERROWPCT_COUNT:
2493     case CTSF_ULAYERCOLPCT_COUNT:
2494     case CTSF_UROWPCT_VALIDN:
2495     case CTSF_UCOLPCT_VALIDN:
2496     case CTSF_UTABLEPCT_VALIDN:
2497     case CTSF_USUBTABLEPCT_VALIDN:
2498     case CTSF_ULAYERPCT_VALIDN:
2499     case CTSF_ULAYERROWPCT_VALIDN:
2500     case CTSF_ULAYERCOLPCT_VALIDN:
2501     case CTSF_UROWPCT_TOTALN:
2502     case CTSF_UCOLPCT_TOTALN:
2503     case CTSF_UTABLEPCT_TOTALN:
2504     case CTSF_USUBTABLEPCT_TOTALN:
2505     case CTSF_ULAYERPCT_TOTALN:
2506     case CTSF_ULAYERROWPCT_TOTALN:
2507     case CTSF_ULAYERCOLPCT_TOTALN:
2508     case CTSF_UMISSING:
2509     case CSTF_UTOTALN:
2510     case CTSF_UVALIDN:
2511       break;
2512
2513     case CTSF_ROW_ID:
2514     case CTSF_COL_ID:
2515     case CTSF_TABLE_ID:
2516     case CTSF_SUBTABLE_ID:
2517     case CTSF_LAYER_ID:
2518     case CTSF_LAYERROW_ID:
2519     case CTSF_LAYERCOL_ID:
2520       break;
2521
2522     case CTSF_MAXIMUM:
2523     case CTSF_MINIMUM:
2524     case CTSF_RANGE:
2525       break;
2526
2527     case CTSF_MEAN:
2528     case CTSF_SEMEAN:
2529     case CTSF_STDDEV:
2530     case CTSF_SUM:
2531     case CTSF_VARIANCE:
2532     case CTSF_ROWPCT_SUM:
2533     case CTSF_COLPCT_SUM:
2534     case CTSF_TABLEPCT_SUM:
2535     case CTSF_SUBTABLEPCT_SUM:
2536     case CTSF_LAYERPCT_SUM:
2537     case CTSF_LAYERROWPCT_SUM:
2538     case CTSF_LAYERCOLPCT_SUM:
2539     case CTSF_UMEAN:
2540     case CTSF_USEMEAN:
2541     case CTSF_USTDDEV:
2542     case CTSF_USUM:
2543     case CTSF_UVARIANCE:
2544     case CTSF_UROWPCT_SUM:
2545     case CTSF_UCOLPCT_SUM:
2546     case CTSF_UTABLEPCT_SUM:
2547     case CTSF_USUBTABLEPCT_SUM:
2548     case CTSF_ULAYERPCT_SUM:
2549     case CTSF_ULAYERROWPCT_SUM:
2550     case CTSF_ULAYERCOLPCT_SUM:
2551       moments1_destroy (s->moments);
2552       break;
2553
2554     case CTSF_MEDIAN:
2555     case CTSF_MODE:
2556     case CTSF_PTILE:
2557     case CTSF_UMEDIAN:
2558     case CTSF_UMODE:
2559     case CTSF_UPTILE:
2560       casewriter_destroy (s->writer);
2561       break;
2562     }
2563 }
2564
2565 static void
2566 ctables_summary_add (union ctables_summary *s,
2567                      const struct ctables_summary_spec *ss,
2568                      const struct variable *var, const union value *value,
2569                      bool is_scale, bool is_scale_missing,
2570                      bool is_missing, bool excluded_missing,
2571                      double d_weight, double e_weight)
2572 {
2573   /* To determine whether a case is included in a given table for a particular
2574      kind of summary, consider the following charts for each variable in the
2575      table.  Only if "yes" appears for every variable for the summary is the
2576      case counted.
2577
2578      Categorical variables:                    VALIDN   COUNT   TOTALN
2579        Valid values in included categories       yes     yes      yes
2580        Missing values in included categories     ---     yes      yes
2581        Missing values in excluded categories     ---     ---      yes
2582        Valid values in excluded categories       ---     ---      ---
2583
2584      Scale variables:                          VALIDN   COUNT   TOTALN
2585        Valid value                               yes     yes      yes
2586        Missing value                             ---     yes      yes
2587
2588      Missing values include both user- and system-missing.  (The system-missing
2589      value is always in an excluded category.)
2590   */
2591   switch (ss->function)
2592     {
2593     case CSTF_TOTALN:
2594     case CTSF_ROWPCT_TOTALN:
2595     case CTSF_COLPCT_TOTALN:
2596     case CTSF_TABLEPCT_TOTALN:
2597     case CTSF_SUBTABLEPCT_TOTALN:
2598     case CTSF_LAYERPCT_TOTALN:
2599     case CTSF_LAYERROWPCT_TOTALN:
2600     case CTSF_LAYERCOLPCT_TOTALN:
2601       s->count += d_weight;
2602       break;
2603
2604     case CSTF_UTOTALN:
2605     case CTSF_UROWPCT_TOTALN:
2606     case CTSF_UCOLPCT_TOTALN:
2607     case CTSF_UTABLEPCT_TOTALN:
2608     case CTSF_USUBTABLEPCT_TOTALN:
2609     case CTSF_ULAYERPCT_TOTALN:
2610     case CTSF_ULAYERROWPCT_TOTALN:
2611     case CTSF_ULAYERCOLPCT_TOTALN:
2612       s->count += 1.0;
2613       break;
2614
2615     case CTSF_COUNT:
2616     case CTSF_ROWPCT_COUNT:
2617     case CTSF_COLPCT_COUNT:
2618     case CTSF_TABLEPCT_COUNT:
2619     case CTSF_SUBTABLEPCT_COUNT:
2620     case CTSF_LAYERPCT_COUNT:
2621     case CTSF_LAYERROWPCT_COUNT:
2622     case CTSF_LAYERCOLPCT_COUNT:
2623       if (is_scale || !excluded_missing)
2624         s->count += d_weight;
2625       break;
2626
2627     case CTSF_UCOUNT:
2628     case CTSF_UROWPCT_COUNT:
2629     case CTSF_UCOLPCT_COUNT:
2630     case CTSF_UTABLEPCT_COUNT:
2631     case CTSF_USUBTABLEPCT_COUNT:
2632     case CTSF_ULAYERPCT_COUNT:
2633     case CTSF_ULAYERROWPCT_COUNT:
2634     case CTSF_ULAYERCOLPCT_COUNT:
2635       if (is_scale || !excluded_missing)
2636         s->count += 1.0;
2637       break;
2638
2639     case CTSF_VALIDN:
2640     case CTSF_ROWPCT_VALIDN:
2641     case CTSF_COLPCT_VALIDN:
2642     case CTSF_TABLEPCT_VALIDN:
2643     case CTSF_SUBTABLEPCT_VALIDN:
2644     case CTSF_LAYERPCT_VALIDN:
2645     case CTSF_LAYERROWPCT_VALIDN:
2646     case CTSF_LAYERCOLPCT_VALIDN:
2647       if (is_scale
2648           ? !is_scale_missing
2649           : !is_missing)
2650         s->count += d_weight;
2651       break;
2652
2653     case CTSF_UVALIDN:
2654     case CTSF_UROWPCT_VALIDN:
2655     case CTSF_UCOLPCT_VALIDN:
2656     case CTSF_UTABLEPCT_VALIDN:
2657     case CTSF_USUBTABLEPCT_VALIDN:
2658     case CTSF_ULAYERPCT_VALIDN:
2659     case CTSF_ULAYERROWPCT_VALIDN:
2660     case CTSF_ULAYERCOLPCT_VALIDN:
2661       if (is_scale
2662           ? !is_scale_missing
2663           : !is_missing)
2664         s->count += 1.0;
2665       break;
2666
2667     case CTSF_ROW_ID:
2668     case CTSF_COL_ID:
2669     case CTSF_TABLE_ID:
2670     case CTSF_SUBTABLE_ID:
2671     case CTSF_LAYER_ID:
2672     case CTSF_LAYERROW_ID:
2673     case CTSF_LAYERCOL_ID:
2674       break;
2675
2676     case CTSF_MISSING:
2677       if (is_missing)
2678         s->count += d_weight;
2679       break;
2680
2681     case CTSF_UMISSING:
2682       if (is_missing)
2683         s->count += 1.0;
2684       break;
2685
2686     case CTSF_ECOUNT:
2687       if (is_scale || !excluded_missing)
2688         s->count += e_weight;
2689       break;
2690
2691     case CTSF_EVALIDN:
2692       if (is_scale
2693           ? !is_scale_missing
2694           : !is_missing)
2695         s->count += e_weight;
2696       break;
2697
2698     case CTSF_ETOTALN:
2699       s->count += e_weight;
2700       break;
2701
2702     case CTSF_MAXIMUM:
2703     case CTSF_MINIMUM:
2704     case CTSF_RANGE:
2705       if (!is_scale_missing)
2706         {
2707           assert (!var_is_alpha (var)); /* XXX? */
2708           if (s->min == SYSMIS || value->f < s->min)
2709             s->min = value->f;
2710           if (s->max == SYSMIS || value->f > s->max)
2711             s->max = value->f;
2712         }
2713       break;
2714
2715     case CTSF_MEAN:
2716     case CTSF_SEMEAN:
2717     case CTSF_STDDEV:
2718     case CTSF_SUM:
2719     case CTSF_VARIANCE:
2720     case CTSF_ROWPCT_SUM:
2721     case CTSF_COLPCT_SUM:
2722     case CTSF_TABLEPCT_SUM:
2723     case CTSF_SUBTABLEPCT_SUM:
2724     case CTSF_LAYERPCT_SUM:
2725     case CTSF_LAYERROWPCT_SUM:
2726     case CTSF_LAYERCOLPCT_SUM:
2727       if (!is_scale_missing)
2728         moments1_add (s->moments, value->f, e_weight);
2729       break;
2730
2731     case CTSF_UMEAN:
2732     case CTSF_USEMEAN:
2733     case CTSF_USTDDEV:
2734     case CTSF_USUM:
2735     case CTSF_UVARIANCE:
2736     case CTSF_UROWPCT_SUM:
2737     case CTSF_UCOLPCT_SUM:
2738     case CTSF_UTABLEPCT_SUM:
2739     case CTSF_USUBTABLEPCT_SUM:
2740     case CTSF_ULAYERPCT_SUM:
2741     case CTSF_ULAYERROWPCT_SUM:
2742     case CTSF_ULAYERCOLPCT_SUM:
2743       if (!is_scale_missing)
2744         moments1_add (s->moments, value->f, 1.0);
2745       break;
2746
2747     case CTSF_UMEDIAN:
2748     case CTSF_UMODE:
2749     case CTSF_UPTILE:
2750       d_weight = e_weight = 1.0;
2751       /* Fall through. */
2752     case CTSF_MEDIAN:
2753     case CTSF_MODE:
2754     case CTSF_PTILE:
2755       if (!is_scale_missing)
2756         {
2757           s->ovalid += e_weight;
2758
2759           struct ccase *c = case_create (casewriter_get_proto (s->writer));
2760           *case_num_rw_idx (c, 0) = value->f;
2761           *case_num_rw_idx (c, 1) = e_weight;
2762           casewriter_write (s->writer, c);
2763         }
2764       break;
2765     }
2766 }
2767
2768 static enum ctables_domain_type
2769 ctables_function_domain (enum ctables_summary_function function)
2770 {
2771   switch (function)
2772     {
2773     case CTSF_COUNT:
2774     case CTSF_ECOUNT:
2775     case CTSF_MISSING:
2776     case CSTF_TOTALN:
2777     case CTSF_ETOTALN:
2778     case CTSF_VALIDN:
2779     case CTSF_EVALIDN:
2780     case CTSF_MAXIMUM:
2781     case CTSF_MINIMUM:
2782     case CTSF_RANGE:
2783     case CTSF_MEAN:
2784     case CTSF_SEMEAN:
2785     case CTSF_STDDEV:
2786     case CTSF_SUM:
2787     case CTSF_VARIANCE:
2788     case CTSF_MEDIAN:
2789     case CTSF_PTILE:
2790     case CTSF_MODE:
2791     case CTSF_UCOUNT:
2792     case CTSF_UMISSING:
2793     case CSTF_UTOTALN:
2794     case CTSF_UVALIDN:
2795     case CTSF_UMEAN:
2796     case CTSF_USEMEAN:
2797     case CTSF_USTDDEV:
2798     case CTSF_USUM:
2799     case CTSF_UVARIANCE:
2800     case CTSF_UMEDIAN:
2801     case CTSF_UPTILE:
2802     case CTSF_UMODE:
2803       NOT_REACHED ();
2804
2805     case CTSF_COLPCT_COUNT:
2806     case CTSF_COLPCT_SUM:
2807     case CTSF_COLPCT_TOTALN:
2808     case CTSF_COLPCT_VALIDN:
2809     case CTSF_UCOLPCT_COUNT:
2810     case CTSF_UCOLPCT_SUM:
2811     case CTSF_UCOLPCT_TOTALN:
2812     case CTSF_UCOLPCT_VALIDN:
2813     case CTSF_COL_ID:
2814       return CTDT_COL;
2815
2816     case CTSF_LAYERCOLPCT_COUNT:
2817     case CTSF_LAYERCOLPCT_SUM:
2818     case CTSF_LAYERCOLPCT_TOTALN:
2819     case CTSF_LAYERCOLPCT_VALIDN:
2820     case CTSF_ULAYERCOLPCT_COUNT:
2821     case CTSF_ULAYERCOLPCT_SUM:
2822     case CTSF_ULAYERCOLPCT_TOTALN:
2823     case CTSF_ULAYERCOLPCT_VALIDN:
2824     case CTSF_LAYERCOL_ID:
2825       return CTDT_LAYERCOL;
2826
2827     case CTSF_LAYERPCT_COUNT:
2828     case CTSF_LAYERPCT_SUM:
2829     case CTSF_LAYERPCT_TOTALN:
2830     case CTSF_LAYERPCT_VALIDN:
2831     case CTSF_ULAYERPCT_COUNT:
2832     case CTSF_ULAYERPCT_SUM:
2833     case CTSF_ULAYERPCT_TOTALN:
2834     case CTSF_ULAYERPCT_VALIDN:
2835     case CTSF_LAYER_ID:
2836       return CTDT_LAYER;
2837
2838     case CTSF_LAYERROWPCT_COUNT:
2839     case CTSF_LAYERROWPCT_SUM:
2840     case CTSF_LAYERROWPCT_TOTALN:
2841     case CTSF_LAYERROWPCT_VALIDN:
2842     case CTSF_ULAYERROWPCT_COUNT:
2843     case CTSF_ULAYERROWPCT_SUM:
2844     case CTSF_ULAYERROWPCT_TOTALN:
2845     case CTSF_ULAYERROWPCT_VALIDN:
2846     case CTSF_LAYERROW_ID:
2847       return CTDT_LAYERROW;
2848
2849     case CTSF_ROWPCT_COUNT:
2850     case CTSF_ROWPCT_SUM:
2851     case CTSF_ROWPCT_TOTALN:
2852     case CTSF_ROWPCT_VALIDN:
2853     case CTSF_UROWPCT_COUNT:
2854     case CTSF_UROWPCT_SUM:
2855     case CTSF_UROWPCT_TOTALN:
2856     case CTSF_UROWPCT_VALIDN:
2857     case CTSF_ROW_ID:
2858       return CTDT_ROW;
2859
2860     case CTSF_SUBTABLEPCT_COUNT:
2861     case CTSF_SUBTABLEPCT_SUM:
2862     case CTSF_SUBTABLEPCT_TOTALN:
2863     case CTSF_SUBTABLEPCT_VALIDN:
2864     case CTSF_USUBTABLEPCT_COUNT:
2865     case CTSF_USUBTABLEPCT_SUM:
2866     case CTSF_USUBTABLEPCT_TOTALN:
2867     case CTSF_USUBTABLEPCT_VALIDN:
2868     case CTSF_SUBTABLE_ID:
2869       return CTDT_SUBTABLE;
2870
2871     case CTSF_TABLEPCT_COUNT:
2872     case CTSF_TABLEPCT_SUM:
2873     case CTSF_TABLEPCT_TOTALN:
2874     case CTSF_TABLEPCT_VALIDN:
2875     case CTSF_UTABLEPCT_COUNT:
2876     case CTSF_UTABLEPCT_SUM:
2877     case CTSF_UTABLEPCT_TOTALN:
2878     case CTSF_UTABLEPCT_VALIDN:
2879     case CTSF_TABLE_ID:
2880       return CTDT_TABLE;
2881     }
2882
2883   NOT_REACHED ();
2884 }
2885
2886 static enum ctables_domain_type
2887 ctables_function_is_pctsum (enum ctables_summary_function function)
2888 {
2889   switch (function)
2890     {
2891     case CTSF_COUNT:
2892     case CTSF_ECOUNT:
2893     case CTSF_MISSING:
2894     case CSTF_TOTALN:
2895     case CTSF_ETOTALN:
2896     case CTSF_VALIDN:
2897     case CTSF_EVALIDN:
2898     case CTSF_MAXIMUM:
2899     case CTSF_MINIMUM:
2900     case CTSF_RANGE:
2901     case CTSF_MEAN:
2902     case CTSF_SEMEAN:
2903     case CTSF_STDDEV:
2904     case CTSF_SUM:
2905     case CTSF_VARIANCE:
2906     case CTSF_MEDIAN:
2907     case CTSF_PTILE:
2908     case CTSF_MODE:
2909     case CTSF_UCOUNT:
2910     case CTSF_UMISSING:
2911     case CSTF_UTOTALN:
2912     case CTSF_UVALIDN:
2913     case CTSF_UMEAN:
2914     case CTSF_USEMEAN:
2915     case CTSF_USTDDEV:
2916     case CTSF_USUM:
2917     case CTSF_UVARIANCE:
2918     case CTSF_UMEDIAN:
2919     case CTSF_UPTILE:
2920     case CTSF_UMODE:
2921     case CTSF_COLPCT_COUNT:
2922     case CTSF_COLPCT_TOTALN:
2923     case CTSF_COLPCT_VALIDN:
2924     case CTSF_UCOLPCT_COUNT:
2925     case CTSF_UCOLPCT_TOTALN:
2926     case CTSF_UCOLPCT_VALIDN:
2927     case CTSF_LAYERCOLPCT_COUNT:
2928     case CTSF_LAYERCOLPCT_TOTALN:
2929     case CTSF_LAYERCOLPCT_VALIDN:
2930     case CTSF_ULAYERCOLPCT_COUNT:
2931     case CTSF_ULAYERCOLPCT_TOTALN:
2932     case CTSF_ULAYERCOLPCT_VALIDN:
2933     case CTSF_LAYERPCT_COUNT:
2934     case CTSF_LAYERPCT_TOTALN:
2935     case CTSF_LAYERPCT_VALIDN:
2936     case CTSF_ULAYERPCT_COUNT:
2937     case CTSF_ULAYERPCT_TOTALN:
2938     case CTSF_ULAYERPCT_VALIDN:
2939     case CTSF_LAYERROWPCT_COUNT:
2940     case CTSF_LAYERROWPCT_TOTALN:
2941     case CTSF_LAYERROWPCT_VALIDN:
2942     case CTSF_ULAYERROWPCT_COUNT:
2943     case CTSF_ULAYERROWPCT_TOTALN:
2944     case CTSF_ULAYERROWPCT_VALIDN:
2945     case CTSF_ROWPCT_COUNT:
2946     case CTSF_ROWPCT_TOTALN:
2947     case CTSF_ROWPCT_VALIDN:
2948     case CTSF_UROWPCT_COUNT:
2949     case CTSF_UROWPCT_TOTALN:
2950     case CTSF_UROWPCT_VALIDN:
2951     case CTSF_SUBTABLEPCT_COUNT:
2952     case CTSF_SUBTABLEPCT_TOTALN:
2953     case CTSF_SUBTABLEPCT_VALIDN:
2954     case CTSF_USUBTABLEPCT_COUNT:
2955     case CTSF_USUBTABLEPCT_TOTALN:
2956     case CTSF_USUBTABLEPCT_VALIDN:
2957     case CTSF_TABLEPCT_COUNT:
2958     case CTSF_TABLEPCT_TOTALN:
2959     case CTSF_TABLEPCT_VALIDN:
2960     case CTSF_UTABLEPCT_COUNT:
2961     case CTSF_UTABLEPCT_TOTALN:
2962     case CTSF_UTABLEPCT_VALIDN:
2963     case CTSF_ROW_ID:
2964     case CTSF_COL_ID:
2965     case CTSF_TABLE_ID:
2966     case CTSF_SUBTABLE_ID:
2967     case CTSF_LAYER_ID:
2968     case CTSF_LAYERROW_ID:
2969     case CTSF_LAYERCOL_ID:
2970       return false;
2971
2972     case CTSF_COLPCT_SUM:
2973     case CTSF_UCOLPCT_SUM:
2974     case CTSF_LAYERCOLPCT_SUM:
2975     case CTSF_ULAYERCOLPCT_SUM:
2976     case CTSF_LAYERPCT_SUM:
2977     case CTSF_ULAYERPCT_SUM:
2978     case CTSF_LAYERROWPCT_SUM:
2979     case CTSF_ULAYERROWPCT_SUM:
2980     case CTSF_ROWPCT_SUM:
2981     case CTSF_UROWPCT_SUM:
2982     case CTSF_SUBTABLEPCT_SUM:
2983     case CTSF_USUBTABLEPCT_SUM:
2984     case CTSF_TABLEPCT_SUM:
2985     case CTSF_UTABLEPCT_SUM:
2986       return true;
2987     }
2988
2989   NOT_REACHED ();
2990 }
2991
2992 static double
2993 ctables_summary_value (const struct ctables_cell *cell,
2994                        union ctables_summary *s,
2995                        const struct ctables_summary_spec *ss)
2996 {
2997   switch (ss->function)
2998     {
2999     case CTSF_COUNT:
3000     case CTSF_ECOUNT:
3001     case CTSF_UCOUNT:
3002       return s->count;
3003
3004     case CTSF_ROW_ID:
3005     case CTSF_COL_ID:
3006     case CTSF_TABLE_ID:
3007     case CTSF_SUBTABLE_ID:
3008     case CTSF_LAYER_ID:
3009     case CTSF_LAYERROW_ID:
3010     case CTSF_LAYERCOL_ID:
3011       return cell->domains[ctables_function_domain (ss->function)]->sequence;
3012
3013     case CTSF_ROWPCT_COUNT:
3014     case CTSF_COLPCT_COUNT:
3015     case CTSF_TABLEPCT_COUNT:
3016     case CTSF_SUBTABLEPCT_COUNT:
3017     case CTSF_LAYERPCT_COUNT:
3018     case CTSF_LAYERROWPCT_COUNT:
3019     case CTSF_LAYERCOLPCT_COUNT:
3020       {
3021         enum ctables_domain_type d = ctables_function_domain (ss->function);
3022         return (cell->domains[d]->e_count
3023                 ? s->count / cell->domains[d]->e_count * 100
3024                 : SYSMIS);
3025       }
3026
3027     case CTSF_UROWPCT_COUNT:
3028     case CTSF_UCOLPCT_COUNT:
3029     case CTSF_UTABLEPCT_COUNT:
3030     case CTSF_USUBTABLEPCT_COUNT:
3031     case CTSF_ULAYERPCT_COUNT:
3032     case CTSF_ULAYERROWPCT_COUNT:
3033     case CTSF_ULAYERCOLPCT_COUNT:
3034       {
3035         enum ctables_domain_type d = ctables_function_domain (ss->function);
3036         return (cell->domains[d]->u_count
3037                 ? s->count / cell->domains[d]->u_count * 100
3038                 : SYSMIS);
3039       }
3040
3041     case CTSF_ROWPCT_VALIDN:
3042     case CTSF_COLPCT_VALIDN:
3043     case CTSF_TABLEPCT_VALIDN:
3044     case CTSF_SUBTABLEPCT_VALIDN:
3045     case CTSF_LAYERPCT_VALIDN:
3046     case CTSF_LAYERROWPCT_VALIDN:
3047     case CTSF_LAYERCOLPCT_VALIDN:
3048       {
3049         enum ctables_domain_type d = ctables_function_domain (ss->function);
3050         return (cell->domains[d]->e_valid
3051                 ? s->count / cell->domains[d]->e_valid * 100
3052                 : SYSMIS);
3053       }
3054
3055     case CTSF_UROWPCT_VALIDN:
3056     case CTSF_UCOLPCT_VALIDN:
3057     case CTSF_UTABLEPCT_VALIDN:
3058     case CTSF_USUBTABLEPCT_VALIDN:
3059     case CTSF_ULAYERPCT_VALIDN:
3060     case CTSF_ULAYERROWPCT_VALIDN:
3061     case CTSF_ULAYERCOLPCT_VALIDN:
3062       {
3063         enum ctables_domain_type d = ctables_function_domain (ss->function);
3064         return (cell->domains[d]->u_valid
3065                 ? s->count / cell->domains[d]->u_valid * 100
3066                 : SYSMIS);
3067       }
3068
3069     case CTSF_ROWPCT_TOTALN:
3070     case CTSF_COLPCT_TOTALN:
3071     case CTSF_TABLEPCT_TOTALN:
3072     case CTSF_SUBTABLEPCT_TOTALN:
3073     case CTSF_LAYERPCT_TOTALN:
3074     case CTSF_LAYERROWPCT_TOTALN:
3075     case CTSF_LAYERCOLPCT_TOTALN:
3076       {
3077         enum ctables_domain_type d = ctables_function_domain (ss->function);
3078         return (cell->domains[d]->e_total
3079                 ? s->count / cell->domains[d]->e_total * 100
3080                 : SYSMIS);
3081       }
3082
3083     case CTSF_UROWPCT_TOTALN:
3084     case CTSF_UCOLPCT_TOTALN:
3085     case CTSF_UTABLEPCT_TOTALN:
3086     case CTSF_USUBTABLEPCT_TOTALN:
3087     case CTSF_ULAYERPCT_TOTALN:
3088     case CTSF_ULAYERROWPCT_TOTALN:
3089     case CTSF_ULAYERCOLPCT_TOTALN:
3090       {
3091         enum ctables_domain_type d = ctables_function_domain (ss->function);
3092         return (cell->domains[d]->u_total
3093                 ? s->count / cell->domains[d]->u_total * 100
3094                 : SYSMIS);
3095       }
3096
3097     case CTSF_MISSING:
3098     case CTSF_UMISSING:
3099     case CSTF_TOTALN:
3100     case CTSF_ETOTALN:
3101     case CSTF_UTOTALN:
3102     case CTSF_VALIDN:
3103     case CTSF_UVALIDN:
3104     case CTSF_EVALIDN:
3105       return s->count;
3106
3107     case CTSF_MAXIMUM:
3108       return s->max;
3109
3110     case CTSF_MINIMUM:
3111       return s->min;
3112
3113     case CTSF_RANGE:
3114       return s->max != SYSMIS && s->min != SYSMIS ? s->max - s->min : SYSMIS;
3115
3116     case CTSF_MEAN:
3117     case CTSF_UMEAN:
3118       {
3119         double mean;
3120         moments1_calculate (s->moments, NULL, &mean, NULL, NULL, NULL);
3121         return mean;
3122       }
3123
3124     case CTSF_SEMEAN:
3125     case CTSF_USEMEAN:
3126       {
3127         double weight, variance;
3128         moments1_calculate (s->moments, &weight, NULL, &variance, NULL, NULL);
3129         return calc_semean (variance, weight);
3130       }
3131
3132     case CTSF_STDDEV:
3133     case CTSF_USTDDEV:
3134       {
3135         double variance;
3136         moments1_calculate (s->moments, NULL, NULL, &variance, NULL, NULL);
3137         return variance != SYSMIS ? sqrt (variance) : SYSMIS;
3138       }
3139
3140     case CTSF_SUM:
3141     case CTSF_USUM:
3142       {
3143         double weight, mean;
3144         moments1_calculate (s->moments, &weight, &mean, NULL, NULL, NULL);
3145         return weight != SYSMIS && mean != SYSMIS ? weight * mean : SYSMIS;
3146       }
3147
3148     case CTSF_VARIANCE:
3149     case CTSF_UVARIANCE:
3150       {
3151         double variance;
3152         moments1_calculate (s->moments, NULL, NULL, &variance, NULL, NULL);
3153         return variance;
3154       }
3155
3156     case CTSF_ROWPCT_SUM:
3157     case CTSF_COLPCT_SUM:
3158     case CTSF_TABLEPCT_SUM:
3159     case CTSF_SUBTABLEPCT_SUM:
3160     case CTSF_LAYERPCT_SUM:
3161     case CTSF_LAYERROWPCT_SUM:
3162     case CTSF_LAYERCOLPCT_SUM:
3163       {
3164         double weight, mean;
3165         moments1_calculate (s->moments, &weight, &mean, NULL, NULL, NULL);
3166         if (weight == SYSMIS || mean == SYSMIS)
3167           return SYSMIS;
3168         enum ctables_domain_type d = ctables_function_domain (ss->function);
3169         double num = weight * mean;
3170         double denom = cell->domains[d]->sums[ss->sum_var_idx].e_sum;
3171         return denom != 0 ? num / denom * 100 : SYSMIS;
3172       }
3173     case CTSF_UROWPCT_SUM:
3174     case CTSF_UCOLPCT_SUM:
3175     case CTSF_UTABLEPCT_SUM:
3176     case CTSF_USUBTABLEPCT_SUM:
3177     case CTSF_ULAYERPCT_SUM:
3178     case CTSF_ULAYERROWPCT_SUM:
3179     case CTSF_ULAYERCOLPCT_SUM:
3180       {
3181         double weight, mean;
3182         moments1_calculate (s->moments, &weight, &mean, NULL, NULL, NULL);
3183         if (weight == SYSMIS || mean == SYSMIS)
3184           return SYSMIS;
3185         enum ctables_domain_type d = ctables_function_domain (ss->function);
3186         double num = weight * mean;
3187         double denom = cell->domains[d]->sums[ss->sum_var_idx].u_sum;
3188         return denom != 0 ? num / denom * 100 : SYSMIS;
3189       }
3190
3191     case CTSF_MEDIAN:
3192     case CTSF_PTILE:
3193     case CTSF_UMEDIAN:
3194     case CTSF_UPTILE:
3195       if (s->writer)
3196         {
3197           struct casereader *reader = casewriter_make_reader (s->writer);
3198           s->writer = NULL;
3199
3200           struct percentile *ptile = percentile_create (
3201             ss->function == CTSF_PTILE ? ss->percentile : 0.5, s->ovalid);
3202           struct order_stats *os = &ptile->parent;
3203           order_stats_accumulate_idx (&os, 1, reader, 1, 0);
3204           s->ovalue = percentile_calculate (ptile, PC_HAVERAGE);
3205           statistic_destroy (&ptile->parent.parent);
3206         }
3207       return s->ovalue;
3208
3209     case CTSF_MODE:
3210     case CTSF_UMODE:
3211       if (s->writer)
3212         {
3213           struct casereader *reader = casewriter_make_reader (s->writer);
3214           s->writer = NULL;
3215
3216           struct mode *mode = mode_create ();
3217           struct order_stats *os = &mode->parent;
3218           order_stats_accumulate_idx (&os, 1, reader, 1, 0);
3219           s->ovalue = mode->mode;
3220           statistic_destroy (&mode->parent.parent);
3221         }
3222       return s->ovalue;
3223     }
3224
3225   NOT_REACHED ();
3226 }
3227
3228 struct ctables_cell_sort_aux
3229   {
3230     const struct ctables_nest *nest;
3231     enum pivot_axis_type a;
3232   };
3233
3234 static int
3235 ctables_cell_compare_3way (const void *a_, const void *b_, const void *aux_)
3236 {
3237   const struct ctables_cell_sort_aux *aux = aux_;
3238   struct ctables_cell *const *ap = a_;
3239   struct ctables_cell *const *bp = b_;
3240   const struct ctables_cell *a = *ap;
3241   const struct ctables_cell *b = *bp;
3242
3243   const struct ctables_nest *nest = aux->nest;
3244   for (size_t i = 0; i < nest->n; i++)
3245     if (i != nest->scale_idx)
3246       {
3247         const struct variable *var = nest->vars[i];
3248         const struct ctables_cell_value *a_cv = &a->axes[aux->a].cvs[i];
3249         const struct ctables_cell_value *b_cv = &b->axes[aux->a].cvs[i];
3250         if (a_cv->category != b_cv->category)
3251           return a_cv->category > b_cv->category ? 1 : -1;
3252
3253         const union value *a_val = &a_cv->value;
3254         const union value *b_val = &b_cv->value;
3255         switch (a_cv->category->type)
3256           {
3257           case CCT_NUMBER:
3258           case CCT_STRING:
3259           case CCT_SUBTOTAL:
3260           case CCT_TOTAL:
3261           case CCT_POSTCOMPUTE:
3262           case CCT_EXCLUDED_MISSING:
3263             /* Must be equal. */
3264             continue;
3265
3266           case CCT_NRANGE:
3267           case CCT_SRANGE:
3268           case CCT_MISSING:
3269           case CCT_OTHERNM:
3270             {
3271               int cmp = value_compare_3way (a_val, b_val, var_get_width (var));
3272               if (cmp)
3273                 return cmp;
3274             }
3275             break;
3276
3277           case CCT_VALUE:
3278             {
3279               int cmp = value_compare_3way (a_val, b_val, var_get_width (var));
3280               if (cmp)
3281                 return a_cv->category->sort_ascending ? cmp : -cmp;
3282             }
3283             break;
3284
3285           case CCT_LABEL:
3286             {
3287               const char *a_label = var_lookup_value_label (var, a_val);
3288               const char *b_label = var_lookup_value_label (var, b_val);
3289               int cmp;
3290               if (a_label)
3291                 {
3292                   if (!b_label)
3293                     return -1;
3294                   cmp = strcmp (a_label, b_label);
3295                 }
3296               else
3297                 {
3298                   if (b_label)
3299                     return 1;
3300                   cmp = value_compare_3way (a_val, b_val, var_get_width (var));
3301                 }
3302               if (cmp)
3303                 return a_cv->category->sort_ascending ? cmp : -cmp;
3304             }
3305             break;
3306
3307           case CCT_FUNCTION:
3308             NOT_REACHED ();
3309           }
3310       }
3311   return 0;
3312 }
3313
3314 static int
3315 ctables_cell_compare_leaf_3way (const void *a_, const void *b_,
3316                                 const void *aux UNUSED)
3317 {
3318   struct ctables_cell *const *ap = a_;
3319   struct ctables_cell *const *bp = b_;
3320   const struct ctables_cell *a = *ap;
3321   const struct ctables_cell *b = *bp;
3322
3323   for (enum pivot_axis_type axis = 0; axis < PIVOT_N_AXES; axis++)
3324     {
3325       int al = a->axes[axis].leaf;
3326       int bl = b->axes[axis].leaf;
3327       if (al != bl)
3328         return al > bl ? 1 : -1;
3329     }
3330   return 0;
3331 }
3332
3333 /* Algorithm:
3334
3335    For each row:
3336        For each ctables_table:
3337            For each combination of row vars:
3338                For each combination of column vars:
3339                    For each combination of layer vars:
3340                        Add entry
3341    Make a table of row values:
3342        Sort entries by row values
3343        Assign a 0-based index to each actual value
3344        Construct a dimension
3345    Make a table of column values
3346    Make a table of layer values
3347    For each entry:
3348        Fill the table entry using the indexes from before.
3349  */
3350
3351 static struct ctables_domain *
3352 ctables_domain_insert (struct ctables_section *s, struct ctables_cell *cell,
3353                        enum ctables_domain_type domain)
3354 {
3355   size_t hash = 0;
3356   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3357     {
3358       const struct ctables_nest *nest = s->nests[a];
3359       for (size_t i = 0; i < nest->n_domains[domain]; i++)
3360         {
3361           size_t v_idx = nest->domains[domain][i];
3362           struct ctables_cell_value *cv = &cell->axes[a].cvs[v_idx];
3363           hash = hash_pointer (cv->category, hash);
3364           if (cv->category->type != CCT_TOTAL
3365               && cv->category->type != CCT_SUBTOTAL
3366               && cv->category->type != CCT_POSTCOMPUTE)
3367             hash = value_hash (&cv->value,
3368                                var_get_width (nest->vars[v_idx]), hash);
3369         }
3370     }
3371
3372   struct ctables_domain *d;
3373   HMAP_FOR_EACH_WITH_HASH (d, struct ctables_domain, node, hash, &s->domains[domain])
3374     {
3375       const struct ctables_cell *df = d->example;
3376       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3377         {
3378           const struct ctables_nest *nest = s->nests[a];
3379           for (size_t i = 0; i < nest->n_domains[domain]; i++)
3380             {
3381               size_t v_idx = nest->domains[domain][i];
3382               struct ctables_cell_value *cv1 = &df->axes[a].cvs[v_idx];
3383               struct ctables_cell_value *cv2 = &cell->axes[a].cvs[v_idx];
3384               if (cv1->category != cv2->category
3385                   || (cv1->category->type != CCT_TOTAL
3386                       && cv1->category->type != CCT_SUBTOTAL
3387                       && cv1->category->type != CCT_POSTCOMPUTE
3388                       && !value_equal (&cv1->value, &cv2->value,
3389                                        var_get_width (nest->vars[v_idx]))))
3390                 goto not_equal;
3391             }
3392         }
3393       return d;
3394
3395     not_equal: ;
3396     }
3397
3398   struct ctables_sum *sums = (s->table->n_sum_vars
3399                               ? xzalloc (s->table->n_sum_vars * sizeof *sums)
3400                               : NULL);
3401
3402   d = xmalloc (sizeof *d);
3403   *d = (struct ctables_domain) { .example = cell, .sums = sums };
3404   hmap_insert (&s->domains[domain], &d->node, hash);
3405   return d;
3406 }
3407
3408 static struct substring
3409 rtrim_value (const union value *v, const struct variable *var)
3410 {
3411   struct substring s = ss_buffer (CHAR_CAST (char *, v->s),
3412                                   var_get_width (var));
3413   ss_rtrim (&s, ss_cstr (" "));
3414   return s;
3415 }
3416
3417 static bool
3418 in_string_range (const union value *v, const struct variable *var,
3419                  const struct substring *srange)
3420 {
3421   struct substring s = rtrim_value (v, var);
3422   return ((!srange[0].string || ss_compare (s, srange[0]) >= 0)
3423           && (!srange[1].string || ss_compare (s, srange[1]) <= 0));
3424 }
3425
3426 static const struct ctables_category *
3427 ctables_categories_match (const struct ctables_categories *c,
3428                           const union value *v, const struct variable *var)
3429 {
3430   if (var_is_numeric (var) && v->f == SYSMIS)
3431     return NULL;
3432
3433   const struct ctables_category *othernm = NULL;
3434   for (size_t i = c->n_cats; i-- > 0; )
3435     {
3436       const struct ctables_category *cat = &c->cats[i];
3437       switch (cat->type)
3438         {
3439         case CCT_NUMBER:
3440           if (cat->number == v->f)
3441             return cat;
3442           break;
3443
3444         case CCT_STRING:
3445           if (ss_equals (cat->string, rtrim_value (v, var)))
3446             return cat;
3447           break;
3448
3449         case CCT_NRANGE:
3450           if ((cat->nrange[0] == -DBL_MAX || v->f >= cat->nrange[0])
3451               && (cat->nrange[1] == DBL_MAX || v->f <= cat->nrange[1]))
3452             return cat;
3453           break;
3454
3455         case CCT_SRANGE:
3456           if (in_string_range (v, var, cat->srange))
3457             return cat;
3458           break;
3459
3460         case CCT_MISSING:
3461           if (var_is_value_missing (var, v))
3462             return cat;
3463           break;
3464
3465         case CCT_POSTCOMPUTE:
3466           break;
3467
3468         case CCT_OTHERNM:
3469           if (!othernm)
3470             othernm = cat;
3471           break;
3472
3473         case CCT_SUBTOTAL:
3474         case CCT_TOTAL:
3475           break;
3476
3477         case CCT_VALUE:
3478         case CCT_LABEL:
3479         case CCT_FUNCTION:
3480           return (cat->include_missing || !var_is_value_missing (var, v) ? cat
3481                   : NULL);
3482
3483         case CCT_EXCLUDED_MISSING:
3484           break;
3485         }
3486     }
3487
3488   return var_is_value_missing (var, v) ? NULL : othernm;
3489 }
3490
3491 static const struct ctables_category *
3492 ctables_categories_total (const struct ctables_categories *c)
3493 {
3494   const struct ctables_category *first = &c->cats[0];
3495   const struct ctables_category *last = &c->cats[c->n_cats - 1];
3496   return (first->type == CCT_TOTAL ? first
3497           : last->type == CCT_TOTAL ? last
3498           : NULL);
3499 }
3500
3501 static struct ctables_cell *
3502 ctables_cell_insert__ (struct ctables_section *s, const struct ccase *c,
3503                        const struct ctables_category *cats[PIVOT_N_AXES][10])
3504 {
3505   size_t hash = 0;
3506   enum ctables_summary_variant sv = CSV_CELL;
3507   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3508     {
3509       const struct ctables_nest *nest = s->nests[a];
3510       for (size_t i = 0; i < nest->n; i++)
3511         if (i != nest->scale_idx)
3512           {
3513             hash = hash_pointer (cats[a][i], hash);
3514             if (cats[a][i]->type != CCT_TOTAL
3515                 && cats[a][i]->type != CCT_SUBTOTAL
3516                 && cats[a][i]->type != CCT_POSTCOMPUTE)
3517               hash = value_hash (case_data (c, nest->vars[i]),
3518                                  var_get_width (nest->vars[i]), hash);
3519             else
3520               sv = CSV_TOTAL;
3521           }
3522     }
3523
3524   struct ctables_cell *cell;
3525   HMAP_FOR_EACH_WITH_HASH (cell, struct ctables_cell, node, hash, &s->cells)
3526     {
3527       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3528         {
3529           const struct ctables_nest *nest = s->nests[a];
3530           for (size_t i = 0; i < nest->n; i++)
3531             if (i != nest->scale_idx
3532                 && (cats[a][i] != cell->axes[a].cvs[i].category
3533                     || (cats[a][i]->type != CCT_TOTAL
3534                         && cats[a][i]->type != CCT_SUBTOTAL
3535                         && cats[a][i]->type != CCT_POSTCOMPUTE
3536                         && !value_equal (case_data (c, nest->vars[i]),
3537                                          &cell->axes[a].cvs[i].value,
3538                                          var_get_width (nest->vars[i])))))
3539                 goto not_equal;
3540         }
3541
3542       return cell;
3543
3544     not_equal: ;
3545     }
3546
3547   cell = xmalloc (sizeof *cell);
3548   cell->hide = false;
3549   cell->sv = sv;
3550   cell->omit_domains = 0;
3551   cell->postcompute = false;
3552   //struct string name = DS_EMPTY_INITIALIZER;
3553   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3554     {
3555       const struct ctables_nest *nest = s->nests[a];
3556       cell->axes[a].cvs = (nest->n
3557                            ? xnmalloc (nest->n, sizeof *cell->axes[a].cvs)
3558                            : NULL);
3559       for (size_t i = 0; i < nest->n; i++)
3560         {
3561           const struct ctables_category *cat = cats[a][i];
3562           const struct variable *var = nest->vars[i];
3563           const union value *value = case_data (c, var);
3564           if (i != nest->scale_idx)
3565             {
3566               const struct ctables_category *subtotal = cat->subtotal;
3567               if (cat->hide || (subtotal && subtotal->hide_subcategories))
3568                 cell->hide = true;
3569
3570               if (cat->type == CCT_TOTAL
3571                   || cat->type == CCT_SUBTOTAL
3572                   || cat->type == CCT_POSTCOMPUTE)
3573                 {
3574                   /* XXX these should be more encompassing I think.*/
3575
3576                   switch (a)
3577                     {
3578                     case PIVOT_AXIS_COLUMN:
3579                       cell->omit_domains |= ((1u << CTDT_TABLE) |
3580                                              (1u << CTDT_LAYER) |
3581                                              (1u << CTDT_LAYERCOL) |
3582                                              (1u << CTDT_SUBTABLE) |
3583                                              (1u << CTDT_COL));
3584                       break;
3585                     case PIVOT_AXIS_ROW:
3586                       cell->omit_domains |= ((1u << CTDT_TABLE) |
3587                                              (1u << CTDT_LAYER) |
3588                                              (1u << CTDT_LAYERROW) |
3589                                              (1u << CTDT_SUBTABLE) |
3590                                              (1u << CTDT_ROW));
3591                       break;
3592                     case PIVOT_AXIS_LAYER:
3593                       cell->omit_domains |= ((1u << CTDT_TABLE) |
3594                                              (1u << CTDT_LAYER));
3595                       break;
3596                     }
3597                 }
3598               if (cat->type == CCT_POSTCOMPUTE)
3599                 cell->postcompute = true;
3600             }
3601
3602           cell->axes[a].cvs[i].category = cat;
3603           value_clone (&cell->axes[a].cvs[i].value, value, var_get_width (var));
3604
3605 #if 0
3606           if (i != nest->scale_idx)
3607             {
3608               if (!ds_is_empty (&name))
3609                 ds_put_cstr (&name, ", ");
3610               char *value_s = data_out (value, var_get_encoding (var),
3611                                         var_get_print_format (var),
3612                                         settings_get_fmt_settings ());
3613               if (cat->type == CCT_TOTAL
3614                   || cat->type == CCT_SUBTOTAL
3615                   || cat->type == CCT_POSTCOMPUTE)
3616                 ds_put_format (&name, "%s=total", var_get_name (var));
3617               else
3618                 ds_put_format (&name, "%s=%s", var_get_name (var),
3619                                value_s + strspn (value_s, " "));
3620               free (value_s);
3621             }
3622 #endif
3623         }
3624     }
3625   //cell->name = ds_steal_cstr (&name);
3626
3627   const struct ctables_nest *ss = s->nests[s->table->summary_axis];
3628   const struct ctables_summary_spec_set *specs = &ss->specs[cell->sv];
3629   cell->summaries = xmalloc (specs->n * sizeof *cell->summaries);
3630   for (size_t i = 0; i < specs->n; i++)
3631     ctables_summary_init (&cell->summaries[i], &specs->specs[i]);
3632   for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
3633     cell->domains[dt] = ctables_domain_insert (s, cell, dt);
3634   hmap_insert (&s->cells, &cell->node, hash);
3635   return cell;
3636 }
3637
3638 static bool
3639 is_scale_missing (const struct ctables_summary_spec_set *specs,
3640                   const struct ccase *c)
3641 {
3642   if (!specs->is_scale)
3643     return false;
3644
3645   if (var_is_num_missing (specs->var, case_num (c, specs->var)))
3646     return true;
3647
3648   for (size_t i = 0; i < specs->n_listwise_vars; i++)
3649     {
3650       const struct variable *var = specs->listwise_vars[i];
3651       if (var_is_num_missing (var, case_num (c, var)))
3652         return true;
3653     }
3654
3655   return false;
3656 }
3657
3658 static void
3659 ctables_cell_add__ (struct ctables_section *s, const struct ccase *c,
3660                     const struct ctables_category *cats[PIVOT_N_AXES][10],
3661                     bool is_missing, bool excluded_missing,
3662                     double d_weight, double e_weight)
3663 {
3664   struct ctables_cell *cell = ctables_cell_insert__ (s, c, cats);
3665   const struct ctables_nest *ss = s->nests[s->table->summary_axis];
3666
3667   const struct ctables_summary_spec_set *specs = &ss->specs[cell->sv];
3668
3669   bool scale_missing = is_scale_missing (specs, c);
3670   for (size_t i = 0; i < specs->n; i++)
3671     ctables_summary_add (&cell->summaries[i], &specs->specs[i],
3672                          specs->var, case_data (c, specs->var), specs->is_scale,
3673                          scale_missing, is_missing, excluded_missing,
3674                          d_weight, e_weight);
3675   for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
3676     if (!(cell->omit_domains && (1u << dt)))
3677       {
3678         struct ctables_domain *d = cell->domains[dt];
3679         d->d_total += d_weight;
3680         d->e_total += e_weight;
3681         d->u_total += 1.0;
3682         if (!excluded_missing)
3683           {
3684             d->d_count += d_weight;
3685             d->e_count += e_weight;
3686             d->u_count += 1.0;
3687           }
3688         if (!is_missing)
3689           {
3690             d->d_valid += d_weight;
3691             d->e_valid += e_weight;
3692             d->u_count += 1.0;
3693
3694             for (size_t i = 0; i < s->table->n_sum_vars; i++)
3695               {
3696                 /* XXX listwise_missing??? */
3697                 const struct variable *var = s->table->sum_vars[i];
3698                 double addend = case_num (c, var);
3699                 if (!var_is_num_missing (var, addend))
3700                   {
3701                     struct ctables_sum *sum = &d->sums[i];
3702                     sum->e_sum += addend * e_weight;
3703                     sum->u_sum += addend;
3704                   }
3705               }
3706           }
3707       }
3708 }
3709
3710 static void
3711 recurse_totals (struct ctables_section *s, const struct ccase *c,
3712                 const struct ctables_category *cats[PIVOT_N_AXES][10],
3713                 bool is_missing, bool excluded_missing,
3714                 double d_weight, double e_weight,
3715                 enum pivot_axis_type start_axis, size_t start_nest)
3716 {
3717   for (enum pivot_axis_type a = start_axis; a < PIVOT_N_AXES; a++)
3718     {
3719       const struct ctables_nest *nest = s->nests[a];
3720       for (size_t i = start_nest; i < nest->n; i++)
3721         {
3722           if (i == nest->scale_idx)
3723             continue;
3724
3725           const struct variable *var = nest->vars[i];
3726
3727           const struct ctables_category *total = ctables_categories_total (
3728             s->table->categories[var_get_dict_index (var)]);
3729           if (total)
3730             {
3731               const struct ctables_category *save = cats[a][i];
3732               cats[a][i] = total;
3733               ctables_cell_add__ (s, c, cats, is_missing, excluded_missing,
3734                                   d_weight, e_weight);
3735               recurse_totals (s, c, cats, is_missing, excluded_missing,
3736                               d_weight, e_weight, a, i + 1);
3737               cats[a][i] = save;
3738             }
3739         }
3740       start_nest = 0;
3741     }
3742 }
3743
3744 static void
3745 recurse_subtotals (struct ctables_section *s, const struct ccase *c,
3746                    const struct ctables_category *cats[PIVOT_N_AXES][10],
3747                    bool is_missing, bool excluded_missing,
3748                    double d_weight, double e_weight,
3749                    enum pivot_axis_type start_axis, size_t start_nest)
3750 {
3751   for (enum pivot_axis_type a = start_axis; a < PIVOT_N_AXES; a++)
3752     {
3753       const struct ctables_nest *nest = s->nests[a];
3754       for (size_t i = start_nest; i < nest->n; i++)
3755         {
3756           if (i == nest->scale_idx)
3757             continue;
3758
3759           const struct ctables_category *save = cats[a][i];
3760           if (save->subtotal)
3761             {
3762               cats[a][i] = save->subtotal;
3763               ctables_cell_add__ (s, c, cats, is_missing, excluded_missing,
3764                                   d_weight, e_weight);
3765               recurse_subtotals (s, c, cats, is_missing, excluded_missing,
3766                                  d_weight, e_weight, a, i + 1);
3767               cats[a][i] = save;
3768             }
3769         }
3770       start_nest = 0;
3771     }
3772 }
3773
3774 static void
3775 ctables_add_occurrence (const struct variable *var,
3776                         const union value *value,
3777                         struct hmap *occurrences)
3778 {
3779   int width = var_get_width (var);
3780   unsigned int hash = value_hash (value, width, 0);
3781
3782   struct ctables_occurrence *o;
3783   HMAP_FOR_EACH_WITH_HASH (o, struct ctables_occurrence, node, hash,
3784                            occurrences)
3785     if (value_equal (value, &o->value, width))
3786       return;
3787
3788   o = xmalloc (sizeof *o);
3789   value_clone (&o->value, value, width);
3790   hmap_insert (occurrences, &o->node, hash);
3791 }
3792
3793 static void
3794 ctables_cell_insert (struct ctables_section *s,
3795                      const struct ccase *c,
3796                      double d_weight, double e_weight)
3797 {
3798   const struct ctables_category *cats[PIVOT_N_AXES][10]; /* XXX */
3799
3800   /* Does at least one categorical variable have a missing value in an included
3801      or excluded category? */
3802   bool is_missing = false;
3803
3804   /* Does at least one categorical variable have a missing value in an excluded
3805      category? */
3806   bool excluded_missing = false;
3807
3808   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3809     {
3810       const struct ctables_nest *nest = s->nests[a];
3811       for (size_t i = 0; i < nest->n; i++)
3812         {
3813           if (i == nest->scale_idx)
3814             continue;
3815
3816           const struct variable *var = nest->vars[i];
3817           const union value *value = case_data (c, var);
3818
3819           bool var_missing = var_is_value_missing (var, value) != 0;
3820           if (var_missing)
3821             is_missing = true;
3822
3823           cats[a][i] = ctables_categories_match (
3824             s->table->categories[var_get_dict_index (var)], value, var);
3825           if (!cats[a][i])
3826             {
3827               if (!var_missing)
3828                 return;
3829
3830               static const struct ctables_category cct_excluded_missing = {
3831                 .type = CCT_EXCLUDED_MISSING,
3832                 .hide = true,
3833               };
3834               cats[a][i] = &cct_excluded_missing;
3835               excluded_missing = true;
3836             }
3837         }
3838     }
3839
3840   if (!excluded_missing)
3841     for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
3842       {
3843         const struct ctables_nest *nest = s->nests[a];
3844         for (size_t i = 0; i < nest->n; i++)
3845           if (i != nest->scale_idx)
3846             {
3847               const struct variable *var = nest->vars[i];
3848               const union value *value = case_data (c, var);
3849               ctables_add_occurrence (var, value, &s->occurrences[a][i]);
3850             }
3851       }
3852
3853   ctables_cell_add__ (s, c, cats, is_missing, excluded_missing,
3854                       d_weight, e_weight);
3855
3856   //if (!excluded_missing)
3857     {
3858       recurse_totals (s, c, cats, is_missing, excluded_missing,
3859                       d_weight, e_weight, 0, 0);
3860       recurse_subtotals (s, c, cats, is_missing, excluded_missing,
3861                          d_weight, e_weight, 0, 0);
3862     }
3863 }
3864
3865 struct merge_item
3866   {
3867     const struct ctables_summary_spec_set *set;
3868     size_t ofs;
3869   };
3870
3871 static int
3872 merge_item_compare_3way (const struct merge_item *a, const struct merge_item *b)
3873 {
3874   const struct ctables_summary_spec *as = &a->set->specs[a->ofs];
3875   const struct ctables_summary_spec *bs = &b->set->specs[b->ofs];
3876   if (as->function != bs->function)
3877     return as->function > bs->function ? 1 : -1;
3878   else if (as->percentile != bs->percentile)
3879     return as->percentile < bs->percentile ? 1 : -1;
3880
3881   const char *as_label = as->label ? as->label : "";
3882   const char *bs_label = bs->label ? bs->label : "";
3883   return strcmp (as_label, bs_label);
3884 }
3885
3886 static struct pivot_value *
3887 ctables_category_create_label__ (const struct ctables_category *cat,
3888                                  const struct variable *var,
3889                                  const union value *value)
3890 {
3891   return (cat->type == CCT_TOTAL || cat->type == CCT_SUBTOTAL
3892           ? pivot_value_new_user_text (cat->total_label, SIZE_MAX)
3893           : pivot_value_new_var_value (var, value));
3894 }
3895
3896 static struct pivot_value *
3897 ctables_postcompute_label (const struct ctables_categories *cats,
3898                            const struct ctables_category *cat,
3899                            const struct variable *var,
3900                            const union value *value)
3901 {
3902   struct substring in = ss_cstr (cat->pc->label);
3903   struct substring target = ss_cstr (")LABEL[");
3904
3905   struct string out = DS_EMPTY_INITIALIZER;
3906   for (;;)
3907     {
3908       size_t chunk = ss_find_substring (in, target);
3909       if (chunk == SIZE_MAX)
3910         {
3911           if (ds_is_empty (&out))
3912             return pivot_value_new_user_text (in.string, in.length);
3913           else
3914             {
3915               ds_put_substring (&out, in);
3916               return pivot_value_new_user_text_nocopy (ds_steal_cstr (&out));
3917             }
3918         }
3919
3920       ds_put_substring (&out, ss_head (in, chunk));
3921       ss_advance (&in, chunk + target.length);
3922
3923       struct substring idx_s;
3924       if (!ss_get_until (&in, ']', &idx_s))
3925         goto error;
3926       char *tail;
3927       long int idx = strtol (idx_s.string, &tail, 10);
3928       if (idx < 1 || idx > cats->n_cats || tail != ss_end (idx_s))
3929         goto error;
3930
3931       struct ctables_category *cat2 = &cats->cats[idx - 1];
3932       struct pivot_value *label2
3933         = ctables_category_create_label__ (cat2, var, value);
3934       char *label2_s = pivot_value_to_string_defaults (label2);
3935       ds_put_cstr (&out, label2_s);
3936       free (label2_s);
3937       pivot_value_destroy (label2);
3938     }
3939
3940 error:
3941   ds_destroy (&out);
3942   return pivot_value_new_user_text (cat->pc->label, SIZE_MAX);
3943 }
3944
3945 static struct pivot_value *
3946 ctables_category_create_label (const struct ctables_categories *cats,
3947                                const struct ctables_category *cat,
3948                                const struct variable *var,
3949                                const union value *value)
3950 {
3951   return (cat->type == CCT_POSTCOMPUTE && cat->pc->label
3952           ? ctables_postcompute_label (cats, cat, var, value)
3953           : ctables_category_create_label__ (cat, var, value));
3954 }
3955
3956 static struct ctables_value *
3957 ctables_value_find__ (struct ctables_table *t, const union value *value,
3958                       int width, unsigned int hash)
3959 {
3960   struct ctables_value *clv;
3961   HMAP_FOR_EACH_WITH_HASH (clv, struct ctables_value, node,
3962                            hash, &t->clabels_values_map)
3963     if (value_equal (value, &clv->value, width))
3964       return clv;
3965   return NULL;
3966 }
3967
3968 static void
3969 ctables_value_insert (struct ctables_table *t, const union value *value,
3970                       int width)
3971 {
3972   unsigned int hash = value_hash (value, width, 0);
3973   struct ctables_value *clv = ctables_value_find__ (t, value, width, hash);
3974   if (!clv)
3975     {
3976       clv = xmalloc (sizeof *clv);
3977       value_clone (&clv->value, value, width);
3978       hmap_insert (&t->clabels_values_map, &clv->node, hash);
3979     }
3980 }
3981
3982 static struct ctables_value *
3983 ctables_value_find (struct ctables_table *t,
3984                     const union value *value, int width)
3985 {
3986   return ctables_value_find__ (t, value, width,
3987                                value_hash (value, width, 0));
3988 }
3989
3990 static void
3991 ctables_table_add_section (struct ctables_table *t, enum pivot_axis_type a,
3992                            size_t ix[PIVOT_N_AXES])
3993 {
3994   if (a < PIVOT_N_AXES)
3995     {
3996       size_t limit = MAX (t->stacks[a].n, 1);
3997       for (ix[a] = 0; ix[a] < limit; ix[a]++)
3998         ctables_table_add_section (t, a + 1, ix);
3999     }
4000   else
4001     {
4002       struct ctables_section *s = &t->sections[t->n_sections++];
4003       *s = (struct ctables_section) {
4004         .table = t,
4005         .cells = HMAP_INITIALIZER (s->cells),
4006       };
4007       for (a = 0; a < PIVOT_N_AXES; a++)
4008         if (t->stacks[a].n)
4009           {
4010             struct ctables_nest *nest = &t->stacks[a].nests[ix[a]];
4011             s->nests[a] = nest;
4012             s->occurrences[a] = xnmalloc (nest->n, sizeof *s->occurrences[a]);
4013             for (size_t i = 0; i < nest->n; i++)
4014               hmap_init (&s->occurrences[a][i]);
4015         }
4016       for (size_t i = 0; i < N_CTDTS; i++)
4017         hmap_init (&s->domains[i]);
4018     }
4019 }
4020
4021 static double
4022 ctpo_add (double a, double b)
4023 {
4024   return a + b;
4025 }
4026
4027 static double
4028 ctpo_sub (double a, double b)
4029 {
4030   return a - b;
4031 }
4032
4033 static double
4034 ctpo_mul (double a, double b)
4035 {
4036   return a * b;
4037 }
4038
4039 static double
4040 ctpo_div (double a, double b)
4041 {
4042   return b ? a / b : SYSMIS;
4043 }
4044
4045 static double
4046 ctpo_pow (double a, double b)
4047 {
4048   int save_errno = errno;
4049   errno = 0;
4050   double result = pow (a, b);
4051   if (errno)
4052     result = SYSMIS;
4053   errno = save_errno;
4054   return result;
4055 }
4056
4057 static double
4058 ctpo_neg (double a, double b UNUSED)
4059 {
4060   return -a;
4061 }
4062
4063 struct ctables_pcexpr_evaluate_ctx
4064   {
4065     const struct ctables_cell *cell;
4066     const struct ctables_section *section;
4067     const struct ctables_categories *cats;
4068     enum pivot_axis_type pc_a;
4069     size_t pc_a_idx;
4070     size_t summary_idx;
4071     enum fmt_type parse_format;
4072   };
4073
4074 static double ctables_pcexpr_evaluate (
4075   const struct ctables_pcexpr_evaluate_ctx *, const struct ctables_pcexpr *);
4076
4077 static double
4078 ctables_pcexpr_evaluate_nonterminal (
4079   const struct ctables_pcexpr_evaluate_ctx *ctx,
4080   const struct ctables_pcexpr *e, size_t n_args,
4081   double evaluate (double, double))
4082 {
4083   double args[2] = { 0, 0 };
4084   for (size_t i = 0; i < n_args; i++)
4085     {
4086       args[i] = ctables_pcexpr_evaluate (ctx, e->subs[i]);
4087       if (!isfinite (args[i]) || args[i] == SYSMIS)
4088         return SYSMIS;
4089     }
4090   return evaluate (args[0], args[1]);
4091 }
4092
4093 static double
4094 ctables_pcexpr_evaluate_category (const struct ctables_pcexpr_evaluate_ctx *ctx,
4095                                   const struct ctables_cell_value *pc_cv)
4096 {
4097   const struct ctables_section *s = ctx->section;
4098
4099   size_t hash = 0;
4100   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
4101     {
4102       const struct ctables_nest *nest = s->nests[a];
4103       for (size_t i = 0; i < nest->n; i++)
4104         if (i != nest->scale_idx)
4105           {
4106             const struct ctables_cell_value *cv
4107               = (a == ctx->pc_a && i == ctx->pc_a_idx ? pc_cv
4108                  : &ctx->cell->axes[a].cvs[i]);
4109             hash = hash_pointer (cv->category, hash);
4110             if (cv->category->type != CCT_TOTAL
4111                 && cv->category->type != CCT_SUBTOTAL
4112                 && cv->category->type != CCT_POSTCOMPUTE)
4113               hash = value_hash (&cv->value,
4114                                  var_get_width (nest->vars[i]), hash);
4115           }
4116     }
4117
4118   struct ctables_cell *tc;
4119   HMAP_FOR_EACH_WITH_HASH (tc, struct ctables_cell, node, hash, &s->cells)
4120     {
4121       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
4122         {
4123           const struct ctables_nest *nest = s->nests[a];
4124           for (size_t i = 0; i < nest->n; i++)
4125             if (i != nest->scale_idx)
4126               {
4127                 const struct ctables_cell_value *p_cv
4128                   = (a == ctx->pc_a && i == ctx->pc_a_idx ? pc_cv
4129                      : &ctx->cell->axes[a].cvs[i]);
4130                 const struct ctables_cell_value *t_cv = &tc->axes[a].cvs[i];
4131                 if (p_cv->category != t_cv->category
4132                     || (p_cv->category->type != CCT_TOTAL
4133                         && p_cv->category->type != CCT_SUBTOTAL
4134                         && p_cv->category->type != CCT_POSTCOMPUTE
4135                         && !value_equal (&p_cv->value,
4136                                          &t_cv->value,
4137                                          var_get_width (nest->vars[i]))))
4138                   goto not_equal;
4139               }
4140         }
4141
4142       goto found;
4143
4144     not_equal: ;
4145     }
4146   return 0;
4147
4148 found: ;
4149   const struct ctables_table *t = s->table;
4150   const struct ctables_nest *specs_nest = s->nests[t->summary_axis];
4151   const struct ctables_summary_spec_set *specs = &specs_nest->specs[tc->sv];
4152   return ctables_summary_value (tc, &tc->summaries[ctx->summary_idx],
4153                                 &specs->specs[ctx->summary_idx]);
4154 }
4155
4156 static double
4157 ctables_pcexpr_evaluate (const struct ctables_pcexpr_evaluate_ctx *ctx,
4158                          const struct ctables_pcexpr *e)
4159 {
4160   switch (e->op)
4161     {
4162     case CTPO_CONSTANT:
4163       return e->number;
4164
4165     case CTPO_CAT_NRANGE:
4166     case CTPO_CAT_SRANGE:
4167       {
4168         struct ctables_cell_value cv = {
4169           .category = ctables_find_category_for_postcompute (ctx->section->table->ctables->dict, ctx->cats, ctx->parse_format, e)
4170         };
4171         assert (cv.category != NULL);
4172
4173         struct hmap *occurrences = &ctx->section->occurrences[ctx->pc_a][ctx->pc_a_idx];
4174         const struct ctables_occurrence *o;
4175
4176         double sum = 0.0;
4177         const struct variable *var = ctx->section->nests[ctx->pc_a]->vars[ctx->pc_a_idx];
4178         HMAP_FOR_EACH (o, struct ctables_occurrence, node, occurrences)
4179           if (ctables_categories_match (ctx->cats, &o->value, var) == cv.category)
4180             {
4181               cv.value = o->value;
4182               sum += ctables_pcexpr_evaluate_category (ctx, &cv);
4183             }
4184         return sum;
4185       }
4186
4187     case CTPO_CAT_NUMBER:
4188     case CTPO_CAT_MISSING:
4189     case CTPO_CAT_OTHERNM:
4190     case CTPO_CAT_SUBTOTAL:
4191     case CTPO_CAT_TOTAL:
4192       {
4193         struct ctables_cell_value cv = {
4194           .category = ctables_find_category_for_postcompute (ctx->section->table->ctables->dict, ctx->cats, ctx->parse_format, e),
4195           .value = { .f = e->number },
4196         };
4197         assert (cv.category != NULL);
4198         return ctables_pcexpr_evaluate_category (ctx, &cv);
4199       }
4200
4201     case CTPO_CAT_STRING:
4202       {
4203         int width = var_get_width (ctx->section->nests[ctx->pc_a]->vars[ctx->pc_a_idx]);
4204         char *s = NULL;
4205         if (width > e->string.length)
4206           {
4207             s = xmalloc (width);
4208             buf_copy_rpad (s, width, e->string.string, e->string.length, ' ');
4209           }
4210         struct ctables_cell_value cv = {
4211           .category = ctables_find_category_for_postcompute (ctx->section->table->ctables->dict, ctx->cats, ctx->parse_format, e),
4212           .value = { .s = CHAR_CAST (uint8_t *, s ? s : e->string.string) },
4213         };
4214         assert (cv.category != NULL);
4215         double retval = ctables_pcexpr_evaluate_category (ctx, &cv);
4216         free (s);
4217         return retval;
4218       }
4219
4220     case CTPO_ADD:
4221       return ctables_pcexpr_evaluate_nonterminal (ctx, e, 2, ctpo_add);
4222
4223     case CTPO_SUB:
4224       return ctables_pcexpr_evaluate_nonterminal (ctx, e, 2, ctpo_sub);
4225
4226     case CTPO_MUL:
4227       return ctables_pcexpr_evaluate_nonterminal (ctx, e, 2, ctpo_mul);
4228
4229     case CTPO_DIV:
4230       return ctables_pcexpr_evaluate_nonterminal (ctx, e, 2, ctpo_div);
4231
4232     case CTPO_POW:
4233       return ctables_pcexpr_evaluate_nonterminal (ctx, e, 2, ctpo_pow);
4234
4235     case CTPO_NEG:
4236       return ctables_pcexpr_evaluate_nonterminal (ctx, e, 1, ctpo_neg);
4237     }
4238
4239   NOT_REACHED ();
4240 }
4241
4242 static const struct ctables_category *
4243 ctables_cell_postcompute (const struct ctables_section *s,
4244                           const struct ctables_cell *cell,
4245                           enum pivot_axis_type *pc_a_p,
4246                           size_t *pc_a_idx_p)
4247 {
4248   assert (cell->postcompute);
4249   const struct ctables_category *pc_cat = NULL;
4250   for (enum pivot_axis_type pc_a = 0; pc_a < PIVOT_N_AXES; pc_a++)
4251     for (size_t pc_a_idx = 0; pc_a_idx < s->nests[pc_a]->n; pc_a_idx++)
4252       {
4253         const struct ctables_cell_value *cv = &cell->axes[pc_a].cvs[pc_a_idx];
4254         if (cv->category->type == CCT_POSTCOMPUTE)
4255           {
4256             if (pc_cat)
4257               {
4258                 /* Multiple postcomputes cross each other.  The value is
4259                    undefined. */
4260                 return NULL;
4261               }
4262
4263             pc_cat = cv->category;
4264             if (pc_a_p)
4265               *pc_a_p = pc_a;
4266             if (pc_a_idx_p)
4267               *pc_a_idx_p = pc_a_idx;
4268           }
4269       }
4270
4271   assert (pc_cat != NULL);
4272   return pc_cat;
4273 }
4274
4275 static double
4276 ctables_cell_calculate_postcompute (const struct ctables_section *s,
4277                                     const struct ctables_cell *cell,
4278                                     const struct ctables_summary_spec *ss,
4279                                     struct fmt_spec *format,
4280                                     bool *is_ctables_format,
4281                                     size_t summary_idx)
4282 {
4283   enum pivot_axis_type pc_a = 0;
4284   size_t pc_a_idx = 0;
4285   const struct ctables_category *pc_cat = ctables_cell_postcompute (
4286     s, cell, &pc_a, &pc_a_idx);
4287   if (!pc_cat)
4288     return SYSMIS;
4289
4290   const struct ctables_postcompute *pc = pc_cat->pc;
4291   if (pc->specs)
4292     {
4293       for (size_t i = 0; i < pc->specs->n; i++)
4294         {
4295           const struct ctables_summary_spec *ss2 = &pc->specs->specs[i];
4296           if (ss->function == ss2->function
4297               && ss->percentile == ss2->percentile)
4298             {
4299               *format = ss2->format;
4300               *is_ctables_format = ss2->is_ctables_format;
4301               break;
4302             }
4303         }
4304     }
4305
4306   const struct variable *var = s->nests[pc_a]->vars[pc_a_idx];
4307   const struct ctables_categories *cats = s->table->categories[
4308     var_get_dict_index (var)];
4309   struct ctables_pcexpr_evaluate_ctx ctx = {
4310     .cell = cell,
4311     .section = s,
4312     .cats = cats,
4313     .pc_a = pc_a,
4314     .pc_a_idx = pc_a_idx,
4315     .summary_idx = summary_idx,
4316     .parse_format = pc_cat->parse_format,
4317   };
4318   return ctables_pcexpr_evaluate (&ctx, pc->expr);
4319 }
4320
4321 static char *
4322 ctables_format (double d, const struct fmt_spec *format,
4323                 const struct fmt_settings *settings)
4324 {
4325   const union value v = { .f = d };
4326   char *s = data_out_stretchy (&v, "UTF-8", format, settings, NULL);
4327
4328   /* The custom-currency specifications for NEQUAL, PAREN, and PCTPAREN don't
4329      produce the results we want for negative numbers, putting the negative
4330      sign in the wrong spot, before the prefix instead of after it.  We can't,
4331      in fact, produce the desired results using a custom-currency
4332      specification.  Instead, we postprocess the output, moving the negative
4333      sign into place:
4334
4335          NEQUAL:   "-N=3"  => "N=-3"
4336          PAREN:    "-(3)"  => "(-3)"
4337          PCTPAREN: "-(3%)" => "(-3%)"
4338
4339      This transformation doesn't affect NEGPAREN. */
4340   char *minus_src = strchr (s, '-');
4341   if (minus_src && (minus_src == s || minus_src[-1] != 'E'))
4342     {
4343       char *n_equals = strstr (s, "N=");
4344       char *lparen = strchr (s, '(');
4345       char *minus_dst = n_equals ? n_equals + 1 : lparen;
4346       if (minus_dst)
4347         move_element (s, minus_dst - s + 1, 1, minus_src - s, minus_dst - s);
4348     }
4349   return s;
4350 }
4351
4352 static void
4353 ctables_table_output (struct ctables *ct, struct ctables_table *t)
4354 {
4355   struct pivot_table *pt = pivot_table_create__ (
4356     (t->title
4357      ? pivot_value_new_user_text (t->title, SIZE_MAX)
4358      : pivot_value_new_text (N_("Custom Tables"))),
4359     "Custom Tables");
4360   if (t->caption)
4361     pivot_table_set_caption (
4362       pt, pivot_value_new_user_text (t->caption, SIZE_MAX));
4363   if (t->corner)
4364     pivot_table_set_corner_text (
4365       pt, pivot_value_new_user_text (t->corner, SIZE_MAX));
4366
4367   bool summary_dimension = (t->summary_axis != t->slabels_axis
4368                             || (!t->slabels_visible
4369                                 && t->summary_specs.n > 1));
4370   if (summary_dimension)
4371     {
4372       struct pivot_dimension *d = pivot_dimension_create (
4373         pt, t->slabels_axis, N_("Statistics"));
4374       const struct ctables_summary_spec_set *specs = &t->summary_specs;
4375       if (!t->slabels_visible)
4376         d->hide_all_labels = true;
4377       for (size_t i = 0; i < specs->n; i++)
4378         pivot_category_create_leaf (
4379           d->root, ctables_summary_label (&specs->specs[i], t->cilevel));
4380     }
4381
4382   bool categories_dimension = t->clabels_example != NULL;
4383   if (categories_dimension)
4384     {
4385       struct pivot_dimension *d = pivot_dimension_create (
4386         pt, t->label_axis[t->clabels_from_axis],
4387         t->clabels_from_axis == PIVOT_AXIS_ROW
4388         ? N_("Row Categories")
4389         : N_("Column Categories"));
4390       const struct variable *var = t->clabels_example;
4391       const struct ctables_categories *c = t->categories[var_get_dict_index (var)];
4392       for (size_t i = 0; i < t->n_clabels_values; i++)
4393         {
4394           const struct ctables_value *value = t->clabels_values[i];
4395           const struct ctables_category *cat = ctables_categories_match (c, &value->value, var);
4396           assert (cat != NULL);
4397           pivot_category_create_leaf (d->root, ctables_category_create_label (
4398                                         c, cat, t->clabels_example,
4399                                         &value->value));
4400         }
4401     }
4402
4403   pivot_table_set_look (pt, ct->look);
4404   struct pivot_dimension *d[PIVOT_N_AXES];
4405   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
4406     {
4407       static const char *names[] = {
4408         [PIVOT_AXIS_ROW] = N_("Rows"),
4409         [PIVOT_AXIS_COLUMN] = N_("Columns"),
4410         [PIVOT_AXIS_LAYER] = N_("Layers"),
4411       };
4412       d[a] = (t->axes[a] || a == t->summary_axis
4413               ? pivot_dimension_create (pt, a, names[a])
4414               : NULL);
4415       if (!d[a])
4416         continue;
4417
4418       assert (t->axes[a]);
4419
4420       for (size_t i = 0; i < t->stacks[a].n; i++)
4421         {
4422           struct ctables_nest *nest = &t->stacks[a].nests[i];
4423           struct ctables_section **sections = xnmalloc (t->n_sections,
4424                                                         sizeof *sections);
4425           size_t n_sections = 0;
4426
4427           size_t n_total_cells = 0;
4428           size_t max_depth = 0;
4429           for (size_t j = 0; j < t->n_sections; j++)
4430             if (t->sections[j].nests[a] == nest)
4431               {
4432                 struct ctables_section *s = &t->sections[j];
4433                 sections[n_sections++] = s;
4434                 n_total_cells += hmap_count (&s->cells);
4435
4436                 size_t depth = s->nests[a]->n;
4437                 max_depth = MAX (depth, max_depth);
4438               }
4439
4440           struct ctables_cell **sorted = xnmalloc (n_total_cells,
4441                                                    sizeof *sorted);
4442           size_t n_sorted = 0;
4443
4444           for (size_t j = 0; j < n_sections; j++)
4445             {
4446               struct ctables_section *s = sections[j];
4447
4448               struct ctables_cell *cell;
4449               HMAP_FOR_EACH (cell, struct ctables_cell, node, &s->cells)
4450                 if (!cell->hide)
4451                   sorted[n_sorted++] = cell;
4452               assert (n_sorted <= n_total_cells);
4453             }
4454
4455           struct ctables_cell_sort_aux aux = { .nest = nest, .a = a };
4456           sort (sorted, n_sorted, sizeof *sorted, ctables_cell_compare_3way, &aux);
4457
4458 #if 0
4459           if (a == PIVOT_AXIS_ROW)
4460             {
4461               size_t ids[N_CTDTS];
4462               memset (ids, 0, sizeof ids);
4463               for (size_t j = 0; j < n_sorted; j++)
4464                 {
4465                   struct ctables_cell *cell = sorted[j];
4466                   for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
4467                     {
4468                       struct ctables_domain *domain = cell->domains[dt];
4469                       if (!domain->sequence)
4470                         domain->sequence = ++ids[dt];
4471                     }
4472                 }
4473             }
4474 #endif
4475
4476 #if 0
4477           for (size_t j = 0; j < n_sorted; j++)
4478             {
4479               printf ("%s (%s): %f/%f = %.1f%%\n", sorted[j]->name, sorted[j]->contributes_to_domains ? "y" : "n", sorted[j]->summaries[0].count, sorted[j]->domains[CTDT_COL]->e_count, sorted[j]->summaries[0].count / sorted[j]->domains[CTDT_COL]->e_count * 100.0);
4480             }
4481           printf ("\n");
4482 #endif
4483           
4484           struct ctables_level
4485             {
4486               enum ctables_level_type
4487                 {
4488                   CTL_VAR,          /* Variable label for nest->vars[var_idx]. */
4489                   CTL_CATEGORY,     /* Category for nest->vars[var_idx]. */
4490                   CTL_SUMMARY,      /* Summary functions. */
4491                 }
4492                 type;
4493
4494               enum settings_value_show vlabel; /* CTL_VAR only. */
4495               size_t var_idx;
4496             };
4497           struct ctables_level *levels = xnmalloc (1 + 2 * max_depth, sizeof *levels);
4498           size_t n_levels = 0;
4499           for (size_t k = 0; k < nest->n; k++)
4500             {
4501               enum ctables_vlabel vlabel = ct->vlabels[var_get_dict_index (nest->vars[k])];
4502               if (vlabel != CTVL_NONE)
4503                 {
4504                   levels[n_levels++] = (struct ctables_level) {
4505                     .type = CTL_VAR,
4506                     .vlabel = (enum settings_value_show) vlabel,
4507                     .var_idx = k,
4508                   };
4509                 }
4510
4511               if (nest->scale_idx != k
4512                   && (k != nest->n - 1 || t->label_axis[a] == a))
4513                 {
4514                   levels[n_levels++] = (struct ctables_level) {
4515                     .type = CTL_CATEGORY,
4516                     .var_idx = k,
4517                   };
4518                 }
4519             }
4520
4521           if (!summary_dimension && a == t->slabels_axis)
4522             {
4523               levels[n_levels++] = (struct ctables_level) {
4524                 .type = CTL_SUMMARY,
4525                 .var_idx = SIZE_MAX,
4526               };
4527             }
4528
4529           /* Pivot categories:
4530
4531              - variable label for nest->vars[0], if vlabel != CTVL_NONE
4532              - category for nest->vars[0], if nest->scale_idx != 0
4533              - variable label for nest->vars[1], if vlabel != CTVL_NONE
4534              - category for nest->vars[1], if nest->scale_idx != 1
4535              ...
4536              - variable label for nest->vars[n - 1], if vlabel != CTVL_NONE
4537              - category for nest->vars[n - 1], if t->label_axis[a] == a && nest->scale_idx != n - 1.
4538              - summary function, if 'a == t->slabels_axis && a ==
4539              t->summary_axis'.
4540
4541              Additional dimensions:
4542
4543              - If 'a == t->slabels_axis && a != t->summary_axis', add a summary
4544              dimension.
4545              - If 't->label_axis[b] == a' for some 'b != a', add a category
4546              dimension to 'a'.
4547           */
4548
4549
4550           struct pivot_category **groups = xnmalloc (1 + 2 * max_depth, sizeof *groups);
4551           int prev_leaf = 0;
4552           for (size_t j = 0; j < n_sorted; j++)
4553             {
4554               struct ctables_cell *cell = sorted[j];
4555               struct ctables_cell *prev = j > 0 ? sorted[j - 1] : NULL;
4556
4557               size_t n_common = 0;
4558               if (j > 0)
4559                 {
4560                   for (; n_common < n_levels; n_common++)
4561                     {
4562                       const struct ctables_level *level = &levels[n_common];
4563                       if (level->type == CTL_CATEGORY)
4564                         {
4565                           size_t var_idx = level->var_idx;
4566                           const struct ctables_category *c = cell->axes[a].cvs[var_idx].category;
4567                           if (prev->axes[a].cvs[var_idx].category != c)
4568                             break;
4569                           else if (c->type != CCT_SUBTOTAL
4570                                    && c->type != CCT_TOTAL
4571                                    && c->type != CCT_POSTCOMPUTE
4572                                    && !value_equal (&prev->axes[a].cvs[var_idx].value,
4573                                                     &cell->axes[a].cvs[var_idx].value,
4574                                                     var_get_type (nest->vars[var_idx])))
4575                             break;
4576                         }
4577                     }
4578                 }
4579
4580               for (size_t k = n_common; k < n_levels; k++)
4581                 {
4582                   const struct ctables_level *level = &levels[k];
4583                   struct pivot_category *parent = k ? groups[k - 1] : d[a]->root;
4584                   if (level->type == CTL_SUMMARY)
4585                     {
4586                       assert (k == n_levels - 1);
4587
4588                       const struct ctables_summary_spec_set *specs = &t->summary_specs;
4589                       for (size_t m = 0; m < specs->n; m++)
4590                         {
4591                           int leaf = pivot_category_create_leaf (
4592                             parent, ctables_summary_label (&specs->specs[m],
4593                                                            t->cilevel));
4594                           if (!m)
4595                             prev_leaf = leaf;
4596                         }
4597                     }
4598                   else
4599                     {
4600                       const struct variable *var = nest->vars[level->var_idx];
4601                       struct pivot_value *label;
4602                       if (level->type == CTL_VAR)
4603                         {
4604                           label = pivot_value_new_variable (var);
4605                           label->variable.show = level->vlabel;
4606                         }
4607                       else if (level->type == CTL_CATEGORY)
4608                         {
4609                           const struct ctables_cell_value *cv = &cell->axes[a].cvs[level->var_idx];
4610                           label = ctables_category_create_label (
4611                             t->categories[var_get_dict_index (var)],
4612                             cv->category, var, &cv->value);
4613                         }
4614                       else
4615                         NOT_REACHED ();
4616
4617                       if (k == n_levels - 1)
4618                         prev_leaf = pivot_category_create_leaf (parent, label);
4619                       else
4620                         groups[k] = pivot_category_create_group__ (parent, label);
4621                     }
4622                 }
4623
4624               cell->axes[a].leaf = prev_leaf;
4625             }
4626           free (sorted);
4627           free (groups);
4628           free (levels);
4629           free (sections);
4630         }
4631     }
4632
4633   {
4634     size_t n_total_cells = 0;
4635     for (size_t j = 0; j < t->n_sections; j++)
4636       n_total_cells += hmap_count (&t->sections[j].cells);
4637
4638     struct ctables_cell **sorted = xnmalloc (n_total_cells, sizeof *sorted);
4639     size_t n_sorted = 0;
4640     for (size_t j = 0; j < t->n_sections; j++)
4641       {
4642         const struct ctables_section *s = &t->sections[j];
4643         struct ctables_cell *cell;
4644         HMAP_FOR_EACH (cell, struct ctables_cell, node, &s->cells)
4645           if (!cell->hide)
4646             sorted[n_sorted++] = cell;
4647       }
4648     assert (n_sorted <= n_total_cells);
4649     sort (sorted, n_sorted, sizeof *sorted, ctables_cell_compare_leaf_3way,
4650           NULL);
4651     size_t ids[N_CTDTS];
4652     memset (ids, 0, sizeof ids);
4653     for (size_t j = 0; j < n_sorted; j++)
4654       {
4655         struct ctables_cell *cell = sorted[j];
4656         for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
4657           {
4658             struct ctables_domain *domain = cell->domains[dt];
4659             if (!domain->sequence)
4660               domain->sequence = ++ids[dt];
4661           }
4662       }
4663
4664     free (sorted);
4665   }
4666
4667   for (size_t i = 0; i < t->n_sections; i++)
4668     {
4669       struct ctables_section *s = &t->sections[i];
4670
4671       struct ctables_cell *cell;
4672       HMAP_FOR_EACH (cell, struct ctables_cell, node, &s->cells)
4673         {
4674           if (cell->hide)
4675             continue;
4676
4677           const struct ctables_nest *specs_nest = s->nests[t->summary_axis];
4678           const struct ctables_summary_spec_set *specs = &specs_nest->specs[cell->sv];
4679           for (size_t j = 0; j < specs->n; j++)
4680             {
4681               size_t dindexes[5];
4682               size_t n_dindexes = 0;
4683
4684               if (summary_dimension)
4685                 dindexes[n_dindexes++] = specs->specs[j].axis_idx;
4686
4687               if (categories_dimension)
4688                 {
4689                   const struct ctables_nest *clabels_nest = s->nests[t->clabels_from_axis];
4690                   const struct variable *var = clabels_nest->vars[clabels_nest->n - 1];
4691                   const union value *value = &cell->axes[t->clabels_from_axis].cvs[clabels_nest->n - 1].value;
4692                   const struct ctables_value *ctv = ctables_value_find (t, value, var_get_width (var));
4693                   if (!ctv)
4694                     continue;
4695                   dindexes[n_dindexes++] = ctv->leaf;
4696                 }
4697
4698               for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
4699                 if (d[a])
4700                   {
4701                     int leaf = cell->axes[a].leaf;
4702                     if (a == t->summary_axis && !summary_dimension)
4703                       leaf += j;
4704                     dindexes[n_dindexes++] = leaf;
4705                   }
4706
4707               const struct ctables_summary_spec *ss = &specs->specs[j];
4708
4709               struct fmt_spec format = specs->specs[j].format;
4710               bool is_ctables_format = ss->is_ctables_format;
4711               double d = (cell->postcompute
4712                           ? ctables_cell_calculate_postcompute (
4713                             s, cell, ss, &format, &is_ctables_format, j)
4714                           : ctables_summary_value (cell, &cell->summaries[j],
4715                                                    ss));
4716
4717               struct pivot_value *value;
4718               if (ct->hide_threshold != 0
4719                   && d < ct->hide_threshold
4720                   && ctables_summary_function_is_count (ss->function))
4721                 {
4722                   value = pivot_value_new_user_text_nocopy (
4723                     xasprintf ("<%d", ct->hide_threshold));
4724                 }
4725               else if (d == 0 && ct->zero)
4726                 value = pivot_value_new_user_text (ct->zero, SIZE_MAX);
4727               else if (d == SYSMIS && ct->missing)
4728                 value = pivot_value_new_user_text (ct->missing, SIZE_MAX);
4729               else if (is_ctables_format)
4730                 value = pivot_value_new_user_text_nocopy (
4731                   ctables_format (d, &format, &ct->ctables_formats));
4732               else
4733                 {
4734                   value = pivot_value_new_number (d);
4735                   value->numeric.format = format;
4736                 }
4737               /* XXX should text values be right-justified? */
4738               pivot_table_put (pt, dindexes, n_dindexes, value);
4739             }
4740         }
4741     }
4742
4743   pivot_table_submit (pt);
4744 }
4745
4746 static bool
4747 ctables_check_label_position (struct ctables_table *t, enum pivot_axis_type a)
4748 {
4749   enum pivot_axis_type label_pos = t->label_axis[a];
4750   if (label_pos == a)
4751     return true;
4752
4753   t->clabels_from_axis = a;
4754
4755   const char *subcommand_name = a == PIVOT_AXIS_ROW ? "ROWLABELS" : "COLLABELS";
4756   const char *pos_name = label_pos == PIVOT_AXIS_LAYER ? "LAYER" : "OPPOSITE";
4757
4758   const struct ctables_stack *stack = &t->stacks[a];
4759   if (!stack->n)
4760     return true;
4761
4762   const struct ctables_nest *n0 = &stack->nests[0];
4763   if (n0->n == 0)
4764     {
4765       assert (stack->n == 1);
4766       return true;
4767     }
4768
4769   const struct variable *v0 = n0->vars[n0->n - 1];
4770   struct ctables_categories *c0 = t->categories[var_get_dict_index (v0)];
4771   t->clabels_example = v0;
4772
4773   for (size_t i = 0; i < c0->n_cats; i++)
4774     if (c0->cats[i].type == CCT_FUNCTION)
4775       {
4776         msg (SE, _("%s=%s is not allowed with sorting based "
4777                    "on a summary function."),
4778              subcommand_name, pos_name);
4779         return false;
4780       }
4781   if (n0->n - 1 == n0->scale_idx)
4782     {
4783       msg (SE, _("%s=%s requires the variables to be moved to be categorical, "
4784                  "but %s is a scale variable."),
4785            subcommand_name, pos_name, var_get_name (v0));
4786       return false;
4787     }
4788
4789   for (size_t i = 1; i < stack->n; i++)
4790     {
4791       const struct ctables_nest *ni = &stack->nests[i];
4792       assert (ni->n > 0);
4793       const struct variable *vi = ni->vars[ni->n - 1];
4794       struct ctables_categories *ci = t->categories[var_get_dict_index (vi)];
4795
4796       if (ni->n - 1 == ni->scale_idx)
4797         {
4798           msg (SE, _("%s=%s requires the variables to be moved to be "
4799                      "categorical, but %s is a scale variable."),
4800                subcommand_name, pos_name, var_get_name (vi));
4801           return false;
4802         }
4803       if (var_get_width (v0) != var_get_width (vi))
4804         {
4805           msg (SE, _("%s=%s requires the variables to be "
4806                      "moved to have the same width, but %s has "
4807                      "width %d and %s has width %d."),
4808                subcommand_name, pos_name,
4809                var_get_name (v0), var_get_width (v0),
4810                var_get_name (vi), var_get_width (vi));
4811           return false;
4812         }
4813       if (!val_labs_equal (var_get_value_labels (v0),
4814                            var_get_value_labels (vi)))
4815         {
4816           msg (SE, _("%s=%s requires the variables to be "
4817                      "moved to have the same value labels, but %s "
4818                      "and %s have different value labels."),
4819                subcommand_name, pos_name,
4820                var_get_name (v0), var_get_name (vi));
4821           return false;
4822         }
4823       if (!ctables_categories_equal (c0, ci))
4824         {
4825           msg (SE, _("%s=%s requires the variables to be "
4826                      "moved to have the same category "
4827                      "specifications, but %s and %s have different "
4828                      "category specifications."),
4829                subcommand_name, pos_name,
4830                var_get_name (v0), var_get_name (vi));
4831           return false;
4832         }
4833     }
4834
4835   return true;
4836 }
4837
4838 static size_t
4839 add_sum_var (struct variable *var,
4840              struct variable ***sum_vars, size_t *n, size_t *allocated)
4841 {
4842   for (size_t i = 0; i < *n; i++)
4843     if (var == (*sum_vars)[i])
4844       return i;
4845
4846   if (*n >= *allocated)
4847     *sum_vars = x2nrealloc (*sum_vars, allocated, sizeof **sum_vars);
4848   (*sum_vars)[*n] = var;
4849   return (*n)++;
4850 }
4851
4852 static void
4853 enumerate_sum_vars (const struct ctables_axis *a,
4854                     struct variable ***sum_vars, size_t *n, size_t *allocated)
4855 {
4856   if (!a)
4857     return;
4858
4859   switch (a->op)
4860     {
4861     case CTAO_VAR:
4862       for (size_t i = 0; i < N_CSVS; i++)
4863         for (size_t j = 0; j < a->specs[i].n; j++)
4864           {
4865             struct ctables_summary_spec *spec = &a->specs[i].specs[j];
4866             if (ctables_function_is_pctsum (spec->function))
4867               spec->sum_var_idx = add_sum_var (a->var, sum_vars, n, allocated);
4868           }
4869       break;
4870
4871     case CTAO_STACK:
4872     case CTAO_NEST:
4873       for (size_t i = 0; i < 2; i++)
4874         enumerate_sum_vars (a->subs[i], sum_vars, n, allocated);
4875       break;
4876     }
4877 }
4878
4879 static bool
4880 ctables_prepare_table (struct ctables_table *t)
4881 {
4882   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
4883     if (t->axes[a])
4884       {
4885         t->stacks[a] = enumerate_fts (a, t->axes[a]);
4886
4887         for (size_t j = 0; j < t->stacks[a].n; j++)
4888           {
4889             struct ctables_nest *nest = &t->stacks[a].nests[j];
4890             for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
4891               {
4892                 nest->domains[dt] = xmalloc (nest->n * sizeof *nest->domains[dt]);
4893                 nest->n_domains[dt] = 0;
4894
4895                 for (size_t k = 0; k < nest->n; k++)
4896                   {
4897                     if (k == nest->scale_idx)
4898                       continue;
4899
4900                     switch (dt)
4901                       {
4902                       case CTDT_TABLE:
4903                         continue;
4904
4905                       case CTDT_LAYER:
4906                         if (a != PIVOT_AXIS_LAYER)
4907                           continue;
4908                         break;
4909
4910                       case CTDT_SUBTABLE:
4911                       case CTDT_ROW:
4912                       case CTDT_COL:
4913                         if (dt == CTDT_SUBTABLE ? a != PIVOT_AXIS_LAYER
4914                             : dt == CTDT_ROW ? a == PIVOT_AXIS_COLUMN
4915                             : a == PIVOT_AXIS_ROW)
4916                           {
4917                             if (k == nest->n - 1
4918                                 || (nest->scale_idx == nest->n - 1
4919                                     && k == nest->n - 2))
4920                               continue;
4921                           }
4922                         break;
4923
4924                       case CTDT_LAYERROW:
4925                         if (a == PIVOT_AXIS_COLUMN)
4926                           continue;
4927                         break;
4928
4929                       case CTDT_LAYERCOL:
4930                         if (a == PIVOT_AXIS_ROW)
4931                           continue;
4932                         break;
4933                       }
4934
4935                     nest->domains[dt][nest->n_domains[dt]++] = k;
4936                   }
4937               }
4938           }
4939       }
4940     else
4941       {
4942         struct ctables_nest *nest = xmalloc (sizeof *nest);
4943         *nest = (struct ctables_nest) { .n = 0 };
4944         t->stacks[a] = (struct ctables_stack) { .nests = nest, .n = 1 };
4945
4946         /* There's no point in moving labels away from an axis that has no
4947            labels, so avoid dealing with the special cases around that. */
4948         t->label_axis[a] = a;
4949       }
4950
4951   struct ctables_stack *stack = &t->stacks[t->summary_axis];
4952   for (size_t i = 0; i < stack->n; i++)
4953     {
4954       struct ctables_nest *nest = &stack->nests[i];
4955       if (!nest->specs[CSV_CELL].n)
4956         {
4957           struct ctables_summary_spec_set *specs = &nest->specs[CSV_CELL];
4958           specs->specs = xmalloc (sizeof *specs->specs);
4959           specs->n = 1;
4960
4961           enum ctables_summary_function function
4962             = specs->is_scale ? CTSF_MEAN : CTSF_COUNT;
4963
4964           *specs->specs = (struct ctables_summary_spec) {
4965             .function = function,
4966             .format = ctables_summary_default_format (function, specs->var),
4967           };
4968           if (!specs->var)
4969             specs->var = nest->vars[0];
4970
4971           ctables_summary_spec_set_clone (&nest->specs[CSV_TOTAL],
4972                                           &nest->specs[CSV_CELL]);
4973         }
4974       else if (!nest->specs[CSV_TOTAL].n)
4975         ctables_summary_spec_set_clone (&nest->specs[CSV_TOTAL],
4976                                         &nest->specs[CSV_CELL]);
4977
4978       if (t->ctables->smissing_listwise)
4979         {
4980           struct variable **listwise_vars = NULL;
4981           size_t n = 0;
4982           size_t allocated = 0;
4983
4984           for (size_t j = nest->group_head; j < stack->n; j++)
4985             {
4986               const struct ctables_nest *other_nest = &stack->nests[j];
4987               if (other_nest->group_head != nest->group_head)
4988                 break;
4989
4990               if (nest != other_nest && other_nest->scale_idx < other_nest->n)
4991                 {
4992                   if (n >= allocated)
4993                     listwise_vars = x2nrealloc (listwise_vars, &allocated,
4994                                                 sizeof *listwise_vars);
4995                   listwise_vars[n++] = other_nest->vars[other_nest->scale_idx];
4996                 }
4997             }
4998           for (enum ctables_summary_variant sv = 0; sv < N_CSVS; sv++)
4999             {
5000               if (sv > 0)
5001                 listwise_vars = xmemdup (listwise_vars,
5002                                          n * sizeof *listwise_vars);
5003               nest->specs[sv].listwise_vars = listwise_vars;
5004               nest->specs[sv].n_listwise_vars = n;
5005             }
5006         }
5007     }
5008
5009   struct ctables_summary_spec_set *merged = &t->summary_specs;
5010   struct merge_item *items = xnmalloc (N_CSVS * stack->n, sizeof *items);
5011   size_t n_left = 0;
5012   for (size_t j = 0; j < stack->n; j++)
5013     {
5014       const struct ctables_nest *nest = &stack->nests[j];
5015       if (nest->n)
5016         for (enum ctables_summary_variant sv = 0; sv < N_CSVS; sv++)
5017           items[n_left++] = (struct merge_item) { .set = &nest->specs[sv] };
5018     }
5019
5020   while (n_left > 0)
5021     {
5022       struct merge_item min = items[0];
5023       for (size_t j = 1; j < n_left; j++)
5024         if (merge_item_compare_3way (&items[j], &min) < 0)
5025           min = items[j];
5026
5027       if (merged->n >= merged->allocated)
5028         merged->specs = x2nrealloc (merged->specs, &merged->allocated,
5029                                     sizeof *merged->specs);
5030       merged->specs[merged->n++] = min.set->specs[min.ofs];
5031
5032       for (size_t j = 0; j < n_left; )
5033         {
5034           if (merge_item_compare_3way (&items[j], &min) == 0)
5035             {
5036               struct merge_item *item = &items[j];
5037               item->set->specs[item->ofs].axis_idx = merged->n - 1;
5038               if (++item->ofs >= item->set->n)
5039                 {
5040                   items[j] = items[--n_left];
5041                   continue;
5042                 }
5043             }
5044           j++;
5045         }
5046     }
5047   free (items);
5048
5049 #if 0
5050   for (size_t j = 0; j < merged->n; j++)
5051     printf ("%s\n", ctables_summary_function_name (merged->specs[j].function));
5052
5053   for (size_t j = 0; j < stack->n; j++)
5054     {
5055       const struct ctables_nest *nest = &stack->nests[j];
5056       for (enum ctables_summary_variant sv = 0; sv < N_CSVS; sv++)
5057         {
5058           const struct ctables_summary_spec_set *specs = &nest->specs[sv];
5059           for (size_t k = 0; k < specs->n; k++)
5060             printf ("(%s, %zu) ", ctables_summary_function_name (specs->specs[k].function),
5061                     specs->specs[k].axis_idx);
5062           printf ("\n");
5063         }
5064     }
5065 #endif
5066
5067   size_t allocated_sum_vars = 0;
5068   enumerate_sum_vars (t->axes[t->summary_axis],
5069                       &t->sum_vars, &t->n_sum_vars, &allocated_sum_vars);
5070
5071   return (ctables_check_label_position (t, PIVOT_AXIS_ROW)
5072           && ctables_check_label_position (t, PIVOT_AXIS_COLUMN));
5073 }
5074
5075 static void
5076 ctables_insert_clabels_values (struct ctables_table *t, const struct ccase *c,
5077                                enum pivot_axis_type a)
5078 {
5079   struct ctables_stack *stack = &t->stacks[a];
5080   for (size_t i = 0; i < stack->n; i++)
5081     {
5082       const struct ctables_nest *nest = &stack->nests[i];
5083       const struct variable *var = nest->vars[nest->n - 1];
5084       const union value *value = case_data (c, var);
5085
5086       if (var_is_numeric (var) && value->f == SYSMIS)
5087         continue;
5088
5089       if (ctables_categories_match (t->categories [var_get_dict_index (var)],
5090                                     value, var))
5091         ctables_value_insert (t, value, var_get_width (var));
5092     }
5093 }
5094
5095 static int
5096 compare_clabels_values_3way (const void *a_, const void *b_, const void *width_)
5097 {
5098   const struct ctables_value *const *ap = a_;
5099   const struct ctables_value *const *bp = b_;
5100   const struct ctables_value *a = *ap;
5101   const struct ctables_value *b = *bp;
5102   const int *width = width_;
5103   return value_compare_3way (&a->value, &b->value, *width);
5104 }
5105
5106 static void
5107 ctables_sort_clabels_values (struct ctables_table *t)
5108 {
5109   const struct variable *v0 = t->clabels_example;
5110   int width = var_get_width (v0);
5111
5112   struct ctables_categories *c0 = t->categories[var_get_dict_index (v0)];
5113   if (c0->show_empty)
5114     {
5115       const struct val_labs *val_labs = var_get_value_labels (v0);
5116       for (const struct val_lab *vl = val_labs_first (val_labs); vl;
5117            vl = val_labs_next (val_labs, vl))
5118         if (ctables_categories_match (c0, &vl->value, v0))
5119           ctables_value_insert (t, &vl->value, width);
5120     }
5121
5122   size_t n = hmap_count (&t->clabels_values_map);
5123   t->clabels_values = xnmalloc (n, sizeof *t->clabels_values);
5124
5125   struct ctables_value *clv;
5126   size_t i = 0;
5127   HMAP_FOR_EACH (clv, struct ctables_value, node, &t->clabels_values_map)
5128     t->clabels_values[i++] = clv;
5129   t->n_clabels_values = n;
5130   assert (i == n);
5131
5132   sort (t->clabels_values, n, sizeof *t->clabels_values,
5133         compare_clabels_values_3way, &width);
5134
5135   for (size_t i = 0; i < n; i++)
5136     t->clabels_values[i]->leaf = i;
5137 }
5138
5139 static void
5140 ctables_add_category_occurrences (const struct variable *var,
5141                                   struct hmap *occurrences,
5142                                   const struct ctables_categories *cats)
5143 {
5144   const struct val_labs *val_labs = var_get_value_labels (var);
5145
5146   for (size_t i = 0; i < cats->n_cats; i++)
5147     {
5148       const struct ctables_category *c = &cats->cats[i];
5149       switch (c->type)
5150         {
5151         case CCT_NUMBER:
5152           ctables_add_occurrence (var, &(const union value) { .f = c->number },
5153                                   occurrences);
5154           break;
5155
5156         case CCT_STRING:
5157           {
5158             int width = var_get_width (var);
5159             union value value;
5160             value_init (&value, width);
5161             value_copy_buf_rpad (&value, width,
5162                                  CHAR_CAST (uint8_t *, c->string.string),
5163                                  c->string.length, ' ');
5164             ctables_add_occurrence (var, &value, occurrences);
5165             value_destroy (&value, width);
5166           }
5167           break;
5168
5169         case CCT_NRANGE:
5170           assert (var_is_numeric (var));
5171           for (const struct val_lab *vl = val_labs_first (val_labs); vl;
5172                vl = val_labs_next (val_labs, vl))
5173             if (vl->value.f >= c->nrange[0] && vl->value.f <= c->nrange[1])
5174               ctables_add_occurrence (var, &vl->value, occurrences);
5175           break;
5176
5177         case CCT_SRANGE:
5178           assert (var_is_alpha (var));
5179           for (const struct val_lab *vl = val_labs_first (val_labs); vl;
5180                vl = val_labs_next (val_labs, vl))
5181             if (in_string_range (&vl->value, var, c->srange))
5182               ctables_add_occurrence (var, &vl->value, occurrences);
5183           break;
5184
5185         case CCT_MISSING:
5186           for (const struct val_lab *vl = val_labs_first (val_labs); vl;
5187                vl = val_labs_next (val_labs, vl))
5188             if (var_is_value_missing (var, &vl->value))
5189               ctables_add_occurrence (var, &vl->value, occurrences);
5190           break;
5191
5192         case CCT_OTHERNM:
5193           for (const struct val_lab *vl = val_labs_first (val_labs); vl;
5194                vl = val_labs_next (val_labs, vl))
5195             ctables_add_occurrence (var, &vl->value, occurrences);
5196           break;
5197
5198         case CCT_POSTCOMPUTE:
5199           break;
5200
5201         case CCT_SUBTOTAL:
5202         case CCT_TOTAL:
5203           break;
5204
5205         case CCT_VALUE:
5206         case CCT_LABEL:
5207         case CCT_FUNCTION:
5208           for (const struct val_lab *vl = val_labs_first (val_labs); vl;
5209                vl = val_labs_next (val_labs, vl))
5210             if (c->include_missing || !var_is_value_missing (var, &vl->value))
5211               ctables_add_occurrence (var, &vl->value, occurrences);
5212           break;
5213
5214         case CCT_EXCLUDED_MISSING:
5215           break;
5216         }
5217     }
5218 }
5219
5220 static void
5221 ctables_section_recurse_add_empty_categories (
5222   struct ctables_section *s,
5223   const struct ctables_category *cats[PIVOT_N_AXES][10], struct ccase *c,
5224   enum pivot_axis_type a, size_t a_idx)
5225 {
5226   if (a >= PIVOT_N_AXES)
5227     ctables_cell_insert__ (s, c, cats);
5228   else if (!s->nests[a] || a_idx >= s->nests[a]->n)
5229     ctables_section_recurse_add_empty_categories (s, cats, c, a + 1, 0);
5230   else
5231     {
5232       const struct variable *var = s->nests[a]->vars[a_idx];
5233       const struct ctables_categories *categories = s->table->categories[
5234         var_get_dict_index (var)];
5235       int width = var_get_width (var);
5236       const struct hmap *occurrences = &s->occurrences[a][a_idx];
5237       const struct ctables_occurrence *o;
5238       HMAP_FOR_EACH (o, struct ctables_occurrence, node, occurrences)
5239         {
5240           union value *value = case_data_rw (c, var);
5241           value_destroy (value, width);
5242           value_clone (value, &o->value, width);
5243           cats[a][a_idx] = ctables_categories_match (categories, value, var);
5244           assert (cats[a][a_idx] != NULL);
5245           ctables_section_recurse_add_empty_categories (s, cats, c, a, a_idx + 1);
5246         }
5247
5248       for (size_t i = 0; i < categories->n_cats; i++)
5249         {
5250           const struct ctables_category *cat = &categories->cats[i];
5251           if (cat->type == CCT_POSTCOMPUTE)
5252             {
5253               cats[a][a_idx] = cat;
5254               ctables_section_recurse_add_empty_categories (s, cats, c, a, a_idx + 1);
5255             }
5256         }
5257     }
5258 }
5259
5260 static void
5261 ctables_section_add_empty_categories (struct ctables_section *s)
5262 {
5263   bool show_empty = false;
5264   for (size_t a = 0; a < PIVOT_N_AXES; a++)
5265     if (s->nests[a])
5266       for (size_t k = 0; k < s->nests[a]->n; k++)
5267         if (k != s->nests[a]->scale_idx)
5268           {
5269             const struct variable *var = s->nests[a]->vars[k];
5270             const struct ctables_categories *cats = s->table->categories[
5271               var_get_dict_index (var)];
5272             if (cats->show_empty)
5273               {
5274                 show_empty = true;
5275                 ctables_add_category_occurrences (var, &s->occurrences[a][k], cats);
5276               }
5277           }
5278   if (!show_empty)
5279     return;
5280
5281   const struct ctables_category *cats[PIVOT_N_AXES][10]; /* XXX */
5282   struct ccase *c = case_create (dict_get_proto (s->table->ctables->dict));
5283   ctables_section_recurse_add_empty_categories (s, cats, c, 0, 0);
5284   case_unref (c);
5285 }
5286
5287 static void
5288 ctables_section_clear (struct ctables_section *s)
5289 {
5290   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
5291     {
5292       const struct ctables_nest *nest = s->nests[a];
5293       for (size_t i = 0; i < nest->n; i++)
5294         if (i != nest->scale_idx)
5295           {
5296             const struct variable *var = nest->vars[i];
5297             int width = var_get_width (var);
5298             struct ctables_occurrence *o, *next;
5299             struct hmap *map = &s->occurrences[a][i];
5300             HMAP_FOR_EACH_SAFE (o, next, struct ctables_occurrence, node, map)
5301               {
5302                 value_destroy (&o->value, width);
5303                 hmap_delete (map, &o->node);
5304                 free (o);
5305               }
5306             hmap_shrink (map);
5307           }
5308     }
5309
5310   struct ctables_cell *cell, *next_cell;
5311   HMAP_FOR_EACH_SAFE (cell, next_cell, struct ctables_cell, node, &s->cells)
5312     {
5313       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
5314         {
5315           const struct ctables_nest *nest = s->nests[a];
5316           for (size_t i = 0; i < nest->n; i++)
5317             if (i != nest->scale_idx)
5318               value_destroy (&cell->axes[a].cvs[i].value,
5319                              var_get_width (nest->vars[i]));
5320           free (cell->axes[a].cvs);
5321         }
5322
5323       const struct ctables_nest *ss = s->nests[s->table->summary_axis];
5324       const struct ctables_summary_spec_set *specs = &ss->specs[cell->sv];
5325       for (size_t i = 0; i < specs->n; i++)
5326         ctables_summary_uninit (&cell->summaries[i], &specs->specs[i]);
5327       free (cell->summaries);
5328
5329       hmap_delete (&s->cells, &cell->node);
5330       free (cell);
5331     }
5332   hmap_shrink (&s->cells);
5333
5334   for (enum ctables_domain_type dt = 0; dt < N_CTDTS; dt++)
5335     {
5336       struct ctables_domain *domain, *next_domain;
5337       HMAP_FOR_EACH_SAFE (domain, next_domain, struct ctables_domain, node,
5338                           &s->domains[dt])
5339         {
5340           free (domain->sums);
5341           hmap_delete (&s->domains[dt], &domain->node);
5342           free (domain);
5343         }
5344       hmap_shrink (&s->domains[dt]);
5345     }
5346 }
5347
5348 static void
5349 ctables_section_uninit (struct ctables_section *s)
5350 {
5351   ctables_section_clear (s);
5352
5353   for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
5354     {
5355       struct ctables_nest *nest = s->nests[a];
5356       for (size_t i = 0; i < nest->n; i++)
5357         hmap_destroy (&s->occurrences[a][i]);
5358       free (s->occurrences[a]);
5359     }
5360
5361   hmap_destroy (&s->cells);
5362   for (size_t i = 0; i < N_CTDTS; i++)
5363     hmap_destroy (&s->domains[i]);
5364 }
5365
5366 static void
5367 ctables_table_clear (struct ctables_table *t)
5368 {
5369   for (size_t i = 0; i < t->n_sections; i++)
5370     ctables_section_clear (&t->sections[i]);
5371
5372   if (t->clabels_example)
5373     {
5374       int width = var_get_width (t->clabels_example);
5375       struct ctables_value *value, *next_value;
5376       HMAP_FOR_EACH_SAFE (value, next_value, struct ctables_value, node,
5377                           &t->clabels_values_map)
5378         {
5379           value_destroy (&value->value, width);
5380           hmap_delete (&t->clabels_values_map, &value->node);
5381           free (value);
5382         }
5383       hmap_shrink (&t->clabels_values_map);
5384
5385       free (t->clabels_values);
5386       t->clabels_values = NULL;
5387       t->n_clabels_values = 0;
5388     }
5389 }
5390
5391 static bool
5392 ctables_execute (struct dataset *ds, struct casereader *input,
5393                  struct ctables *ct)
5394 {
5395   for (size_t i = 0; i < ct->n_tables; i++)
5396     {
5397       struct ctables_table *t = ct->tables[i];
5398       t->sections = xnmalloc (MAX (1, t->stacks[PIVOT_AXIS_ROW].n) *
5399                               MAX (1, t->stacks[PIVOT_AXIS_COLUMN].n) *
5400                               MAX (1, t->stacks[PIVOT_AXIS_LAYER].n),
5401                               sizeof *t->sections);
5402       size_t ix[PIVOT_N_AXES];
5403       ctables_table_add_section (t, 0, ix);
5404     }
5405
5406   struct dictionary *dict = dataset_dict (ds);
5407   struct casegrouper *grouper
5408     = (dict_get_split_type (dict) == SPLIT_SEPARATE
5409        ? casegrouper_create_splits (input, dict)
5410        : casegrouper_create_vars (input, NULL, 0));
5411   struct casereader *group;
5412   while (casegrouper_get_next_group (grouper, &group))
5413     {
5414       /* Output SPLIT FILE variables. */
5415       struct ccase *c = casereader_peek (group, 0);
5416       if (c != NULL)
5417         {
5418           output_split_file_values (ds, c);
5419           case_unref (c);
5420         }
5421
5422       bool warn_on_invalid = true;
5423       for (c = casereader_read (group); c;
5424            case_unref (c), c = casereader_read (group))
5425         {
5426           double d_weight = dict_get_case_weight (dict, c, &warn_on_invalid);
5427           double e_weight = (ct->e_weight
5428                              ? var_force_valid_weight (ct->e_weight,
5429                                                        case_num (c, ct->e_weight),
5430                                                        &warn_on_invalid)
5431                              : d_weight);
5432
5433           for (size_t i = 0; i < ct->n_tables; i++)
5434             {
5435               struct ctables_table *t = ct->tables[i];
5436
5437               for (size_t j = 0; j < t->n_sections; j++)
5438                 ctables_cell_insert (&t->sections[j], c, d_weight, e_weight);
5439
5440               for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
5441                 if (t->label_axis[a] != a)
5442                   ctables_insert_clabels_values (t, c, a);
5443             }
5444         }
5445       casereader_destroy (group);
5446
5447       for (size_t i = 0; i < ct->n_tables; i++)
5448         {
5449           struct ctables_table *t = ct->tables[i];
5450
5451           if (t->clabels_example)
5452             ctables_sort_clabels_values (t);
5453
5454           for (size_t j = 0; j < t->n_sections; j++)
5455             ctables_section_add_empty_categories (&t->sections[j]);
5456
5457           ctables_table_output (ct, t);
5458           ctables_table_clear (t);
5459         }
5460     }
5461   return casegrouper_destroy (grouper);
5462 }
5463 \f
5464 /* Postcomputes. */
5465
5466 typedef struct ctables_pcexpr *parse_recursively_func (struct lexer *,
5467                                                        struct dictionary *);
5468
5469 static void
5470 ctables_pcexpr_destroy (struct ctables_pcexpr *e)
5471 {
5472   if (e)
5473     {
5474       switch (e->op)
5475         {
5476         case CTPO_CAT_STRING:
5477           ss_dealloc (&e->string);
5478           break;
5479
5480         case CTPO_CAT_SRANGE:
5481           for (size_t i = 0; i < 2; i++)
5482             ss_dealloc (&e->srange[i]);
5483           break;
5484
5485         case CTPO_ADD:
5486         case CTPO_SUB:
5487         case CTPO_MUL:
5488         case CTPO_DIV:
5489         case CTPO_POW:
5490         case CTPO_NEG:
5491           for (size_t i = 0; i < 2; i++)
5492             ctables_pcexpr_destroy (e->subs[i]);
5493           break;
5494
5495         case CTPO_CONSTANT:
5496         case CTPO_CAT_NUMBER:
5497         case CTPO_CAT_NRANGE:
5498         case CTPO_CAT_MISSING:
5499         case CTPO_CAT_OTHERNM:
5500         case CTPO_CAT_SUBTOTAL:
5501         case CTPO_CAT_TOTAL:
5502           break;
5503         }
5504
5505       msg_location_destroy (e->location);
5506       free (e);
5507     }
5508 }
5509
5510 static struct ctables_pcexpr *
5511 ctables_pcexpr_allocate_binary (enum ctables_postcompute_op op,
5512                                 struct ctables_pcexpr *sub0,
5513                                 struct ctables_pcexpr *sub1)
5514 {
5515   struct ctables_pcexpr *e = xmalloc (sizeof *e);
5516   *e = (struct ctables_pcexpr) {
5517     .op = op,
5518     .subs = { sub0, sub1 },
5519     .location = msg_location_merged (sub0->location, sub1->location),
5520   };
5521   return e;
5522 }
5523
5524 /* How to parse an operator. */
5525 struct operator
5526   {
5527     enum token_type token;
5528     enum ctables_postcompute_op op;
5529   };
5530
5531 static const struct operator *
5532 ctables_pcexpr_match_operator (struct lexer *lexer,
5533                               const struct operator ops[], size_t n_ops)
5534 {
5535   for (const struct operator *op = ops; op < ops + n_ops; op++)
5536     if (lex_token (lexer) == op->token)
5537       {
5538         if (op->token != T_NEG_NUM)
5539           lex_get (lexer);
5540
5541         return op;
5542       }
5543
5544   return NULL;
5545 }
5546
5547 static struct ctables_pcexpr *
5548 ctables_pcexpr_parse_binary_operators__ (
5549   struct lexer *lexer, struct dictionary *dict,
5550   const struct operator ops[], size_t n_ops,
5551   parse_recursively_func *parse_next_level,
5552   const char *chain_warning, struct ctables_pcexpr *lhs)
5553 {
5554   for (int op_count = 0; ; op_count++)
5555     {
5556       const struct operator *op
5557         = ctables_pcexpr_match_operator (lexer, ops, n_ops);
5558       if (!op)
5559         {
5560           if (op_count > 1 && chain_warning)
5561             msg_at (SW, lhs->location, "%s", chain_warning);
5562
5563           return lhs;
5564         }
5565
5566       struct ctables_pcexpr *rhs = parse_next_level (lexer, dict);
5567       if (!rhs)
5568         {
5569           ctables_pcexpr_destroy (lhs);
5570           return NULL;
5571         }
5572
5573       lhs = ctables_pcexpr_allocate_binary (op->op, lhs, rhs);
5574     }
5575 }
5576
5577 static struct ctables_pcexpr *
5578 ctables_pcexpr_parse_binary_operators (
5579   struct lexer *lexer, struct dictionary *dict,
5580   const struct operator ops[], size_t n_ops,
5581   parse_recursively_func *parse_next_level, const char *chain_warning)
5582 {
5583   struct ctables_pcexpr *lhs = parse_next_level (lexer, dict);
5584   if (!lhs)
5585     return NULL;
5586
5587   return ctables_pcexpr_parse_binary_operators__ (lexer, dict, ops, n_ops,
5588                                                  parse_next_level,
5589                                                  chain_warning, lhs);
5590 }
5591
5592 static struct ctables_pcexpr *ctables_pcexpr_parse_add (struct lexer *,
5593                                                         struct dictionary *);
5594
5595 static struct ctables_pcexpr
5596 ctpo_cat_nrange (double low, double high)
5597 {
5598   return (struct ctables_pcexpr) {
5599     .op = CTPO_CAT_NRANGE,
5600     .nrange = { low, high },
5601   };
5602 }
5603
5604 static struct ctables_pcexpr
5605 ctpo_cat_srange (struct substring low, struct substring high)
5606 {
5607   return (struct ctables_pcexpr) {
5608     .op = CTPO_CAT_SRANGE,
5609     .srange = { low, high },
5610   };
5611 }
5612
5613 static struct ctables_pcexpr *
5614 ctables_pcexpr_parse_primary (struct lexer *lexer, struct dictionary *dict)
5615 {
5616   int start_ofs = lex_ofs (lexer);
5617   struct ctables_pcexpr e;
5618   if (lex_is_number (lexer))
5619     {
5620       e = (struct ctables_pcexpr) { .op = CTPO_CONSTANT,
5621                                     .number = lex_number (lexer) };
5622       lex_get (lexer);
5623     }
5624   else if (lex_match_id (lexer, "MISSING"))
5625     e = (struct ctables_pcexpr) { .op = CTPO_CAT_MISSING };
5626   else if (lex_match_id (lexer, "OTHERNM"))
5627     e = (struct ctables_pcexpr) { .op = CTPO_CAT_OTHERNM };
5628   else if (lex_match_id (lexer, "TOTAL"))
5629     e = (struct ctables_pcexpr) { .op = CTPO_CAT_TOTAL };
5630   else if (lex_match_id (lexer, "SUBTOTAL"))
5631     {
5632       size_t subtotal_index = 0;
5633       if (lex_match (lexer, T_LBRACK))
5634         {
5635           if (!lex_force_int_range (lexer, "SUBTOTAL", 1, LONG_MAX))
5636             return NULL;
5637           subtotal_index = lex_integer (lexer);
5638           lex_get (lexer);
5639           if (!lex_force_match (lexer, T_RBRACK))
5640             return NULL;
5641         }
5642       e = (struct ctables_pcexpr) { .op = CTPO_CAT_SUBTOTAL,
5643                                     .subtotal_index = subtotal_index };
5644     }
5645   else if (lex_match (lexer, T_LBRACK))
5646     {
5647       if (lex_match_id (lexer, "LO"))
5648         {
5649           if (!lex_force_match_id (lexer, "THRU"))
5650             return false;
5651
5652           if (lex_is_string (lexer))
5653             {
5654               struct substring low = { .string = NULL };
5655               struct substring high = parse_substring (lexer, dict);
5656               e = ctpo_cat_srange (low, high);
5657             }
5658           else
5659             {
5660               if (!lex_force_num (lexer))
5661                 return false;
5662               e = ctpo_cat_nrange (-DBL_MAX, lex_number (lexer));
5663               lex_get (lexer);
5664             }
5665         }
5666       else if (lex_is_number (lexer))
5667         {
5668           double number = lex_number (lexer);
5669           lex_get (lexer);
5670           if (lex_match_id (lexer, "THRU"))
5671             {
5672               if (lex_match_id (lexer, "HI"))
5673                 e = ctpo_cat_nrange (number, DBL_MAX);
5674               else
5675                 {
5676                   if (!lex_force_num (lexer))
5677                     return false;
5678                   e = ctpo_cat_nrange (number, lex_number (lexer));
5679                   lex_get (lexer);
5680                 }
5681             }
5682           else
5683             e = (struct ctables_pcexpr) { .op = CTPO_CAT_NUMBER,
5684                                           .number = number };
5685         }
5686       else if (lex_is_string (lexer))
5687         {
5688           struct substring s = parse_substring (lexer, dict);
5689
5690           if (lex_match_id (lexer, "THRU"))
5691             {
5692               struct substring high;
5693
5694               if (lex_match_id (lexer, "HI"))
5695                 high = (struct substring) { .string = NULL };
5696               else
5697                 {
5698                   if (!lex_force_string (lexer))
5699                     {
5700                       ss_dealloc (&s);
5701                       return false;
5702                     }
5703                   high = parse_substring (lexer, dict);
5704                 }
5705
5706               e = ctpo_cat_srange (s, high);
5707             }
5708           else
5709             e = (struct ctables_pcexpr) { .op = CTPO_CAT_STRING, .string = s };
5710         }
5711       else
5712         {
5713           lex_error (lexer, NULL);
5714           return NULL;
5715         }
5716
5717       if (!lex_force_match (lexer, T_RBRACK))
5718         {
5719           if (e.op == CTPO_CAT_STRING)
5720             ss_dealloc (&e.string);
5721           else if (e.op == CTPO_CAT_SRANGE)
5722             {
5723               ss_dealloc (&e.srange[0]);
5724               ss_dealloc (&e.srange[1]);
5725             }
5726           return NULL;
5727         }
5728     }
5729   else if (lex_match (lexer, T_LPAREN))
5730     {
5731       struct ctables_pcexpr *ep = ctables_pcexpr_parse_add (lexer, dict);
5732       if (!ep)
5733         return NULL;
5734       if (!lex_force_match (lexer, T_RPAREN))
5735         {
5736           ctables_pcexpr_destroy (ep);
5737           return NULL;
5738         }
5739       return ep;
5740     }
5741   else
5742     {
5743       lex_error (lexer, NULL);
5744       return NULL;
5745     }
5746
5747   e.location = lex_ofs_location (lexer, start_ofs, lex_ofs (lexer) - 1);
5748   return xmemdup (&e, sizeof e);
5749 }
5750
5751 static struct ctables_pcexpr *
5752 ctables_pcexpr_allocate_neg (struct ctables_pcexpr *sub,
5753                              struct lexer *lexer, int start_ofs)
5754 {
5755   struct ctables_pcexpr *e = xmalloc (sizeof *e);
5756   *e = (struct ctables_pcexpr) {
5757     .op = CTPO_NEG,
5758     .subs = { sub },
5759     .location = lex_ofs_location (lexer, start_ofs, lex_ofs (lexer) - 1),
5760   };
5761   return e;
5762 }
5763
5764 static struct ctables_pcexpr *
5765 ctables_pcexpr_parse_exp (struct lexer *lexer, struct dictionary *dict)
5766 {
5767   static const struct operator op = { T_EXP, CTPO_POW };
5768
5769   const char *chain_warning =
5770     _("The exponentiation operator (`**') is left-associative: "
5771       "`a**b**c' equals `(a**b)**c', not `a**(b**c)'.  "
5772       "To disable this warning, insert parentheses.");
5773
5774   if (lex_token (lexer) != T_NEG_NUM || lex_next_token (lexer, 1) != T_EXP)
5775     return ctables_pcexpr_parse_binary_operators (lexer, dict, &op, 1,
5776                                                   ctables_pcexpr_parse_primary,
5777                                                   chain_warning);
5778
5779   /* Special case for situations like "-5**6", which must be parsed as
5780      -(5**6). */
5781
5782   int start_ofs = lex_ofs (lexer);
5783   struct ctables_pcexpr *lhs = xmalloc (sizeof *lhs);
5784   *lhs = (struct ctables_pcexpr) {
5785     .op = CTPO_CONSTANT,
5786     .number = -lex_tokval (lexer),
5787     .location = lex_ofs_location (lexer, start_ofs, lex_ofs (lexer)),
5788   };
5789   lex_get (lexer);
5790
5791   struct ctables_pcexpr *node = ctables_pcexpr_parse_binary_operators__ (
5792     lexer, dict, &op, 1,
5793     ctables_pcexpr_parse_primary, chain_warning, lhs);
5794   if (!node)
5795     return NULL;
5796
5797   return ctables_pcexpr_allocate_neg (node, lexer, start_ofs);
5798 }
5799
5800 /* Parses the unary minus level. */
5801 static struct ctables_pcexpr *
5802 ctables_pcexpr_parse_neg (struct lexer *lexer, struct dictionary *dict)
5803 {
5804   int start_ofs = lex_ofs (lexer);
5805   if (!lex_match (lexer, T_DASH))
5806     return ctables_pcexpr_parse_exp (lexer, dict);
5807
5808   struct ctables_pcexpr *inner = ctables_pcexpr_parse_neg (lexer, dict);
5809   if (!inner)
5810     return NULL;
5811
5812   return ctables_pcexpr_allocate_neg (inner, lexer, start_ofs);
5813 }
5814
5815 /* Parses the multiplication and division level. */
5816 static struct ctables_pcexpr *
5817 ctables_pcexpr_parse_mul (struct lexer *lexer, struct dictionary *dict)
5818 {
5819   static const struct operator ops[] =
5820     {
5821       { T_ASTERISK, CTPO_MUL },
5822       { T_SLASH, CTPO_DIV },
5823     };
5824
5825   return ctables_pcexpr_parse_binary_operators (lexer, dict, ops,
5826                                                sizeof ops / sizeof *ops,
5827                                                ctables_pcexpr_parse_neg, NULL);
5828 }
5829
5830 /* Parses the addition and subtraction level. */
5831 static struct ctables_pcexpr *
5832 ctables_pcexpr_parse_add (struct lexer *lexer, struct dictionary *dict)
5833 {
5834   static const struct operator ops[] =
5835     {
5836       { T_PLUS, CTPO_ADD },
5837       { T_DASH, CTPO_SUB },
5838       { T_NEG_NUM, CTPO_ADD },
5839     };
5840
5841   return ctables_pcexpr_parse_binary_operators (lexer, dict,
5842                                                ops, sizeof ops / sizeof *ops,
5843                                                ctables_pcexpr_parse_mul, NULL);
5844 }
5845
5846 static struct ctables_postcompute *
5847 ctables_find_postcompute (struct ctables *ct, const char *name)
5848 {
5849   struct ctables_postcompute *pc;
5850   HMAP_FOR_EACH_WITH_HASH (pc, struct ctables_postcompute, hmap_node,
5851                            utf8_hash_case_string (name, 0), &ct->postcomputes)
5852     if (!utf8_strcasecmp (pc->name, name))
5853       return pc;
5854   return NULL;
5855 }
5856
5857 static bool
5858 ctables_parse_pcompute (struct lexer *lexer, struct dictionary *dict,
5859                         struct ctables *ct)
5860 {
5861   int pcompute_start = lex_ofs (lexer) - 1;
5862
5863   if (!lex_match (lexer, T_AND))
5864     {
5865       lex_error_expecting (lexer, "&");
5866       return false;
5867     }
5868   if (!lex_force_id (lexer))
5869     return false;
5870
5871   char *name = ss_xstrdup (lex_tokss (lexer));
5872
5873   lex_get (lexer);
5874   if (!lex_force_match (lexer, T_EQUALS)
5875       || !lex_force_match_id (lexer, "EXPR")
5876       || !lex_force_match (lexer, T_LPAREN))
5877     {
5878       free (name);
5879       return false;
5880     }
5881
5882   int expr_start = lex_ofs (lexer);
5883   struct ctables_pcexpr *expr = ctables_pcexpr_parse_add (lexer, dict);
5884   int expr_end = lex_ofs (lexer) - 1;
5885   if (!expr || !lex_force_match (lexer, T_RPAREN))
5886     {
5887       ctables_pcexpr_destroy (expr);
5888       free (name);
5889       return false;
5890     }
5891   int pcompute_end = lex_ofs (lexer) - 1;
5892
5893   struct msg_location *location = lex_ofs_location (lexer, pcompute_start,
5894                                                     pcompute_end);
5895
5896   struct ctables_postcompute *pc = ctables_find_postcompute (ct, name);
5897   if (pc)
5898     {
5899       msg_at (SW, location, _("New definition of &%s will override the "
5900                               "previous definition."),
5901               pc->name);
5902       msg_at (SN, pc->location, _("This is the previous definition."));
5903
5904       ctables_pcexpr_destroy (pc->expr);
5905       msg_location_destroy (pc->location);
5906       free (name);
5907     }
5908   else
5909     {
5910       pc = xmalloc (sizeof *pc);
5911       *pc = (struct ctables_postcompute) { .name = name };
5912       hmap_insert (&ct->postcomputes, &pc->hmap_node,
5913                    utf8_hash_case_string (pc->name, 0));
5914     }
5915   pc->expr = expr;
5916   pc->location = location;
5917   if (!pc->label)
5918     pc->label = lex_ofs_representation (lexer, expr_start, expr_end);
5919   return true;
5920 }
5921
5922 static bool
5923 ctables_parse_pproperties_format (struct lexer *lexer,
5924                                   struct ctables_summary_spec_set *sss)
5925 {
5926   *sss = (struct ctables_summary_spec_set) { .n = 0 };
5927
5928   while (lex_token (lexer) != T_ENDCMD && lex_token (lexer) != T_SLASH
5929          && !(lex_token (lexer) == T_ID
5930               && (lex_id_match (ss_cstr ("LABEL"), lex_tokss (lexer))
5931                   || lex_id_match (ss_cstr ("HIDESOURCECATS"),
5932                                    lex_tokss (lexer)))))
5933     {
5934       /* Parse function. */
5935       enum ctables_summary_function function;
5936       if (!parse_ctables_summary_function (lexer, &function))
5937         goto error;
5938
5939       /* Parse percentile. */
5940       double percentile = 0;
5941       if (function == CTSF_PTILE)
5942         {
5943           if (!lex_force_num_range_closed (lexer, "PTILE", 0, 100))
5944             goto error;
5945           percentile = lex_number (lexer);
5946           lex_get (lexer);
5947         }
5948
5949       /* Parse format. */
5950       struct fmt_spec format;
5951       bool is_ctables_format;
5952       if (!parse_ctables_format_specifier (lexer, &format, &is_ctables_format))
5953         goto error;
5954
5955       if (sss->n >= sss->allocated)
5956         sss->specs = x2nrealloc (sss->specs, &sss->allocated,
5957                                  sizeof *sss->specs);
5958       sss->specs[sss->n++] = (struct ctables_summary_spec) {
5959         .function = function,
5960         .percentile = percentile,
5961         .format = format,
5962         .is_ctables_format = is_ctables_format,
5963       };
5964     }
5965   return true;
5966
5967 error:
5968   ctables_summary_spec_set_uninit (sss);
5969   return false;
5970 }
5971
5972 static bool
5973 ctables_parse_pproperties (struct lexer *lexer, struct ctables *ct)
5974 {
5975   struct ctables_postcompute **pcs = NULL;
5976   size_t n_pcs = 0;
5977   size_t allocated_pcs = 0;
5978
5979   while (lex_match (lexer, T_AND))
5980     {
5981       if (!lex_force_id (lexer))
5982         goto error;
5983       struct ctables_postcompute *pc
5984         = ctables_find_postcompute (ct, lex_tokcstr (lexer));
5985       if (!pc)
5986         {
5987           msg (SE, _("Unknown computed category &%s."), lex_tokcstr (lexer));
5988           goto error;
5989         }
5990       lex_get (lexer);
5991
5992       if (n_pcs >= allocated_pcs)
5993         pcs = x2nrealloc (pcs, &allocated_pcs, sizeof *pcs);
5994       pcs[n_pcs++] = pc;
5995     }
5996
5997   while (lex_token (lexer) != T_SLASH && lex_token (lexer) != T_ENDCMD)
5998     {
5999       if (lex_match_id (lexer, "LABEL"))
6000         {
6001           lex_match (lexer, T_EQUALS);
6002           if (!lex_force_string (lexer))
6003             goto error;
6004
6005           for (size_t i = 0; i < n_pcs; i++)
6006             {
6007               free (pcs[i]->label);
6008               pcs[i]->label = ss_xstrdup (lex_tokss (lexer));
6009             }
6010
6011           lex_get (lexer);
6012         }
6013       else if (lex_match_id (lexer, "FORMAT"))
6014         {
6015           lex_match (lexer, T_EQUALS);
6016
6017           struct ctables_summary_spec_set sss;
6018           if (!ctables_parse_pproperties_format (lexer, &sss))
6019             goto error;
6020
6021           for (size_t i = 0; i < n_pcs; i++)
6022             {
6023               if (pcs[i]->specs)
6024                 ctables_summary_spec_set_uninit (pcs[i]->specs);
6025               else
6026                 pcs[i]->specs = xmalloc (sizeof *pcs[i]->specs);
6027               ctables_summary_spec_set_clone (pcs[i]->specs, &sss);
6028             }
6029           ctables_summary_spec_set_uninit (&sss);
6030         }
6031       else if (lex_match_id (lexer, "HIDESOURCECATS"))
6032         {
6033           lex_match (lexer, T_EQUALS);
6034           bool hide_source_cats;
6035           if (!parse_bool (lexer, &hide_source_cats))
6036             goto error;
6037           for (size_t i = 0; i < n_pcs; i++)
6038             pcs[i]->hide_source_cats = hide_source_cats;
6039         }
6040       else
6041         {
6042           lex_error_expecting (lexer, "LABEL", "FORMAT", "HIDESOURCECATS");
6043           goto error;
6044         }
6045     }
6046   free (pcs);
6047   return true;
6048
6049 error:
6050   free (pcs);
6051   return false;
6052 }
6053
6054 static void
6055 put_strftime (struct string *out, time_t now, const char *format)
6056 {
6057   const struct tm *tm = localtime (&now);
6058   char value[128];
6059   strftime (value, sizeof value, format, tm);
6060   ds_put_cstr (out, value);
6061 }
6062
6063 static bool
6064 skip_prefix (struct substring *s, struct substring prefix)
6065 {
6066   if (ss_starts_with (*s, prefix))
6067     {
6068       ss_advance (s, prefix.length);
6069       return true;
6070     }
6071   else
6072     return false;
6073 }
6074
6075 static void
6076 put_table_expression (struct string *out, struct lexer *lexer,
6077                       struct dictionary *dict, int expr_start, int expr_end)
6078 {
6079   size_t nest = 0;
6080   for (int ofs = expr_start; ofs < expr_end; ofs++)
6081     {
6082       const struct token *t = lex_ofs_token (lexer, ofs);
6083       if (t->type == T_LBRACK)
6084         nest++;
6085       else if (t->type == T_RBRACK && nest > 0)
6086         nest--;
6087       else if (nest > 0)
6088         {
6089           /* Nothing. */
6090         }
6091       else if (t->type == T_ID)
6092         {
6093           const struct variable *var
6094             = dict_lookup_var (dict, t->string.string);
6095           const char *label = var ? var_get_label (var) : NULL;
6096           ds_put_cstr (out, label ? label : t->string.string);
6097         }
6098       else
6099         {
6100           if (ofs != expr_start && t->type != T_RPAREN && ds_last (out) != ' ')
6101             ds_put_byte (out, ' ');
6102
6103           char *repr = lex_ofs_representation (lexer, ofs, ofs);
6104           ds_put_cstr (out, repr);
6105           free (repr);
6106
6107           if (ofs + 1 != expr_end && t->type != T_LPAREN)
6108             ds_put_byte (out, ' ');
6109         }
6110     }
6111 }
6112
6113 static void
6114 put_title_text (struct string *out, struct substring in, time_t now,
6115                 struct lexer *lexer, struct dictionary *dict,
6116                 int expr_start, int expr_end)
6117 {
6118   for (;;)
6119     {
6120       size_t chunk = ss_find_byte (in, ')');
6121       ds_put_substring (out, ss_head (in, chunk));
6122       ss_advance (&in, chunk);
6123       if (ss_is_empty (in))
6124         return;
6125
6126       if (skip_prefix (&in, ss_cstr (")DATE")))
6127         put_strftime (out, now, "%x");
6128       else if (skip_prefix (&in, ss_cstr (")TIME")))
6129         put_strftime (out, now, "%X");
6130       else if (skip_prefix (&in, ss_cstr (")TABLE")))
6131         put_table_expression (out, lexer, dict, expr_start, expr_end);
6132       else
6133         {
6134           ds_put_byte (out, ')');
6135           ss_advance (&in, 1);
6136         }
6137     }
6138 }
6139
6140 int
6141 cmd_ctables (struct lexer *lexer, struct dataset *ds)
6142 {
6143   struct casereader *input = NULL;
6144
6145   struct measure_guesser *mg = measure_guesser_create (ds);
6146   if (mg)
6147     {
6148       input = proc_open (ds);
6149       measure_guesser_run (mg, input);
6150       measure_guesser_destroy (mg);
6151     }
6152
6153   size_t n_vars = dict_get_n_vars (dataset_dict (ds));
6154   enum ctables_vlabel *vlabels = xnmalloc (n_vars, sizeof *vlabels);
6155   enum settings_value_show tvars = settings_get_show_variables ();
6156   for (size_t i = 0; i < n_vars; i++)
6157     vlabels[i] = (enum ctables_vlabel) tvars;
6158
6159   struct pivot_table_look *look = pivot_table_look_unshare (
6160     pivot_table_look_ref (pivot_table_look_get_default ()));
6161   look->omit_empty = false;
6162
6163   struct ctables *ct = xmalloc (sizeof *ct);
6164   *ct = (struct ctables) {
6165     .dict = dataset_dict (ds),
6166     .look = look,
6167     .ctables_formats = FMT_SETTINGS_INIT,
6168     .vlabels = vlabels,
6169     .postcomputes = HMAP_INITIALIZER (ct->postcomputes),
6170   };
6171
6172   time_t now = time (NULL);
6173
6174   struct ctf
6175     {
6176       enum fmt_type type;
6177       const char *dot_string;
6178       const char *comma_string;
6179     };
6180   static const struct ctf ctfs[4] = {
6181     { CTEF_NEGPAREN, "(,,,)",   "(...)" },
6182     { CTEF_NEQUAL,   "-,N=,,",  "-.N=.." },
6183     { CTEF_PAREN,    "-,(,),",  "-.(.)." },
6184     { CTEF_PCTPAREN, "-,(,%),", "-.(.%)." },
6185   };
6186   bool is_dot = settings_get_fmt_settings ()->decimal == '.';
6187   for (size_t i = 0; i < 4; i++)
6188     {
6189       const char *s = is_dot ? ctfs[i].dot_string : ctfs[i].comma_string;
6190       fmt_settings_set_cc (&ct->ctables_formats, ctfs[i].type,
6191                            fmt_number_style_from_string (s));
6192     }
6193
6194   if (!lex_force_match (lexer, T_SLASH))
6195     goto error;
6196
6197   while (!lex_match_id (lexer, "TABLE"))
6198     {
6199       if (lex_match_id (lexer, "FORMAT"))
6200         {
6201           double widths[2] = { SYSMIS, SYSMIS };
6202           double units_per_inch = 72.0;
6203
6204           while (lex_token (lexer) != T_SLASH)
6205             {
6206               if (lex_match_id (lexer, "MINCOLWIDTH"))
6207                 {
6208                   if (!parse_col_width (lexer, "MINCOLWIDTH", &widths[0]))
6209                     goto error;
6210                 }
6211               else if (lex_match_id (lexer, "MAXCOLWIDTH"))
6212                 {
6213                   if (!parse_col_width (lexer, "MAXCOLWIDTH", &widths[1]))
6214                     goto error;
6215                 }
6216               else if (lex_match_id (lexer, "UNITS"))
6217                 {
6218                   lex_match (lexer, T_EQUALS);
6219                   if (lex_match_id (lexer, "POINTS"))
6220                     units_per_inch = 72.0;
6221                   else if (lex_match_id (lexer, "INCHES"))
6222                     units_per_inch = 1.0;
6223                   else if (lex_match_id (lexer, "CM"))
6224                     units_per_inch = 2.54;
6225                   else
6226                     {
6227                       lex_error_expecting (lexer, "POINTS", "INCHES", "CM");
6228                       goto error;
6229                     }
6230                 }
6231               else if (lex_match_id (lexer, "EMPTY"))
6232                 {
6233                   free (ct->zero);
6234                   ct->zero = NULL;
6235
6236                   lex_match (lexer, T_EQUALS);
6237                   if (lex_match_id (lexer, "ZERO"))
6238                     {
6239                       /* Nothing to do. */
6240                     }
6241                   else if (lex_match_id (lexer, "BLANK"))
6242                     ct->zero = xstrdup ("");
6243                   else if (lex_force_string (lexer))
6244                     {
6245                       ct->zero = ss_xstrdup (lex_tokss (lexer));
6246                       lex_get (lexer);
6247                     }
6248                   else
6249                     goto error;
6250                 }
6251               else if (lex_match_id (lexer, "MISSING"))
6252                 {
6253                   lex_match (lexer, T_EQUALS);
6254                   if (!lex_force_string (lexer))
6255                     goto error;
6256
6257                   free (ct->missing);
6258                   ct->missing = (strcmp (lex_tokcstr (lexer), ".")
6259                                  ? ss_xstrdup (lex_tokss (lexer))
6260                                  : NULL);
6261                   lex_get (lexer);
6262                 }
6263               else
6264                 {
6265                   lex_error_expecting (lexer, "MINCOLWIDTH", "MAXCOLWIDTH",
6266                                        "UNITS", "EMPTY", "MISSING");
6267                   goto error;
6268                 }
6269             }
6270
6271           if (widths[0] != SYSMIS && widths[1] != SYSMIS
6272               && widths[0] > widths[1])
6273             {
6274               msg (SE, _("MINCOLWIDTH must not be greater than MAXCOLWIDTH."));
6275               goto error;
6276             }
6277
6278           for (size_t i = 0; i < 2; i++)
6279             if (widths[i] != SYSMIS)
6280               {
6281                 int *wr = ct->look->width_ranges[TABLE_HORZ];
6282                 wr[i] = widths[i] / units_per_inch * 96.0;
6283                 if (wr[0] > wr[1])
6284                   wr[!i] = wr[i];
6285               }
6286         }
6287       else if (lex_match_id (lexer, "VLABELS"))
6288         {
6289           if (!lex_force_match_id (lexer, "VARIABLES"))
6290             goto error;
6291           lex_match (lexer, T_EQUALS);
6292
6293           struct variable **vars;
6294           size_t n_vars;
6295           if (!parse_variables (lexer, dataset_dict (ds), &vars, &n_vars,
6296                                 PV_NO_SCRATCH))
6297             goto error;
6298
6299           if (!lex_force_match_id (lexer, "DISPLAY"))
6300             {
6301               free (vars);
6302               goto error;
6303             }
6304           lex_match (lexer, T_EQUALS);
6305
6306           enum ctables_vlabel vlabel;
6307           if (lex_match_id (lexer, "DEFAULT"))
6308             vlabel = (enum ctables_vlabel) settings_get_show_variables ();
6309           else if (lex_match_id (lexer, "NAME"))
6310             vlabel = CTVL_NAME;
6311           else if (lex_match_id (lexer, "LABEL"))
6312             vlabel = CTVL_LABEL;
6313           else if (lex_match_id (lexer, "BOTH"))
6314             vlabel = CTVL_BOTH;
6315           else if (lex_match_id (lexer, "NONE"))
6316             vlabel = CTVL_NONE;
6317           else
6318             {
6319               lex_error_expecting (lexer, "DEFAULT", "NAME", "LABEL",
6320                                    "BOTH", "NONE");
6321               free (vars);
6322               goto error;
6323             }
6324
6325           for (size_t i = 0; i < n_vars; i++)
6326             ct->vlabels[var_get_dict_index (vars[i])] = vlabel;
6327           free (vars);
6328         }
6329       else if (lex_match_id (lexer, "MRSETS"))
6330         {
6331           if (!lex_force_match_id (lexer, "COUNTDUPLICATES"))
6332             goto error;
6333           lex_match (lexer, T_EQUALS);
6334           if (!parse_bool (lexer, &ct->mrsets_count_duplicates))
6335             goto error;
6336         }
6337       else if (lex_match_id (lexer, "SMISSING"))
6338         {
6339           if (lex_match_id (lexer, "VARIABLE"))
6340             ct->smissing_listwise = false;
6341           else if (lex_match_id (lexer, "LISTWISE"))
6342             ct->smissing_listwise = true;
6343           else
6344             {
6345               lex_error_expecting (lexer, "VARIABLE", "LISTWISE");
6346               goto error;
6347             }
6348         }
6349       else if (lex_match_id (lexer, "PCOMPUTE"))
6350         {
6351           if (!ctables_parse_pcompute (lexer, dataset_dict (ds), ct))
6352             goto error;
6353         }
6354       else if (lex_match_id (lexer, "PPROPERTIES"))
6355         {
6356           if (!ctables_parse_pproperties (lexer, ct))
6357             goto error;
6358         }
6359       else if (lex_match_id (lexer, "WEIGHT"))
6360         {
6361           if (!lex_force_match_id (lexer, "VARIABLE"))
6362             goto error;
6363           lex_match (lexer, T_EQUALS);
6364           ct->e_weight = parse_variable (lexer, dataset_dict (ds));
6365           if (!ct->e_weight)
6366             goto error;
6367         }
6368       else if (lex_match_id (lexer, "HIDESMALLCOUNTS"))
6369         {
6370           if (lex_match_id (lexer, "COUNT"))
6371             {
6372               lex_match (lexer, T_EQUALS);
6373               if (!lex_force_int_range (lexer, "HIDESMALLCOUNTS COUNT",
6374                                         2, INT_MAX))
6375                 goto error;
6376               ct->hide_threshold = lex_integer (lexer);
6377               lex_get (lexer);
6378             }
6379           else if (ct->hide_threshold == 0)
6380             ct->hide_threshold = 5;
6381         }
6382       else
6383         {
6384           lex_error_expecting (lexer, "FORMAT", "VLABELS", "MRSETS",
6385                                "SMISSING", "PCOMPUTE", "PPROPERTIES",
6386                                "WEIGHT", "HIDESMALLCOUNTS", "TABLE");
6387           goto error;
6388         }
6389
6390       if (!lex_force_match (lexer, T_SLASH))
6391         goto error;
6392     }
6393
6394   size_t allocated_tables = 0;
6395   do
6396     {
6397       if (ct->n_tables >= allocated_tables)
6398         ct->tables = x2nrealloc (ct->tables, &allocated_tables,
6399                                  sizeof *ct->tables);
6400
6401       struct ctables_category *cat = xmalloc (sizeof *cat);
6402       *cat = (struct ctables_category) {
6403         .type = CCT_VALUE,
6404         .include_missing = false,
6405         .sort_ascending = true,
6406       };
6407
6408       struct ctables_categories *c = xmalloc (sizeof *c);
6409       size_t n_vars = dict_get_n_vars (dataset_dict (ds));
6410       *c = (struct ctables_categories) {
6411         .n_refs = n_vars,
6412         .cats = cat,
6413         .n_cats = 1,
6414         .show_empty = true,
6415       };
6416
6417       struct ctables_categories **categories = xnmalloc (n_vars,
6418                                                          sizeof *categories);
6419       for (size_t i = 0; i < n_vars; i++)
6420         categories[i] = c;
6421
6422       struct ctables_table *t = xmalloc (sizeof *t);
6423       *t = (struct ctables_table) {
6424         .ctables = ct,
6425         .slabels_axis = PIVOT_AXIS_COLUMN,
6426         .slabels_visible = true,
6427         .clabels_values_map = HMAP_INITIALIZER (t->clabels_values_map),
6428         .label_axis = {
6429           [PIVOT_AXIS_ROW] = PIVOT_AXIS_ROW,
6430           [PIVOT_AXIS_COLUMN] = PIVOT_AXIS_COLUMN,
6431           [PIVOT_AXIS_LAYER] = PIVOT_AXIS_LAYER,
6432         },
6433         .clabels_from_axis = PIVOT_AXIS_LAYER,
6434         .categories = categories,
6435         .n_categories = n_vars,
6436         .cilevel = 95,
6437       };
6438       ct->tables[ct->n_tables++] = t;
6439
6440       lex_match (lexer, T_EQUALS);
6441       int expr_start = lex_ofs (lexer);
6442       if (!ctables_axis_parse (lexer, dataset_dict (ds), ct, t, PIVOT_AXIS_ROW))
6443         goto error;
6444       if (lex_match (lexer, T_BY))
6445         {
6446           if (!ctables_axis_parse (lexer, dataset_dict (ds),
6447                                    ct, t, PIVOT_AXIS_COLUMN))
6448             goto error;
6449
6450           if (lex_match (lexer, T_BY))
6451             {
6452               if (!ctables_axis_parse (lexer, dataset_dict (ds),
6453                                        ct, t, PIVOT_AXIS_LAYER))
6454                 goto error;
6455             }
6456         }
6457       int expr_end = lex_ofs (lexer);
6458
6459       if (!t->axes[PIVOT_AXIS_ROW] && !t->axes[PIVOT_AXIS_COLUMN]
6460           && !t->axes[PIVOT_AXIS_LAYER])
6461         {
6462           lex_error (lexer, _("At least one variable must be specified."));
6463           goto error;
6464         }
6465
6466       const struct ctables_axis *scales[PIVOT_N_AXES];
6467       size_t n_scales = 0;
6468       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
6469         {
6470           scales[a] = find_scale (t->axes[a]);
6471           if (scales[a])
6472             n_scales++;
6473         }
6474       if (n_scales > 1)
6475         {
6476           msg (SE, _("Scale variables may appear only on one axis."));
6477           if (scales[PIVOT_AXIS_ROW])
6478             msg_at (SN, scales[PIVOT_AXIS_ROW]->loc,
6479                     _("This scale variable appears on the rows axis."));
6480           if (scales[PIVOT_AXIS_COLUMN])
6481             msg_at (SN, scales[PIVOT_AXIS_COLUMN]->loc,
6482                     _("This scale variable appears on the columns axis."));
6483           if (scales[PIVOT_AXIS_LAYER])
6484             msg_at (SN, scales[PIVOT_AXIS_LAYER]->loc,
6485                     _("This scale variable appears on the layer axis."));
6486           goto error;
6487         }
6488
6489       const struct ctables_axis *summaries[PIVOT_N_AXES];
6490       size_t n_summaries = 0;
6491       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
6492         {
6493           summaries[a] = (scales[a]
6494                           ? scales[a]
6495                           : find_categorical_summary_spec (t->axes[a]));
6496           if (summaries[a])
6497             n_summaries++;
6498         }
6499       if (n_summaries > 1)
6500         {
6501           msg (SE, _("Summaries may appear only on one axis."));
6502           for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
6503             if (summaries[a])
6504               {
6505                 msg_at (SN, summaries[a]->loc,
6506                         a == PIVOT_AXIS_ROW
6507                         ? _("This variable on the rows axis has a summary.")
6508                         : a == PIVOT_AXIS_COLUMN
6509                         ? _("This variable on the columns axis has a summary.")
6510                         : _("This variable on the layers axis has a summary."));
6511                 if (scales[a])
6512                   msg_at (SN, summaries[a]->loc,
6513                           _("This is a scale variable, so it always has a "
6514                             "summary even if the syntax does not explicitly "
6515                             "specify one."));
6516               }
6517           goto error;
6518         }
6519       for (enum pivot_axis_type a = 0; a < PIVOT_N_AXES; a++)
6520         if (n_summaries ? summaries[a] : t->axes[a])
6521           {
6522             t->summary_axis = a;
6523             break;
6524           }
6525
6526       if (lex_token (lexer) == T_ENDCMD)
6527         {
6528           if (!ctables_prepare_table (t))
6529             goto error;
6530           break;
6531         }
6532       if (!lex_force_match (lexer, T_SLASH))
6533         goto error;
6534
6535       while (!lex_match_id (lexer, "TABLE") && lex_token (lexer) != T_ENDCMD)
6536         {
6537           if (lex_match_id (lexer, "SLABELS"))
6538             {
6539               while (lex_token (lexer) != T_SLASH && lex_token (lexer) != T_ENDCMD)
6540                 {
6541                   if (lex_match_id (lexer, "POSITION"))
6542                     {
6543                       lex_match (lexer, T_EQUALS);
6544                       if (lex_match_id (lexer, "COLUMN"))
6545                         t->slabels_axis = PIVOT_AXIS_COLUMN;
6546                       else if (lex_match_id (lexer, "ROW"))
6547                         t->slabels_axis = PIVOT_AXIS_ROW;
6548                       else if (lex_match_id (lexer, "LAYER"))
6549                         t->slabels_axis = PIVOT_AXIS_LAYER;
6550                       else
6551                         {
6552                           lex_error_expecting (lexer, "COLUMN", "ROW", "LAYER");
6553                           goto error;
6554                         }
6555                     }
6556                   else if (lex_match_id (lexer, "VISIBLE"))
6557                     {
6558                       lex_match (lexer, T_EQUALS);
6559                       if (!parse_bool (lexer, &t->slabels_visible))
6560                         goto error;
6561                     }
6562                   else
6563                     {
6564                       lex_error_expecting (lexer, "POSITION", "VISIBLE");
6565                       goto error;
6566                     }
6567                 }
6568             }
6569           else if (lex_match_id (lexer, "CLABELS"))
6570             {
6571               if (lex_match_id (lexer, "AUTO"))
6572                 {
6573                   t->label_axis[PIVOT_AXIS_ROW] = PIVOT_AXIS_ROW;
6574                   t->label_axis[PIVOT_AXIS_COLUMN] = PIVOT_AXIS_COLUMN;
6575                 }
6576               else if (lex_match_id (lexer, "ROWLABELS"))
6577                 {
6578                   lex_match (lexer, T_EQUALS);
6579                   if (lex_match_id (lexer, "OPPOSITE"))
6580                     t->label_axis[PIVOT_AXIS_ROW] = PIVOT_AXIS_COLUMN;
6581                   else if (lex_match_id (lexer, "LAYER"))
6582                     t->label_axis[PIVOT_AXIS_ROW] = PIVOT_AXIS_LAYER;
6583                   else
6584                     {
6585                       lex_error_expecting (lexer, "OPPOSITE", "LAYER");
6586                       goto error;
6587                     }
6588                 }
6589               else if (lex_match_id (lexer, "COLLABELS"))
6590                 {
6591                   lex_match (lexer, T_EQUALS);
6592                   if (lex_match_id (lexer, "OPPOSITE"))
6593                     t->label_axis[PIVOT_AXIS_COLUMN] = PIVOT_AXIS_ROW;
6594                   else if (lex_match_id (lexer, "LAYER"))
6595                     t->label_axis[PIVOT_AXIS_COLUMN] = PIVOT_AXIS_LAYER;
6596                   else
6597                     {
6598                       lex_error_expecting (lexer, "OPPOSITE", "LAYER");
6599                       goto error;
6600                     }
6601                 }
6602               else
6603                 {
6604                   lex_error_expecting (lexer, "AUTO", "ROWLABELS",
6605                                        "COLLABELS");
6606                   goto error;
6607                 }
6608             }
6609           else if (lex_match_id (lexer, "CRITERIA"))
6610             {
6611               if (!lex_force_match_id (lexer, "CILEVEL"))
6612                 goto error;
6613               lex_match (lexer, T_EQUALS);
6614
6615               if (!lex_force_num_range_halfopen (lexer, "CILEVEL", 0, 100))
6616                 goto error;
6617               t->cilevel = lex_number (lexer);
6618               lex_get (lexer);
6619             }
6620           else if (lex_match_id (lexer, "CATEGORIES"))
6621             {
6622               if (!ctables_table_parse_categories (lexer, dataset_dict (ds),
6623                                                    ct, t))
6624                 goto error;
6625             }
6626           else if (lex_match_id (lexer, "TITLES"))
6627             {
6628               do
6629                 {
6630                   char **textp;
6631                   if (lex_match_id (lexer, "CAPTION"))
6632                     textp = &t->caption;
6633                   else if (lex_match_id (lexer, "CORNER"))
6634                     textp = &t->corner;
6635                   else if (lex_match_id (lexer, "TITLE"))
6636                     textp = &t->title;
6637                   else
6638                     {
6639                       lex_error_expecting (lexer, "CAPTION", "CORNER", "TITLE");
6640                       goto error;
6641                     }
6642                   lex_match (lexer, T_EQUALS);
6643
6644                   struct string s = DS_EMPTY_INITIALIZER;
6645                   while (lex_is_string (lexer))
6646                     {
6647                       if (!ds_is_empty (&s))
6648                         ds_put_byte (&s, ' ');
6649                       put_title_text (&s, lex_tokss (lexer), now,
6650                                       lexer, dataset_dict (ds),
6651                                       expr_start, expr_end);
6652                       lex_get (lexer);
6653                     }
6654                   free (*textp);
6655                   *textp = ds_steal_cstr (&s);
6656                 }
6657               while (lex_token (lexer) != T_SLASH
6658                      && lex_token (lexer) != T_ENDCMD);
6659             }
6660           else if (lex_match_id (lexer, "SIGTEST"))
6661             {
6662               if (!t->chisq)
6663                 {
6664                   t->chisq = xmalloc (sizeof *t->chisq);
6665                   *t->chisq = (struct ctables_chisq) {
6666                     .alpha = .05,
6667                     .include_mrsets = true,
6668                     .all_visible = true,
6669                   };
6670                 }
6671
6672               do
6673                 {
6674                   if (lex_match_id (lexer, "TYPE"))
6675                     {
6676                       lex_match (lexer, T_EQUALS);
6677                       if (!lex_force_match_id (lexer, "CHISQUARE"))
6678                         goto error;
6679                     }
6680                   else if (lex_match_id (lexer, "ALPHA"))
6681                     {
6682                       lex_match (lexer, T_EQUALS);
6683                       if (!lex_force_num_range_halfopen (lexer, "ALPHA", 0, 1))
6684                         goto error;
6685                       t->chisq->alpha = lex_number (lexer);
6686                       lex_get (lexer);
6687                     }
6688                   else if (lex_match_id (lexer, "INCLUDEMRSETS"))
6689                     {
6690                       lex_match (lexer, T_EQUALS);
6691                       if (!parse_bool (lexer, &t->chisq->include_mrsets))
6692                         goto error;
6693                     }
6694                   else if (lex_match_id (lexer, "CATEGORIES"))
6695                     {
6696                       lex_match (lexer, T_EQUALS);
6697                       if (lex_match_id (lexer, "ALLVISIBLE"))
6698                         t->chisq->all_visible = true;
6699                       else if (lex_match_id (lexer, "SUBTOTALS"))
6700                         t->chisq->all_visible = false;
6701                       else
6702                         {
6703                           lex_error_expecting (lexer,
6704                                                "ALLVISIBLE", "SUBTOTALS");
6705                           goto error;
6706                         }
6707                     }
6708                   else
6709                     {
6710                       lex_error_expecting (lexer, "TYPE", "ALPHA",
6711                                            "INCLUDEMRSETS", "CATEGORIES");
6712                       goto error;
6713                     }
6714                 }
6715               while (lex_token (lexer) != T_SLASH
6716                      && lex_token (lexer) != T_ENDCMD);
6717             }
6718           else if (lex_match_id (lexer, "COMPARETEST"))
6719             {
6720               if (!t->pairwise)
6721                 {
6722                   t->pairwise = xmalloc (sizeof *t->pairwise);
6723                   *t->pairwise = (struct ctables_pairwise) {
6724                     .type = PROP,
6725                     .alpha = { .05, .05 },
6726                     .adjust = BONFERRONI,
6727                     .include_mrsets = true,
6728                     .meansvariance_allcats = true,
6729                     .all_visible = true,
6730                     .merge = false,
6731                     .apa_style = true,
6732                     .show_sig = false,
6733                   };
6734                 }
6735
6736               do
6737                 {
6738                   if (lex_match_id (lexer, "TYPE"))
6739                     {
6740                       lex_match (lexer, T_EQUALS);
6741                       if (lex_match_id (lexer, "PROP"))
6742                         t->pairwise->type = PROP;
6743                       else if (lex_match_id (lexer, "MEAN"))
6744                         t->pairwise->type = MEAN;
6745                       else
6746                         {
6747                           lex_error_expecting (lexer, "PROP", "MEAN");
6748                           goto error;
6749                         }
6750                     }
6751                   else if (lex_match_id (lexer, "ALPHA"))
6752                     {
6753                       lex_match (lexer, T_EQUALS);
6754
6755                       if (!lex_force_num_range_open (lexer, "ALPHA", 0, 1))
6756                         goto error;
6757                       double a0 = lex_number (lexer);
6758                       lex_get (lexer);
6759
6760                       lex_match (lexer, T_COMMA);
6761                       if (lex_is_number (lexer))
6762                         {
6763                           if (!lex_force_num_range_open (lexer, "ALPHA", 0, 1))
6764                             goto error;
6765                           double a1 = lex_number (lexer);
6766                           lex_get (lexer);
6767
6768                           t->pairwise->alpha[0] = MIN (a0, a1);
6769                           t->pairwise->alpha[1] = MAX (a0, a1);
6770                         }
6771                       else
6772                         t->pairwise->alpha[0] = t->pairwise->alpha[1] = a0;
6773                     }
6774                   else if (lex_match_id (lexer, "ADJUST"))
6775                     {
6776                       lex_match (lexer, T_EQUALS);
6777                       if (lex_match_id (lexer, "BONFERRONI"))
6778                         t->pairwise->adjust = BONFERRONI;
6779                       else if (lex_match_id (lexer, "BH"))
6780                         t->pairwise->adjust = BH;
6781                       else if (lex_match_id (lexer, "NONE"))
6782                         t->pairwise->adjust = 0;
6783                       else
6784                         {
6785                           lex_error_expecting (lexer, "BONFERRONI", "BH",
6786                                                "NONE");
6787                           goto error;
6788                         }
6789                     }
6790                   else if (lex_match_id (lexer, "INCLUDEMRSETS"))
6791                     {
6792                       lex_match (lexer, T_EQUALS);
6793                       if (!parse_bool (lexer, &t->pairwise->include_mrsets))
6794                         goto error;
6795                     }
6796                   else if (lex_match_id (lexer, "MEANSVARIANCE"))
6797                     {
6798                       lex_match (lexer, T_EQUALS);
6799                       if (lex_match_id (lexer, "ALLCATS"))
6800                         t->pairwise->meansvariance_allcats = true;
6801                       else if (lex_match_id (lexer, "TESTEDCATS"))
6802                         t->pairwise->meansvariance_allcats = false;
6803                       else
6804                         {
6805                           lex_error_expecting (lexer, "ALLCATS", "TESTEDCATS");
6806                           goto error;
6807                         }
6808                     }
6809                   else if (lex_match_id (lexer, "CATEGORIES"))
6810                     {
6811                       lex_match (lexer, T_EQUALS);
6812                       if (lex_match_id (lexer, "ALLVISIBLE"))
6813                         t->pairwise->all_visible = true;
6814                       else if (lex_match_id (lexer, "SUBTOTALS"))
6815                         t->pairwise->all_visible = false;
6816                       else
6817                         {
6818                           lex_error_expecting (lexer, "ALLVISIBLE",
6819                                                "SUBTOTALS");
6820                           goto error;
6821                         }
6822                     }
6823                   else if (lex_match_id (lexer, "MERGE"))
6824                     {
6825                       lex_match (lexer, T_EQUALS);
6826                       if (!parse_bool (lexer, &t->pairwise->merge))
6827                         goto error;
6828                     }
6829                   else if (lex_match_id (lexer, "STYLE"))
6830                     {
6831                       lex_match (lexer, T_EQUALS);
6832                       if (lex_match_id (lexer, "APA"))
6833                         t->pairwise->apa_style = true;
6834                       else if (lex_match_id (lexer, "SIMPLE"))
6835                         t->pairwise->apa_style = false;
6836                       else
6837                         {
6838                           lex_error_expecting (lexer, "APA", "SIMPLE");
6839                           goto error;
6840                         }
6841                     }
6842                   else if (lex_match_id (lexer, "SHOWSIG"))
6843                     {
6844                       lex_match (lexer, T_EQUALS);
6845                       if (!parse_bool (lexer, &t->pairwise->show_sig))
6846                         goto error;
6847                     }
6848                   else
6849                     {
6850                       lex_error_expecting (lexer, "TYPE", "ALPHA", "ADJUST",
6851                                            "INCLUDEMRSETS", "MEANSVARIANCE",
6852                                            "CATEGORIES", "MERGE", "STYLE",
6853                                            "SHOWSIG");
6854                       goto error;
6855                     }
6856                 }
6857               while (lex_token (lexer) != T_SLASH
6858                      && lex_token (lexer) != T_ENDCMD);
6859             }
6860           else
6861             {
6862               lex_error_expecting (lexer, "TABLE", "SLABELS", "CLABELS",
6863                                    "CRITERIA", "CATEGORIES", "TITLES",
6864                                    "SIGTEST", "COMPARETEST");
6865               goto error;
6866             }
6867
6868           if (!lex_match (lexer, T_SLASH))
6869             break;
6870         }
6871
6872       if (t->label_axis[PIVOT_AXIS_ROW] != PIVOT_AXIS_ROW
6873           && t->label_axis[PIVOT_AXIS_COLUMN] != PIVOT_AXIS_COLUMN)
6874         {
6875           msg (SE, _("ROWLABELS and COLLABELS may not both be specified."));
6876           goto error;
6877         }
6878
6879       if (!ctables_prepare_table (t))
6880         goto error;
6881     }
6882   while (lex_token (lexer) != T_ENDCMD);
6883
6884   if (!input)
6885     input = proc_open (ds);
6886   bool ok = ctables_execute (ds, input, ct);
6887   ok = proc_commit (ds) && ok;
6888
6889   ctables_destroy (ct);
6890   return ok ? CMD_SUCCESS : CMD_FAILURE;
6891
6892 error:
6893   if (input)
6894     proc_commit (ds);
6895   ctables_destroy (ct);
6896   return CMD_FAILURE;
6897 }
6898