OSDN Git Service

8fc2a6c37be7ba6689e52d530e424feff80c91a5
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various stuctures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006 Free Software Foundation, 
3    Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 2, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING.  If not, write to the Free
20 Software Foundation, 51 Franklin Street, Fifth Floor,Boston, MA
21 02110-1301, USA.  */
22
23
24 #include "config.h"
25 #include "system.h"
26 #include "flags.h"
27 #include "gfortran.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30
31 /* Types used in equivalence statements.  */
32
33 typedef enum seq_type
34 {
35   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
36 }
37 seq_type;
38
39 /* Stack to push the current if we descend into a block during
40    resolution.  See resolve_branch() and resolve_code().  */
41
42 typedef struct code_stack
43 {
44   struct gfc_code *head, *current;
45   struct code_stack *prev;
46 }
47 code_stack;
48
49 static code_stack *cs_base = NULL;
50
51
52 /* Nonzero if we're inside a FORALL block.  */
53
54 static int forall_flag;
55
56 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
57
58 static int omp_workshare_flag;
59
60 /* Nonzero if we are processing a formal arglist. The corresponding function
61    resets the flag each time that it is read.  */
62 static int formal_arg_flag = 0;
63
64 /* True if we are resolving a specification expression.  */
65 static int specification_expr = 0;
66
67 /* The id of the last entry seen.  */
68 static int current_entry_id;
69
70 int
71 gfc_is_formal_arg (void)
72 {
73   return formal_arg_flag;
74 }
75
76 /* Resolve types of formal argument lists.  These have to be done early so that
77    the formal argument lists of module procedures can be copied to the
78    containing module before the individual procedures are resolved
79    individually.  We also resolve argument lists of procedures in interface
80    blocks because they are self-contained scoping units.
81
82    Since a dummy argument cannot be a non-dummy procedure, the only
83    resort left for untyped names are the IMPLICIT types.  */
84
85 static void
86 resolve_formal_arglist (gfc_symbol * proc)
87 {
88   gfc_formal_arglist *f;
89   gfc_symbol *sym;
90   int i;
91
92   /* TODO: Procedures whose return character length parameter is not constant
93      or assumed must also have explicit interfaces.  */
94   if (proc->result != NULL)
95     sym = proc->result;
96   else
97     sym = proc;
98
99   if (gfc_elemental (proc)
100       || sym->attr.pointer || sym->attr.allocatable
101       || (sym->as && sym->as->rank > 0))
102     proc->attr.always_explicit = 1;
103
104   formal_arg_flag = 1;
105
106   for (f = proc->formal; f; f = f->next)
107     {
108       sym = f->sym;
109
110       if (sym == NULL)
111         {
112           /* Alternate return placeholder.  */
113           if (gfc_elemental (proc))
114             gfc_error ("Alternate return specifier in elemental subroutine "
115                        "'%s' at %L is not allowed", proc->name,
116                        &proc->declared_at);
117           if (proc->attr.function)
118             gfc_error ("Alternate return specifier in function "
119                        "'%s' at %L is not allowed", proc->name,
120                        &proc->declared_at);
121           continue;
122         }
123
124       if (sym->attr.if_source != IFSRC_UNKNOWN)
125         resolve_formal_arglist (sym);
126
127       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
128         {
129           if (gfc_pure (proc) && !gfc_pure (sym))
130             {
131               gfc_error
132                 ("Dummy procedure '%s' of PURE procedure at %L must also "
133                  "be PURE", sym->name, &sym->declared_at);
134               continue;
135             }
136
137           if (gfc_elemental (proc))
138             {
139               gfc_error
140                 ("Dummy procedure at %L not allowed in ELEMENTAL procedure",
141                  &sym->declared_at);
142               continue;
143             }
144
145           continue;
146         }
147
148       if (sym->ts.type == BT_UNKNOWN)
149         {
150           if (!sym->attr.function || sym->result == sym)
151             gfc_set_default_type (sym, 1, sym->ns);
152         }
153
154       gfc_resolve_array_spec (sym->as, 0);
155
156       /* We can't tell if an array with dimension (:) is assumed or deferred
157          shape until we know if it has the pointer or allocatable attributes.
158       */
159       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
160           && !(sym->attr.pointer || sym->attr.allocatable))
161         {
162           sym->as->type = AS_ASSUMED_SHAPE;
163           for (i = 0; i < sym->as->rank; i++)
164             sym->as->lower[i] = gfc_int_expr (1);
165         }
166
167       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
168           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
169           || sym->attr.optional)
170         proc->attr.always_explicit = 1;
171
172       /* If the flavor is unknown at this point, it has to be a variable.
173          A procedure specification would have already set the type.  */
174
175       if (sym->attr.flavor == FL_UNKNOWN)
176         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
177
178       if (gfc_pure (proc))
179         {
180           if (proc->attr.function && !sym->attr.pointer
181               && sym->attr.flavor != FL_PROCEDURE
182               && sym->attr.intent != INTENT_IN)
183
184             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
185                        "INTENT(IN)", sym->name, proc->name,
186                        &sym->declared_at);
187
188           if (proc->attr.subroutine && !sym->attr.pointer
189               && sym->attr.intent == INTENT_UNKNOWN)
190
191             gfc_error
192               ("Argument '%s' of pure subroutine '%s' at %L must have "
193                "its INTENT specified", sym->name, proc->name,
194                &sym->declared_at);
195         }
196
197
198       if (gfc_elemental (proc))
199         {
200           if (sym->as != NULL)
201             {
202               gfc_error
203                 ("Argument '%s' of elemental procedure at %L must be scalar",
204                  sym->name, &sym->declared_at);
205               continue;
206             }
207
208           if (sym->attr.pointer)
209             {
210               gfc_error
211                 ("Argument '%s' of elemental procedure at %L cannot have "
212                  "the POINTER attribute", sym->name, &sym->declared_at);
213               continue;
214             }
215         }
216
217       /* Each dummy shall be specified to be scalar.  */
218       if (proc->attr.proc == PROC_ST_FUNCTION)
219         {
220           if (sym->as != NULL)
221             {
222               gfc_error
223                 ("Argument '%s' of statement function at %L must be scalar",
224                  sym->name, &sym->declared_at);
225               continue;
226             }
227
228           if (sym->ts.type == BT_CHARACTER)
229             {
230               gfc_charlen *cl = sym->ts.cl;
231               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
232                 {
233                   gfc_error
234                     ("Character-valued argument '%s' of statement function at "
235                      "%L must has constant length",
236                      sym->name, &sym->declared_at);
237                   continue;
238                 }
239             }
240         }
241     }
242   formal_arg_flag = 0;
243 }
244
245
246 /* Work function called when searching for symbols that have argument lists
247    associated with them.  */
248
249 static void
250 find_arglists (gfc_symbol * sym)
251 {
252
253   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
254     return;
255
256   resolve_formal_arglist (sym);
257 }
258
259
260 /* Given a namespace, resolve all formal argument lists within the namespace.
261  */
262
263 static void
264 resolve_formal_arglists (gfc_namespace * ns)
265 {
266
267   if (ns == NULL)
268     return;
269
270   gfc_traverse_ns (ns, find_arglists);
271 }
272
273
274 static void
275 resolve_contained_fntype (gfc_symbol * sym, gfc_namespace * ns)
276 {
277   try t;
278
279   /* If this namespace is not a function, ignore it.  */
280   if (! sym
281       || !(sym->attr.function
282            || sym->attr.flavor == FL_VARIABLE))
283     return;
284
285   /* Try to find out of what the return type is.  */
286   if (sym->result != NULL)
287     sym = sym->result;
288
289   if (sym->ts.type == BT_UNKNOWN)
290     {
291       t = gfc_set_default_type (sym, 0, ns);
292
293       if (t == FAILURE && !sym->attr.untyped)
294         {
295           gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
296                      sym->name, &sym->declared_at); /* FIXME */
297           sym->attr.untyped = 1;
298         }
299     }
300
301   /*Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character type,
302     lists the only ways a character length value of * can be used: dummy arguments
303     of procedures, named constants, and function results in external functions.
304     Internal function results are not on that list; ergo, not permitted.  */
305
306   if (sym->ts.type == BT_CHARACTER)
307     {
308       gfc_charlen *cl = sym->ts.cl;
309       if (!cl || !cl->length)
310         gfc_error ("Character-valued internal function '%s' at %L must "
311                    "not be assumed length", sym->name, &sym->declared_at);
312     }
313 }
314
315
316 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
317    introduce duplicates.  */
318
319 static void
320 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
321 {
322   gfc_formal_arglist *f, *new_arglist;
323   gfc_symbol *new_sym;
324
325   for (; new_args != NULL; new_args = new_args->next)
326     {
327       new_sym = new_args->sym;
328       /* See if this arg is already in the formal argument list.  */
329       for (f = proc->formal; f; f = f->next)
330         {
331           if (new_sym == f->sym)
332             break;
333         }
334
335       if (f)
336         continue;
337
338       /* Add a new argument.  Argument order is not important.  */
339       new_arglist = gfc_get_formal_arglist ();
340       new_arglist->sym = new_sym;
341       new_arglist->next = proc->formal;
342       proc->formal  = new_arglist;
343     }
344 }
345
346
347 /* Resolve alternate entry points.  If a symbol has multiple entry points we
348    create a new master symbol for the main routine, and turn the existing
349    symbol into an entry point.  */
350
351 static void
352 resolve_entries (gfc_namespace * ns)
353 {
354   gfc_namespace *old_ns;
355   gfc_code *c;
356   gfc_symbol *proc;
357   gfc_entry_list *el;
358   char name[GFC_MAX_SYMBOL_LEN + 1];
359   static int master_count = 0;
360
361   if (ns->proc_name == NULL)
362     return;
363
364   /* No need to do anything if this procedure doesn't have alternate entry
365      points.  */
366   if (!ns->entries)
367     return;
368
369   /* We may already have resolved alternate entry points.  */
370   if (ns->proc_name->attr.entry_master)
371     return;
372
373   /* If this isn't a procedure something has gone horribly wrong.  */
374   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
375
376   /* Remember the current namespace.  */
377   old_ns = gfc_current_ns;
378
379   gfc_current_ns = ns;
380
381   /* Add the main entry point to the list of entry points.  */
382   el = gfc_get_entry_list ();
383   el->sym = ns->proc_name;
384   el->id = 0;
385   el->next = ns->entries;
386   ns->entries = el;
387   ns->proc_name->attr.entry = 1;
388
389   /* If it is a module function, it needs to be in the right namespace
390      so that gfc_get_fake_result_decl can gather up the results. The
391      need for this arose in get_proc_name, where these beasts were
392      left in their own namespace, to keep prior references linked to
393      the entry declaration.*/
394   if (ns->proc_name->attr.function
395         && ns->parent
396         && ns->parent->proc_name->attr.flavor == FL_MODULE)
397     el->sym->ns = ns;
398
399   /* Add an entry statement for it.  */
400   c = gfc_get_code ();
401   c->op = EXEC_ENTRY;
402   c->ext.entry = el;
403   c->next = ns->code;
404   ns->code = c;
405
406   /* Create a new symbol for the master function.  */
407   /* Give the internal function a unique name (within this file).
408      Also include the function name so the user has some hope of figuring
409      out what is going on.  */
410   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
411             master_count++, ns->proc_name->name);
412   gfc_get_ha_symbol (name, &proc);
413   gcc_assert (proc != NULL);
414
415   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
416   if (ns->proc_name->attr.subroutine)
417     gfc_add_subroutine (&proc->attr, proc->name, NULL);
418   else
419     {
420       gfc_symbol *sym;
421       gfc_typespec *ts, *fts;
422       gfc_array_spec *as, *fas;
423       gfc_add_function (&proc->attr, proc->name, NULL);
424       proc->result = proc;
425       fas = ns->entries->sym->as;
426       fas = fas ? fas : ns->entries->sym->result->as;
427       fts = &ns->entries->sym->result->ts;
428       if (fts->type == BT_UNKNOWN)
429         fts = gfc_get_default_type (ns->entries->sym->result, NULL);
430       for (el = ns->entries->next; el; el = el->next)
431         {
432           ts = &el->sym->result->ts;
433           as = el->sym->as;
434           as = as ? as : el->sym->result->as;
435           if (ts->type == BT_UNKNOWN)
436             ts = gfc_get_default_type (el->sym->result, NULL);
437
438           if (! gfc_compare_types (ts, fts)
439               || (el->sym->result->attr.dimension
440                   != ns->entries->sym->result->attr.dimension)
441               || (el->sym->result->attr.pointer
442                   != ns->entries->sym->result->attr.pointer))
443             break;
444
445           else if (as && fas && gfc_compare_array_spec (as, fas) == 0)
446             gfc_error ("Procedure %s at %L has entries with mismatched "
447                        "array specifications", ns->entries->sym->name,
448                        &ns->entries->sym->declared_at);
449         }
450
451       if (el == NULL)
452         {
453           sym = ns->entries->sym->result;
454           /* All result types the same.  */
455           proc->ts = *fts;
456           if (sym->attr.dimension)
457             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
458           if (sym->attr.pointer)
459             gfc_add_pointer (&proc->attr, NULL);
460         }
461       else
462         {
463           /* Otherwise the result will be passed through a union by
464              reference.  */
465           proc->attr.mixed_entry_master = 1;
466           for (el = ns->entries; el; el = el->next)
467             {
468               sym = el->sym->result;
469               if (sym->attr.dimension)
470               {
471                 if (el == ns->entries)
472                   gfc_error
473                   ("FUNCTION result %s can't be an array in FUNCTION %s at %L",
474                    sym->name, ns->entries->sym->name, &sym->declared_at);
475                 else
476                   gfc_error
477                     ("ENTRY result %s can't be an array in FUNCTION %s at %L",
478                      sym->name, ns->entries->sym->name, &sym->declared_at);
479               }
480               else if (sym->attr.pointer)
481               {
482                 if (el == ns->entries)
483                   gfc_error
484                   ("FUNCTION result %s can't be a POINTER in FUNCTION %s at %L",
485                    sym->name, ns->entries->sym->name, &sym->declared_at);
486                 else
487                   gfc_error
488                     ("ENTRY result %s can't be a POINTER in FUNCTION %s at %L",
489                      sym->name, ns->entries->sym->name, &sym->declared_at);
490               }
491               else
492                 {
493                   ts = &sym->ts;
494                   if (ts->type == BT_UNKNOWN)
495                     ts = gfc_get_default_type (sym, NULL);
496                   switch (ts->type)
497                     {
498                     case BT_INTEGER:
499                       if (ts->kind == gfc_default_integer_kind)
500                         sym = NULL;
501                       break;
502                     case BT_REAL:
503                       if (ts->kind == gfc_default_real_kind
504                           || ts->kind == gfc_default_double_kind)
505                         sym = NULL;
506                       break;
507                     case BT_COMPLEX:
508                       if (ts->kind == gfc_default_complex_kind)
509                         sym = NULL;
510                       break;
511                     case BT_LOGICAL:
512                       if (ts->kind == gfc_default_logical_kind)
513                         sym = NULL;
514                       break;
515                     case BT_UNKNOWN:
516                       /* We will issue error elsewhere.  */
517                       sym = NULL;
518                       break;
519                     default:
520                       break;
521                     }
522                   if (sym)
523                   {
524                     if (el == ns->entries)
525                       gfc_error
526                         ("FUNCTION result %s can't be of type %s in FUNCTION %s at %L",
527                          sym->name, gfc_typename (ts), ns->entries->sym->name,
528                          &sym->declared_at);
529                     else
530                       gfc_error
531                         ("ENTRY result %s can't be of type %s in FUNCTION %s at %L",
532                          sym->name, gfc_typename (ts), ns->entries->sym->name,
533                          &sym->declared_at);
534                   }
535                 }
536             }
537         }
538     }
539   proc->attr.access = ACCESS_PRIVATE;
540   proc->attr.entry_master = 1;
541
542   /* Merge all the entry point arguments.  */
543   for (el = ns->entries; el; el = el->next)
544     merge_argument_lists (proc, el->sym->formal);
545
546   /* Use the master function for the function body.  */
547   ns->proc_name = proc;
548
549   /* Finalize the new symbols.  */
550   gfc_commit_symbols ();
551
552   /* Restore the original namespace.  */
553   gfc_current_ns = old_ns;
554 }
555
556
557 /* Resolve contained function types.  Because contained functions can call one
558    another, they have to be worked out before any of the contained procedures
559    can be resolved.
560
561    The good news is that if a function doesn't already have a type, the only
562    way it can get one is through an IMPLICIT type or a RESULT variable, because
563    by definition contained functions are contained namespace they're contained
564    in, not in a sibling or parent namespace.  */
565
566 static void
567 resolve_contained_functions (gfc_namespace * ns)
568 {
569   gfc_namespace *child;
570   gfc_entry_list *el;
571
572   resolve_formal_arglists (ns);
573
574   for (child = ns->contained; child; child = child->sibling)
575     {
576       /* Resolve alternate entry points first.  */
577       resolve_entries (child);
578
579       /* Then check function return types.  */
580       resolve_contained_fntype (child->proc_name, child);
581       for (el = child->entries; el; el = el->next)
582         resolve_contained_fntype (el->sym, child);
583     }
584 }
585
586
587 /* Resolve all of the elements of a structure constructor and make sure that
588    the types are correct.  */
589
590 static try
591 resolve_structure_cons (gfc_expr * expr)
592 {
593   gfc_constructor *cons;
594   gfc_component *comp;
595   try t;
596   symbol_attribute a;
597
598   t = SUCCESS;
599   cons = expr->value.constructor;
600   /* A constructor may have references if it is the result of substituting a
601      parameter variable.  In this case we just pull out the component we
602      want.  */
603   if (expr->ref)
604     comp = expr->ref->u.c.sym->components;
605   else
606     comp = expr->ts.derived->components;
607
608   for (; comp; comp = comp->next, cons = cons->next)
609     {
610       if (! cons->expr)
611         continue;
612
613       if (gfc_resolve_expr (cons->expr) == FAILURE)
614         {
615           t = FAILURE;
616           continue;
617         }
618
619       if (cons->expr->expr_type != EXPR_NULL
620             && comp->as && comp->as->rank != cons->expr->rank
621             && (comp->allocatable || cons->expr->rank))
622         {
623           gfc_error ("The rank of the element in the derived type "
624                      "constructor at %L does not match that of the "
625                      "component (%d/%d)", &cons->expr->where,
626                      cons->expr->rank, comp->as ? comp->as->rank : 0);
627           t = FAILURE;
628         }
629
630       /* If we don't have the right type, try to convert it.  */
631
632       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
633         {
634           t = FAILURE;
635           if (comp->pointer && cons->expr->ts.type != BT_UNKNOWN)
636             gfc_error ("The element in the derived type constructor at %L, "
637                        "for pointer component '%s', is %s but should be %s",
638                        &cons->expr->where, comp->name,
639                        gfc_basic_typename (cons->expr->ts.type),
640                        gfc_basic_typename (comp->ts.type));
641           else
642             t = gfc_convert_type (cons->expr, &comp->ts, 1);
643         }
644
645       if (!comp->pointer || cons->expr->expr_type == EXPR_NULL)
646         continue;
647
648       a = gfc_expr_attr (cons->expr);
649
650       if (!a.pointer && !a.target)
651         {
652           t = FAILURE;
653           gfc_error ("The element in the derived type constructor at %L, "
654                      "for pointer component '%s' should be a POINTER or "
655                      "a TARGET", &cons->expr->where, comp->name);
656         }
657     }
658
659   return t;
660 }
661
662
663
664 /****************** Expression name resolution ******************/
665
666 /* Returns 0 if a symbol was not declared with a type or
667    attribute declaration statement, nonzero otherwise.  */
668
669 static int
670 was_declared (gfc_symbol * sym)
671 {
672   symbol_attribute a;
673
674   a = sym->attr;
675
676   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
677     return 1;
678
679   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
680       || a.optional || a.pointer || a.save || a.target
681       || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
682     return 1;
683
684   return 0;
685 }
686
687
688 /* Determine if a symbol is generic or not.  */
689
690 static int
691 generic_sym (gfc_symbol * sym)
692 {
693   gfc_symbol *s;
694
695   if (sym->attr.generic ||
696       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
697     return 1;
698
699   if (was_declared (sym) || sym->ns->parent == NULL)
700     return 0;
701
702   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
703
704   return (s == NULL) ? 0 : generic_sym (s);
705 }
706
707
708 /* Determine if a symbol is specific or not.  */
709
710 static int
711 specific_sym (gfc_symbol * sym)
712 {
713   gfc_symbol *s;
714
715   if (sym->attr.if_source == IFSRC_IFBODY
716       || sym->attr.proc == PROC_MODULE
717       || sym->attr.proc == PROC_INTERNAL
718       || sym->attr.proc == PROC_ST_FUNCTION
719       || (sym->attr.intrinsic &&
720           gfc_specific_intrinsic (sym->name))
721       || sym->attr.external)
722     return 1;
723
724   if (was_declared (sym) || sym->ns->parent == NULL)
725     return 0;
726
727   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
728
729   return (s == NULL) ? 0 : specific_sym (s);
730 }
731
732
733 /* Figure out if the procedure is specific, generic or unknown.  */
734
735 typedef enum
736 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
737 proc_type;
738
739 static proc_type
740 procedure_kind (gfc_symbol * sym)
741 {
742
743   if (generic_sym (sym))
744     return PTYPE_GENERIC;
745
746   if (specific_sym (sym))
747     return PTYPE_SPECIFIC;
748
749   return PTYPE_UNKNOWN;
750 }
751
752 /* Check references to assumed size arrays.  The flag need_full_assumed_size
753    is nonzero when matching actual arguments.  */
754
755 static int need_full_assumed_size = 0;
756
757 static bool
758 check_assumed_size_reference (gfc_symbol * sym, gfc_expr * e)
759 {
760   gfc_ref * ref;
761   int dim;
762   int last = 1;
763
764   if (need_full_assumed_size
765         || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
766       return false;
767
768   for (ref = e->ref; ref; ref = ref->next)
769     if (ref->type == REF_ARRAY)
770       for (dim = 0; dim < ref->u.ar.as->rank; dim++)
771         last = (ref->u.ar.end[dim] == NULL) && (ref->u.ar.type == DIMEN_ELEMENT);
772
773   if (last)
774     {
775       gfc_error ("The upper bound in the last dimension must "
776                  "appear in the reference to the assumed size "
777                  "array '%s' at %L.", sym->name, &e->where);
778       return true;
779     }
780   return false;
781 }
782
783
784 /* Look for bad assumed size array references in argument expressions
785   of elemental and array valued intrinsic procedures.  Since this is
786   called from procedure resolution functions, it only recurses at
787   operators.  */
788
789 static bool
790 resolve_assumed_size_actual (gfc_expr *e)
791 {
792   if (e == NULL)
793    return false;
794
795   switch (e->expr_type)
796     {
797     case EXPR_VARIABLE:
798       if (e->symtree
799             && check_assumed_size_reference (e->symtree->n.sym, e))
800         return true;
801       break;
802
803     case EXPR_OP:
804       if (resolve_assumed_size_actual (e->value.op.op1)
805             || resolve_assumed_size_actual (e->value.op.op2))
806         return true;
807       break;
808
809     default:
810       break;
811     }
812   return false;
813 }
814
815
816 /* Resolve an actual argument list.  Most of the time, this is just
817    resolving the expressions in the list.
818    The exception is that we sometimes have to decide whether arguments
819    that look like procedure arguments are really simple variable
820    references.  */
821
822 static try
823 resolve_actual_arglist (gfc_actual_arglist * arg)
824 {
825   gfc_symbol *sym;
826   gfc_symtree *parent_st;
827   gfc_expr *e;
828
829   for (; arg; arg = arg->next)
830     {
831
832       e = arg->expr;
833       if (e == NULL)
834         {
835           /* Check the label is a valid branching target.  */
836           if (arg->label)
837             {
838               if (arg->label->defined == ST_LABEL_UNKNOWN)
839                 {
840                   gfc_error ("Label %d referenced at %L is never defined",
841                              arg->label->value, &arg->label->where);
842                   return FAILURE;
843                 }
844             }
845           continue;
846         }
847
848       if (e->ts.type != BT_PROCEDURE)
849         {
850           if (gfc_resolve_expr (e) != SUCCESS)
851             return FAILURE;
852           continue;
853         }
854
855       /* See if the expression node should really be a variable
856          reference.  */
857
858       sym = e->symtree->n.sym;
859
860       if (sym->attr.flavor == FL_PROCEDURE
861           || sym->attr.intrinsic
862           || sym->attr.external)
863         {
864           int actual_ok;
865
866           /* If a procedure is not already determined to be something else
867              check if it is intrinsic.  */
868           if (!sym->attr.intrinsic
869                 && !(sym->attr.external || sym->attr.use_assoc
870                        || sym->attr.if_source == IFSRC_IFBODY)
871                 && gfc_intrinsic_name (sym->name, sym->attr.subroutine))
872             sym->attr.intrinsic = 1;
873
874           if (sym->attr.proc == PROC_ST_FUNCTION)
875             {
876               gfc_error ("Statement function '%s' at %L is not allowed as an "
877                          "actual argument", sym->name, &e->where);
878             }
879
880           actual_ok = gfc_intrinsic_actual_ok (sym->name, sym->attr.subroutine);
881           if (sym->attr.intrinsic && actual_ok == 0)
882             {
883               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
884                          "actual argument", sym->name, &e->where);
885             }
886           else if (sym->attr.intrinsic && actual_ok == 2)
887           /* We need a special case for CHAR, which is the only intrinsic
888              function allowed as actual argument in F2003 and not allowed
889              in F95.  */
890             gfc_notify_std (GFC_STD_F2003, "Fortran 2003: CHAR intrinsic "
891                             "allowed as actual argument at %L", &e->where);
892
893           if (sym->attr.contained && !sym->attr.use_assoc
894               && sym->ns->proc_name->attr.flavor != FL_MODULE)
895             {
896               gfc_error ("Internal procedure '%s' is not allowed as an "
897                          "actual argument at %L", sym->name, &e->where);
898             }
899
900           if (sym->attr.elemental && !sym->attr.intrinsic)
901             {
902               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
903                          "allowed as an actual argument at %L", sym->name,
904                          &e->where);
905             }
906
907           if (sym->attr.generic)
908             {
909               gfc_error ("GENERIC non-INTRINSIC procedure '%s' is not "
910                          "allowed as an actual argument at %L", sym->name,
911                          &e->where);
912             }
913
914           /* If the symbol is the function that names the current (or
915              parent) scope, then we really have a variable reference.  */
916
917           if (sym->attr.function && sym->result == sym
918               && (sym->ns->proc_name == sym
919                   || (sym->ns->parent != NULL
920                       && sym->ns->parent->proc_name == sym)))
921             goto got_variable;
922
923           continue;
924         }
925
926       /* See if the name is a module procedure in a parent unit.  */
927
928       if (was_declared (sym) || sym->ns->parent == NULL)
929         goto got_variable;
930
931       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
932         {
933           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
934           return FAILURE;
935         }
936
937       if (parent_st == NULL)
938         goto got_variable;
939
940       sym = parent_st->n.sym;
941       e->symtree = parent_st;           /* Point to the right thing.  */
942
943       if (sym->attr.flavor == FL_PROCEDURE
944           || sym->attr.intrinsic
945           || sym->attr.external)
946         {
947           continue;
948         }
949
950     got_variable:
951       e->expr_type = EXPR_VARIABLE;
952       e->ts = sym->ts;
953       if (sym->as != NULL)
954         {
955           e->rank = sym->as->rank;
956           e->ref = gfc_get_ref ();
957           e->ref->type = REF_ARRAY;
958           e->ref->u.ar.type = AR_FULL;
959           e->ref->u.ar.as = sym->as;
960         }
961     }
962
963   return SUCCESS;
964 }
965
966
967 /* Do the checks of the actual argument list that are specific to elemental
968    procedures.  If called with c == NULL, we have a function, otherwise if
969    expr == NULL, we have a subroutine.  */
970 static try
971 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
972 {
973   gfc_actual_arglist *arg0;
974   gfc_actual_arglist *arg;
975   gfc_symbol *esym = NULL;
976   gfc_intrinsic_sym *isym = NULL;
977   gfc_expr *e = NULL;
978   gfc_intrinsic_arg *iformal = NULL;
979   gfc_formal_arglist *eformal = NULL;
980   bool formal_optional = false;
981   bool set_by_optional = false;
982   int i;
983   int rank = 0;
984
985   /* Is this an elemental procedure?  */
986   if (expr && expr->value.function.actual != NULL)
987     {
988       if (expr->value.function.esym != NULL
989             && expr->value.function.esym->attr.elemental)
990         {
991           arg0 = expr->value.function.actual;
992           esym = expr->value.function.esym;
993         }
994       else if (expr->value.function.isym != NULL
995                  && expr->value.function.isym->elemental)
996         {
997           arg0 = expr->value.function.actual;
998           isym = expr->value.function.isym;
999         }
1000       else
1001         return SUCCESS;
1002     }
1003   else if (c && c->ext.actual != NULL
1004              && c->symtree->n.sym->attr.elemental)
1005     {
1006       arg0 = c->ext.actual;
1007       esym = c->symtree->n.sym;
1008     }
1009   else
1010     return SUCCESS;
1011
1012   /* The rank of an elemental is the rank of its array argument(s).  */
1013   for (arg = arg0; arg; arg = arg->next)
1014     {
1015       if (arg->expr != NULL && arg->expr->rank > 0)
1016         {
1017           rank = arg->expr->rank;
1018           if (arg->expr->expr_type == EXPR_VARIABLE
1019                 && arg->expr->symtree->n.sym->attr.optional)
1020             set_by_optional = true;
1021
1022           /* Function specific; set the result rank and shape.  */
1023           if (expr)
1024             {
1025               expr->rank = rank;
1026               if (!expr->shape && arg->expr->shape)
1027                 {
1028                   expr->shape = gfc_get_shape (rank);
1029                   for (i = 0; i < rank; i++)
1030                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1031                 }
1032             }
1033           break;
1034         }
1035     }
1036
1037   /* If it is an array, it shall not be supplied as an actual argument
1038      to an elemental procedure unless an array of the same rank is supplied
1039      as an actual argument corresponding to a nonoptional dummy argument of
1040      that elemental procedure(12.4.1.5).  */
1041   formal_optional = false;
1042   if (isym)
1043     iformal = isym->formal;
1044   else
1045     eformal = esym->formal;
1046
1047   for (arg = arg0; arg; arg = arg->next)
1048     {
1049       if (eformal)
1050         {
1051           if (eformal->sym && eformal->sym->attr.optional)
1052             formal_optional = true;
1053           eformal = eformal->next;
1054         }
1055       else if (isym && iformal)
1056         {
1057           if (iformal->optional)
1058             formal_optional = true;
1059           iformal = iformal->next;
1060         }
1061       else if (isym)
1062         formal_optional = true;
1063
1064       if (pedantic && arg->expr != NULL
1065             && arg->expr->expr_type == EXPR_VARIABLE
1066             && arg->expr->symtree->n.sym->attr.optional
1067             && formal_optional
1068             && arg->expr->rank
1069             && (set_by_optional || arg->expr->rank != rank)
1070             && !(isym && isym->generic_id == GFC_ISYM_CONVERSION))
1071         {
1072           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1073                        "MISSING, it cannot be the actual argument of an "
1074                        "ELEMENTAL procedure unless there is a non-optional"
1075                        "argument with the same rank (12.4.1.5)",
1076                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1077           return FAILURE;
1078         }
1079     }
1080
1081   for (arg = arg0; arg; arg = arg->next)
1082     {
1083       if (arg->expr == NULL || arg->expr->rank == 0)
1084         continue;
1085
1086       /* Being elemental, the last upper bound of an assumed size array
1087          argument must be present.  */
1088       if (resolve_assumed_size_actual (arg->expr))
1089         return FAILURE;
1090
1091       if (expr)
1092         continue;
1093
1094       /* Elemental subroutine array actual arguments must conform.  */
1095       if (e != NULL)
1096         {
1097           if (gfc_check_conformance ("elemental subroutine", arg->expr, e)
1098                 == FAILURE)
1099             return FAILURE;
1100         }
1101       else
1102         e = arg->expr;
1103     }
1104
1105   return SUCCESS;
1106 }
1107
1108
1109 /* Go through each actual argument in ACTUAL and see if it can be
1110    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1111    function being called, or NULL if not known.  */
1112
1113 static void
1114 find_noncopying_intrinsics (gfc_symbol * fnsym, gfc_actual_arglist * actual)
1115 {
1116   gfc_actual_arglist *ap;
1117   gfc_expr *expr;
1118
1119   for (ap = actual; ap; ap = ap->next)
1120     if (ap->expr
1121         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1122         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual))
1123       ap->expr->inline_noncopying_intrinsic = 1;
1124 }
1125
1126 /* This function does the checking of references to global procedures
1127    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1128    77 and 95 standards.  It checks for a gsymbol for the name, making
1129    one if it does not already exist.  If it already exists, then the
1130    reference being resolved must correspond to the type of gsymbol.
1131    Otherwise, the new symbol is equipped with the attributes of the
1132    reference.  The corresponding code that is called in creating
1133    global entities is parse.c.  */
1134
1135 static void
1136 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1137 {
1138   gfc_gsymbol * gsym;
1139   unsigned int type;
1140
1141   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1142
1143   gsym = gfc_get_gsymbol (sym->name);
1144
1145   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1146     global_used (gsym, where);
1147
1148   if (gsym->type == GSYM_UNKNOWN)
1149     {
1150       gsym->type = type;
1151       gsym->where = *where;
1152     }
1153
1154   gsym->used = 1;
1155 }
1156
1157 /************* Function resolution *************/
1158
1159 /* Resolve a function call known to be generic.
1160    Section 14.1.2.4.1.  */
1161
1162 static match
1163 resolve_generic_f0 (gfc_expr * expr, gfc_symbol * sym)
1164 {
1165   gfc_symbol *s;
1166
1167   if (sym->attr.generic)
1168     {
1169       s =
1170         gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1171       if (s != NULL)
1172         {
1173           expr->value.function.name = s->name;
1174           expr->value.function.esym = s;
1175
1176           if (s->ts.type != BT_UNKNOWN)
1177             expr->ts = s->ts;
1178           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1179             expr->ts = s->result->ts;
1180
1181           if (s->as != NULL)
1182             expr->rank = s->as->rank;
1183           else if (s->result != NULL && s->result->as != NULL)
1184             expr->rank = s->result->as->rank;
1185
1186           return MATCH_YES;
1187         }
1188
1189       /* TODO: Need to search for elemental references in generic interface */
1190     }
1191
1192   if (sym->attr.intrinsic)
1193     return gfc_intrinsic_func_interface (expr, 0);
1194
1195   return MATCH_NO;
1196 }
1197
1198
1199 static try
1200 resolve_generic_f (gfc_expr * expr)
1201 {
1202   gfc_symbol *sym;
1203   match m;
1204
1205   sym = expr->symtree->n.sym;
1206
1207   for (;;)
1208     {
1209       m = resolve_generic_f0 (expr, sym);
1210       if (m == MATCH_YES)
1211         return SUCCESS;
1212       else if (m == MATCH_ERROR)
1213         return FAILURE;
1214
1215 generic:
1216       if (sym->ns->parent == NULL)
1217         break;
1218       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1219
1220       if (sym == NULL)
1221         break;
1222       if (!generic_sym (sym))
1223         goto generic;
1224     }
1225
1226   /* Last ditch attempt.  */
1227
1228   if (!gfc_generic_intrinsic (expr->symtree->n.sym->name))
1229     {
1230       gfc_error ("There is no specific function for the generic '%s' at %L",
1231                  expr->symtree->n.sym->name, &expr->where);
1232       return FAILURE;
1233     }
1234
1235   m = gfc_intrinsic_func_interface (expr, 0);
1236   if (m == MATCH_YES)
1237     return SUCCESS;
1238   if (m == MATCH_NO)
1239     gfc_error
1240       ("Generic function '%s' at %L is not consistent with a specific "
1241        "intrinsic interface", expr->symtree->n.sym->name, &expr->where);
1242
1243   return FAILURE;
1244 }
1245
1246
1247 /* Resolve a function call known to be specific.  */
1248
1249 static match
1250 resolve_specific_f0 (gfc_symbol * sym, gfc_expr * expr)
1251 {
1252   match m;
1253
1254   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1255     {
1256       if (sym->attr.dummy)
1257         {
1258           sym->attr.proc = PROC_DUMMY;
1259           goto found;
1260         }
1261
1262       sym->attr.proc = PROC_EXTERNAL;
1263       goto found;
1264     }
1265
1266   if (sym->attr.proc == PROC_MODULE
1267       || sym->attr.proc == PROC_ST_FUNCTION
1268       || sym->attr.proc == PROC_INTERNAL)
1269     goto found;
1270
1271   if (sym->attr.intrinsic)
1272     {
1273       m = gfc_intrinsic_func_interface (expr, 1);
1274       if (m == MATCH_YES)
1275         return MATCH_YES;
1276       if (m == MATCH_NO)
1277         gfc_error
1278           ("Function '%s' at %L is INTRINSIC but is not compatible with "
1279            "an intrinsic", sym->name, &expr->where);
1280
1281       return MATCH_ERROR;
1282     }
1283
1284   return MATCH_NO;
1285
1286 found:
1287   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1288
1289   expr->ts = sym->ts;
1290   expr->value.function.name = sym->name;
1291   expr->value.function.esym = sym;
1292   if (sym->as != NULL)
1293     expr->rank = sym->as->rank;
1294
1295   return MATCH_YES;
1296 }
1297
1298
1299 static try
1300 resolve_specific_f (gfc_expr * expr)
1301 {
1302   gfc_symbol *sym;
1303   match m;
1304
1305   sym = expr->symtree->n.sym;
1306
1307   for (;;)
1308     {
1309       m = resolve_specific_f0 (sym, expr);
1310       if (m == MATCH_YES)
1311         return SUCCESS;
1312       if (m == MATCH_ERROR)
1313         return FAILURE;
1314
1315       if (sym->ns->parent == NULL)
1316         break;
1317
1318       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1319
1320       if (sym == NULL)
1321         break;
1322     }
1323
1324   gfc_error ("Unable to resolve the specific function '%s' at %L",
1325              expr->symtree->n.sym->name, &expr->where);
1326
1327   return SUCCESS;
1328 }
1329
1330
1331 /* Resolve a procedure call not known to be generic nor specific.  */
1332
1333 static try
1334 resolve_unknown_f (gfc_expr * expr)
1335 {
1336   gfc_symbol *sym;
1337   gfc_typespec *ts;
1338
1339   sym = expr->symtree->n.sym;
1340
1341   if (sym->attr.dummy)
1342     {
1343       sym->attr.proc = PROC_DUMMY;
1344       expr->value.function.name = sym->name;
1345       goto set_type;
1346     }
1347
1348   /* See if we have an intrinsic function reference.  */
1349
1350   if (gfc_intrinsic_name (sym->name, 0))
1351     {
1352       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1353         return SUCCESS;
1354       return FAILURE;
1355     }
1356
1357   /* The reference is to an external name.  */
1358
1359   sym->attr.proc = PROC_EXTERNAL;
1360   expr->value.function.name = sym->name;
1361   expr->value.function.esym = expr->symtree->n.sym;
1362
1363   if (sym->as != NULL)
1364     expr->rank = sym->as->rank;
1365
1366   /* Type of the expression is either the type of the symbol or the
1367      default type of the symbol.  */
1368
1369 set_type:
1370   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1371
1372   if (sym->ts.type != BT_UNKNOWN)
1373     expr->ts = sym->ts;
1374   else
1375     {
1376       ts = gfc_get_default_type (sym, sym->ns);
1377
1378       if (ts->type == BT_UNKNOWN)
1379         {
1380           gfc_error ("Function '%s' at %L has no IMPLICIT type",
1381                      sym->name, &expr->where);
1382           return FAILURE;
1383         }
1384       else
1385         expr->ts = *ts;
1386     }
1387
1388   return SUCCESS;
1389 }
1390
1391
1392 /* Figure out if a function reference is pure or not.  Also set the name
1393    of the function for a potential error message.  Return nonzero if the
1394    function is PURE, zero if not.  */
1395
1396 static int
1397 pure_function (gfc_expr * e, const char **name)
1398 {
1399   int pure;
1400
1401   if (e->value.function.esym)
1402     {
1403       pure = gfc_pure (e->value.function.esym);
1404       *name = e->value.function.esym->name;
1405     }
1406   else if (e->value.function.isym)
1407     {
1408       pure = e->value.function.isym->pure
1409         || e->value.function.isym->elemental;
1410       *name = e->value.function.isym->name;
1411     }
1412   else
1413     {
1414       /* Implicit functions are not pure.  */
1415       pure = 0;
1416       *name = e->value.function.name;
1417     }
1418
1419   return pure;
1420 }
1421
1422
1423 /* Resolve a function call, which means resolving the arguments, then figuring
1424    out which entity the name refers to.  */
1425 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
1426    to INTENT(OUT) or INTENT(INOUT).  */
1427
1428 static try
1429 resolve_function (gfc_expr * expr)
1430 {
1431   gfc_actual_arglist *arg;
1432   gfc_symbol * sym;
1433   const char *name;
1434   try t;
1435   int temp;
1436
1437   sym = NULL;
1438   if (expr->symtree)
1439     sym = expr->symtree->n.sym;
1440
1441   /* If the procedure is not internal, a statement function or a module
1442      procedure,it must be external and should be checked for usage.  */
1443   if (sym && !sym->attr.dummy && !sym->attr.contained
1444         && sym->attr.proc != PROC_ST_FUNCTION
1445         && !sym->attr.use_assoc)
1446     resolve_global_procedure (sym, &expr->where, 0);
1447
1448   /* Switch off assumed size checking and do this again for certain kinds
1449      of procedure, once the procedure itself is resolved.  */
1450   need_full_assumed_size++;
1451
1452   if (resolve_actual_arglist (expr->value.function.actual) == FAILURE)
1453     return FAILURE;
1454
1455   /* Resume assumed_size checking. */
1456   need_full_assumed_size--;
1457
1458   if (sym && sym->ts.type == BT_CHARACTER
1459         && sym->ts.cl
1460         && sym->ts.cl->length == NULL
1461         && !sym->attr.dummy
1462         && expr->value.function.esym == NULL
1463         && !sym->attr.contained)
1464     {
1465       /* Internal procedures are taken care of in resolve_contained_fntype.  */
1466       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
1467                  "be used at %L since it is not a dummy argument",
1468                  sym->name, &expr->where);
1469       return FAILURE;
1470     }
1471
1472 /* See if function is already resolved.  */
1473
1474   if (expr->value.function.name != NULL)
1475     {
1476       if (expr->ts.type == BT_UNKNOWN)
1477         expr->ts = sym->ts;
1478       t = SUCCESS;
1479     }
1480   else
1481     {
1482       /* Apply the rules of section 14.1.2.  */
1483
1484       switch (procedure_kind (sym))
1485         {
1486         case PTYPE_GENERIC:
1487           t = resolve_generic_f (expr);
1488           break;
1489
1490         case PTYPE_SPECIFIC:
1491           t = resolve_specific_f (expr);
1492           break;
1493
1494         case PTYPE_UNKNOWN:
1495           t = resolve_unknown_f (expr);
1496           break;
1497
1498         default:
1499           gfc_internal_error ("resolve_function(): bad function type");
1500         }
1501     }
1502
1503   /* If the expression is still a function (it might have simplified),
1504      then we check to see if we are calling an elemental function.  */
1505
1506   if (expr->expr_type != EXPR_FUNCTION)
1507     return t;
1508
1509   temp = need_full_assumed_size;
1510   need_full_assumed_size = 0;
1511
1512   if (resolve_elemental_actual (expr, NULL) == FAILURE)
1513     return FAILURE;
1514
1515   if (omp_workshare_flag
1516       && expr->value.function.esym
1517       && ! gfc_elemental (expr->value.function.esym))
1518     {
1519       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed"
1520                  " in WORKSHARE construct", expr->value.function.esym->name,
1521                  &expr->where);
1522       t = FAILURE;
1523     }
1524
1525   else if (expr->value.function.actual != NULL
1526              && expr->value.function.isym != NULL
1527              && expr->value.function.isym->generic_id != GFC_ISYM_LBOUND
1528              && expr->value.function.isym->generic_id != GFC_ISYM_LOC
1529              && expr->value.function.isym->generic_id != GFC_ISYM_PRESENT)
1530     {
1531       /* Array instrinsics must also have the last upper bound of an
1532          assumed size array argument.  UBOUND and SIZE have to be
1533          excluded from the check if the second argument is anything
1534          than a constant.  */
1535       int inquiry;
1536       inquiry = expr->value.function.isym->generic_id == GFC_ISYM_UBOUND
1537                   || expr->value.function.isym->generic_id == GFC_ISYM_SIZE;
1538
1539       for (arg = expr->value.function.actual; arg; arg = arg->next)
1540         {
1541           if (inquiry && arg->next != NULL && arg->next->expr
1542                 && arg->next->expr->expr_type != EXPR_CONSTANT)
1543             break;
1544
1545           if (arg->expr != NULL
1546                 && arg->expr->rank > 0
1547                 && resolve_assumed_size_actual (arg->expr))
1548             return FAILURE;
1549         }
1550     }
1551
1552   need_full_assumed_size = temp;
1553
1554   if (!pure_function (expr, &name) && name)
1555     {
1556       if (forall_flag)
1557         {
1558           gfc_error
1559             ("reference to non-PURE function '%s' at %L inside a "
1560              "FORALL %s", name, &expr->where, forall_flag == 2 ?
1561              "mask" : "block");
1562           t = FAILURE;
1563         }
1564       else if (gfc_pure (NULL))
1565         {
1566           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
1567                      "procedure within a PURE procedure", name, &expr->where);
1568           t = FAILURE;
1569         }
1570     }
1571
1572   /* Functions without the RECURSIVE attribution are not allowed to
1573    * call themselves.  */
1574   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
1575     {
1576       gfc_symbol *esym, *proc;
1577       esym = expr->value.function.esym;
1578       proc = gfc_current_ns->proc_name;
1579       if (esym == proc)
1580       {
1581         gfc_error ("Function '%s' at %L cannot call itself, as it is not "
1582                    "RECURSIVE", name, &expr->where);
1583         t = FAILURE;
1584       }
1585
1586       if (esym->attr.entry && esym->ns->entries && proc->ns->entries
1587           && esym->ns->entries->sym == proc->ns->entries->sym)
1588       {
1589         gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
1590                    "'%s' is not declared as RECURSIVE",
1591                    esym->name, &expr->where, esym->ns->entries->sym->name);
1592         t = FAILURE;
1593       }
1594     }
1595
1596   /* Character lengths of use associated functions may contains references to
1597      symbols not referenced from the current program unit otherwise.  Make sure
1598      those symbols are marked as referenced.  */
1599
1600   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
1601       && expr->value.function.esym->attr.use_assoc)
1602     {
1603       gfc_expr_set_symbols_referenced (expr->ts.cl->length);
1604     }
1605
1606   if (t == SUCCESS)
1607     find_noncopying_intrinsics (expr->value.function.esym,
1608                                 expr->value.function.actual);
1609   return t;
1610 }
1611
1612
1613 /************* Subroutine resolution *************/
1614
1615 static void
1616 pure_subroutine (gfc_code * c, gfc_symbol * sym)
1617 {
1618
1619   if (gfc_pure (sym))
1620     return;
1621
1622   if (forall_flag)
1623     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
1624                sym->name, &c->loc);
1625   else if (gfc_pure (NULL))
1626     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
1627                &c->loc);
1628 }
1629
1630
1631 static match
1632 resolve_generic_s0 (gfc_code * c, gfc_symbol * sym)
1633 {
1634   gfc_symbol *s;
1635
1636   if (sym->attr.generic)
1637     {
1638       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
1639       if (s != NULL)
1640         {
1641           c->resolved_sym = s;
1642           pure_subroutine (c, s);
1643           return MATCH_YES;
1644         }
1645
1646       /* TODO: Need to search for elemental references in generic interface.  */
1647     }
1648
1649   if (sym->attr.intrinsic)
1650     return gfc_intrinsic_sub_interface (c, 0);
1651
1652   return MATCH_NO;
1653 }
1654
1655
1656 static try
1657 resolve_generic_s (gfc_code * c)
1658 {
1659   gfc_symbol *sym;
1660   match m;
1661
1662   sym = c->symtree->n.sym;
1663
1664   for (;;)
1665     {
1666       m = resolve_generic_s0 (c, sym);
1667       if (m == MATCH_YES)
1668         return SUCCESS;
1669       else if (m == MATCH_ERROR)
1670         return FAILURE;
1671
1672 generic:
1673       if (sym->ns->parent == NULL)
1674         break;
1675       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1676
1677       if (sym == NULL)
1678         break;
1679       if (!generic_sym (sym))
1680         goto generic;
1681     }
1682
1683   /* Last ditch attempt.  */
1684   sym = c->symtree->n.sym;
1685   if (!gfc_generic_intrinsic (sym->name))
1686     {
1687       gfc_error
1688         ("There is no specific subroutine for the generic '%s' at %L",
1689          sym->name, &c->loc);
1690       return FAILURE;
1691     }
1692
1693   m = gfc_intrinsic_sub_interface (c, 0);
1694   if (m == MATCH_YES)
1695     return SUCCESS;
1696   if (m == MATCH_NO)
1697     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
1698                "intrinsic subroutine interface", sym->name, &c->loc);
1699
1700   return FAILURE;
1701 }
1702
1703
1704 /* Resolve a subroutine call known to be specific.  */
1705
1706 static match
1707 resolve_specific_s0 (gfc_code * c, gfc_symbol * sym)
1708 {
1709   match m;
1710
1711   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1712     {
1713       if (sym->attr.dummy)
1714         {
1715           sym->attr.proc = PROC_DUMMY;
1716           goto found;
1717         }
1718
1719       sym->attr.proc = PROC_EXTERNAL;
1720       goto found;
1721     }
1722
1723   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
1724     goto found;
1725
1726   if (sym->attr.intrinsic)
1727     {
1728       m = gfc_intrinsic_sub_interface (c, 1);
1729       if (m == MATCH_YES)
1730         return MATCH_YES;
1731       if (m == MATCH_NO)
1732         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
1733                    "with an intrinsic", sym->name, &c->loc);
1734
1735       return MATCH_ERROR;
1736     }
1737
1738   return MATCH_NO;
1739
1740 found:
1741   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
1742
1743   c->resolved_sym = sym;
1744   pure_subroutine (c, sym);
1745
1746   return MATCH_YES;
1747 }
1748
1749
1750 static try
1751 resolve_specific_s (gfc_code * c)
1752 {
1753   gfc_symbol *sym;
1754   match m;
1755
1756   sym = c->symtree->n.sym;
1757
1758   for (;;)
1759     {
1760       m = resolve_specific_s0 (c, sym);
1761       if (m == MATCH_YES)
1762         return SUCCESS;
1763       if (m == MATCH_ERROR)
1764         return FAILURE;
1765
1766       if (sym->ns->parent == NULL)
1767         break;
1768
1769       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1770
1771       if (sym == NULL)
1772         break;
1773     }
1774
1775   sym = c->symtree->n.sym;
1776   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
1777              sym->name, &c->loc);
1778
1779   return FAILURE;
1780 }
1781
1782
1783 /* Resolve a subroutine call not known to be generic nor specific.  */
1784
1785 static try
1786 resolve_unknown_s (gfc_code * c)
1787 {
1788   gfc_symbol *sym;
1789
1790   sym = c->symtree->n.sym;
1791
1792   if (sym->attr.dummy)
1793     {
1794       sym->attr.proc = PROC_DUMMY;
1795       goto found;
1796     }
1797
1798   /* See if we have an intrinsic function reference.  */
1799
1800   if (gfc_intrinsic_name (sym->name, 1))
1801     {
1802       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
1803         return SUCCESS;
1804       return FAILURE;
1805     }
1806
1807   /* The reference is to an external name.  */
1808
1809 found:
1810   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
1811
1812   c->resolved_sym = sym;
1813
1814   pure_subroutine (c, sym);
1815
1816   return SUCCESS;
1817 }
1818
1819
1820 /* Resolve a subroutine call.  Although it was tempting to use the same code
1821    for functions, subroutines and functions are stored differently and this
1822    makes things awkward.  */
1823
1824 static try
1825 resolve_call (gfc_code * c)
1826 {
1827   try t;
1828
1829   if (c->symtree && c->symtree->n.sym
1830         && c->symtree->n.sym->ts.type != BT_UNKNOWN)
1831     {
1832       gfc_error ("'%s' at %L has a type, which is not consistent with "
1833                  "the CALL at %L", c->symtree->n.sym->name,
1834                  &c->symtree->n.sym->declared_at, &c->loc);
1835       return FAILURE;
1836     }
1837
1838   /* If the procedure is not internal or module, it must be external and
1839      should be checked for usage.  */
1840   if (c->symtree && c->symtree->n.sym
1841         && !c->symtree->n.sym->attr.dummy
1842         && !c->symtree->n.sym->attr.contained
1843         && !c->symtree->n.sym->attr.use_assoc)
1844     resolve_global_procedure (c->symtree->n.sym, &c->loc, 1);
1845
1846   /* Subroutines without the RECURSIVE attribution are not allowed to
1847    * call themselves.  */
1848   if (c->symtree && c->symtree->n.sym && !c->symtree->n.sym->attr.recursive)
1849     {
1850       gfc_symbol *csym, *proc;
1851       csym = c->symtree->n.sym;
1852       proc = gfc_current_ns->proc_name;
1853       if (csym == proc)
1854       {
1855         gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
1856                    "RECURSIVE", csym->name, &c->loc);
1857         t = FAILURE;
1858       }
1859
1860       if (csym->attr.entry && csym->ns->entries && proc->ns->entries
1861           && csym->ns->entries->sym == proc->ns->entries->sym)
1862       {
1863         gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
1864                    "'%s' is not declared as RECURSIVE",
1865                    csym->name, &c->loc, csym->ns->entries->sym->name);
1866         t = FAILURE;
1867       }
1868     }
1869
1870   /* Switch off assumed size checking and do this again for certain kinds
1871      of procedure, once the procedure itself is resolved.  */
1872   need_full_assumed_size++;
1873
1874   if (resolve_actual_arglist (c->ext.actual) == FAILURE)
1875     return FAILURE;
1876
1877   /* Resume assumed_size checking. */
1878   need_full_assumed_size--;
1879
1880
1881   t = SUCCESS;
1882   if (c->resolved_sym == NULL)
1883     switch (procedure_kind (c->symtree->n.sym))
1884       {
1885       case PTYPE_GENERIC:
1886         t = resolve_generic_s (c);
1887         break;
1888
1889       case PTYPE_SPECIFIC:
1890         t = resolve_specific_s (c);
1891         break;
1892
1893       case PTYPE_UNKNOWN:
1894         t = resolve_unknown_s (c);
1895         break;
1896
1897       default:
1898         gfc_internal_error ("resolve_subroutine(): bad function type");
1899       }
1900
1901   /* Some checks of elemental subroutine actual arguments.  */
1902   if (resolve_elemental_actual (NULL, c) == FAILURE)
1903     return FAILURE;
1904
1905   if (t == SUCCESS)
1906     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
1907   return t;
1908 }
1909
1910 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
1911    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
1912    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
1913    if their shapes do not match.  If either op1->shape or op2->shape is
1914    NULL, return SUCCESS.  */
1915
1916 static try
1917 compare_shapes (gfc_expr * op1, gfc_expr * op2)
1918 {
1919   try t;
1920   int i;
1921
1922   t = SUCCESS;
1923
1924   if (op1->shape != NULL && op2->shape != NULL)
1925     {
1926       for (i = 0; i < op1->rank; i++)
1927         {
1928           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
1929            {
1930              gfc_error ("Shapes for operands at %L and %L are not conformable",
1931                          &op1->where, &op2->where);
1932              t = FAILURE;
1933              break;
1934            }
1935         }
1936     }
1937
1938   return t;
1939 }
1940
1941 /* Resolve an operator expression node.  This can involve replacing the
1942    operation with a user defined function call.  */
1943
1944 static try
1945 resolve_operator (gfc_expr * e)
1946 {
1947   gfc_expr *op1, *op2;
1948   char msg[200];
1949   try t;
1950
1951   /* Resolve all subnodes-- give them types.  */
1952
1953   switch (e->value.op.operator)
1954     {
1955     default:
1956       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
1957         return FAILURE;
1958
1959     /* Fall through...  */
1960
1961     case INTRINSIC_NOT:
1962     case INTRINSIC_UPLUS:
1963     case INTRINSIC_UMINUS:
1964     case INTRINSIC_PARENTHESES:
1965       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
1966         return FAILURE;
1967       break;
1968     }
1969
1970   /* Typecheck the new node.  */
1971
1972   op1 = e->value.op.op1;
1973   op2 = e->value.op.op2;
1974
1975   switch (e->value.op.operator)
1976     {
1977     case INTRINSIC_UPLUS:
1978     case INTRINSIC_UMINUS:
1979       if (op1->ts.type == BT_INTEGER
1980           || op1->ts.type == BT_REAL
1981           || op1->ts.type == BT_COMPLEX)
1982         {
1983           e->ts = op1->ts;
1984           break;
1985         }
1986
1987       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
1988                gfc_op2string (e->value.op.operator), gfc_typename (&e->ts));
1989       goto bad_op;
1990
1991     case INTRINSIC_PLUS:
1992     case INTRINSIC_MINUS:
1993     case INTRINSIC_TIMES:
1994     case INTRINSIC_DIVIDE:
1995     case INTRINSIC_POWER:
1996       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
1997         {
1998           gfc_type_convert_binary (e);
1999           break;
2000         }
2001
2002       sprintf (msg,
2003                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
2004                gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2005                gfc_typename (&op2->ts));
2006       goto bad_op;
2007
2008     case INTRINSIC_CONCAT:
2009       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2010         {
2011           e->ts.type = BT_CHARACTER;
2012           e->ts.kind = op1->ts.kind;
2013           break;
2014         }
2015
2016       sprintf (msg,
2017                _("Operands of string concatenation operator at %%L are %s/%s"),
2018                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
2019       goto bad_op;
2020
2021     case INTRINSIC_AND:
2022     case INTRINSIC_OR:
2023     case INTRINSIC_EQV:
2024     case INTRINSIC_NEQV:
2025       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2026         {
2027           e->ts.type = BT_LOGICAL;
2028           e->ts.kind = gfc_kind_max (op1, op2);
2029           if (op1->ts.kind < e->ts.kind)
2030             gfc_convert_type (op1, &e->ts, 2);
2031           else if (op2->ts.kind < e->ts.kind)
2032             gfc_convert_type (op2, &e->ts, 2);
2033           break;
2034         }
2035
2036       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
2037                gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2038                gfc_typename (&op2->ts));
2039
2040       goto bad_op;
2041
2042     case INTRINSIC_NOT:
2043       if (op1->ts.type == BT_LOGICAL)
2044         {
2045           e->ts.type = BT_LOGICAL;
2046           e->ts.kind = op1->ts.kind;
2047           break;
2048         }
2049
2050       sprintf (msg, _("Operand of .NOT. operator at %%L is %s"),
2051                gfc_typename (&op1->ts));
2052       goto bad_op;
2053
2054     case INTRINSIC_GT:
2055     case INTRINSIC_GE:
2056     case INTRINSIC_LT:
2057     case INTRINSIC_LE:
2058       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
2059         {
2060           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
2061           goto bad_op;
2062         }
2063
2064       /* Fall through...  */
2065
2066     case INTRINSIC_EQ:
2067     case INTRINSIC_NE:
2068       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2069         {
2070           e->ts.type = BT_LOGICAL;
2071           e->ts.kind = gfc_default_logical_kind;
2072           break;
2073         }
2074
2075       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2076         {
2077           gfc_type_convert_binary (e);
2078
2079           e->ts.type = BT_LOGICAL;
2080           e->ts.kind = gfc_default_logical_kind;
2081           break;
2082         }
2083
2084       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2085         sprintf (msg,
2086                  _("Logicals at %%L must be compared with %s instead of %s"),
2087                  e->value.op.operator == INTRINSIC_EQ ? ".EQV." : ".NEQV.",
2088                  gfc_op2string (e->value.op.operator));
2089       else
2090         sprintf (msg,
2091                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
2092                  gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2093                  gfc_typename (&op2->ts));
2094
2095       goto bad_op;
2096
2097     case INTRINSIC_USER:
2098       if (op2 == NULL)
2099         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
2100                  e->value.op.uop->name, gfc_typename (&op1->ts));
2101       else
2102         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
2103                  e->value.op.uop->name, gfc_typename (&op1->ts),
2104                  gfc_typename (&op2->ts));
2105
2106       goto bad_op;
2107
2108     case INTRINSIC_PARENTHESES:
2109       break;
2110
2111     default:
2112       gfc_internal_error ("resolve_operator(): Bad intrinsic");
2113     }
2114
2115   /* Deal with arrayness of an operand through an operator.  */
2116
2117   t = SUCCESS;
2118
2119   switch (e->value.op.operator)
2120     {
2121     case INTRINSIC_PLUS:
2122     case INTRINSIC_MINUS:
2123     case INTRINSIC_TIMES:
2124     case INTRINSIC_DIVIDE:
2125     case INTRINSIC_POWER:
2126     case INTRINSIC_CONCAT:
2127     case INTRINSIC_AND:
2128     case INTRINSIC_OR:
2129     case INTRINSIC_EQV:
2130     case INTRINSIC_NEQV:
2131     case INTRINSIC_EQ:
2132     case INTRINSIC_NE:
2133     case INTRINSIC_GT:
2134     case INTRINSIC_GE:
2135     case INTRINSIC_LT:
2136     case INTRINSIC_LE:
2137
2138       if (op1->rank == 0 && op2->rank == 0)
2139         e->rank = 0;
2140
2141       if (op1->rank == 0 && op2->rank != 0)
2142         {
2143           e->rank = op2->rank;
2144
2145           if (e->shape == NULL)
2146             e->shape = gfc_copy_shape (op2->shape, op2->rank);
2147         }
2148
2149       if (op1->rank != 0 && op2->rank == 0)
2150         {
2151           e->rank = op1->rank;
2152
2153           if (e->shape == NULL)
2154             e->shape = gfc_copy_shape (op1->shape, op1->rank);
2155         }
2156
2157       if (op1->rank != 0 && op2->rank != 0)
2158         {
2159           if (op1->rank == op2->rank)
2160             {
2161               e->rank = op1->rank;
2162               if (e->shape == NULL)
2163                 {
2164                   t = compare_shapes(op1, op2);
2165                   if (t == FAILURE)
2166                     e->shape = NULL;
2167                   else
2168                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2169                 }
2170             }
2171           else
2172             {
2173               gfc_error ("Inconsistent ranks for operator at %L and %L",
2174                          &op1->where, &op2->where);
2175               t = FAILURE;
2176
2177               /* Allow higher level expressions to work.  */
2178               e->rank = 0;
2179             }
2180         }
2181
2182       break;
2183
2184     case INTRINSIC_NOT:
2185     case INTRINSIC_UPLUS:
2186     case INTRINSIC_UMINUS:
2187     case INTRINSIC_PARENTHESES:
2188       e->rank = op1->rank;
2189
2190       if (e->shape == NULL)
2191         e->shape = gfc_copy_shape (op1->shape, op1->rank);
2192
2193       /* Simply copy arrayness attribute */
2194       break;
2195
2196     default:
2197       break;
2198     }
2199
2200   /* Attempt to simplify the expression.  */
2201   if (t == SUCCESS)
2202     t = gfc_simplify_expr (e, 0);
2203   return t;
2204
2205 bad_op:
2206
2207   if (gfc_extend_expr (e) == SUCCESS)
2208     return SUCCESS;
2209
2210   gfc_error (msg, &e->where);
2211
2212   return FAILURE;
2213 }
2214
2215
2216 /************** Array resolution subroutines **************/
2217
2218
2219 typedef enum
2220 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
2221 comparison;
2222
2223 /* Compare two integer expressions.  */
2224
2225 static comparison
2226 compare_bound (gfc_expr * a, gfc_expr * b)
2227 {
2228   int i;
2229
2230   if (a == NULL || a->expr_type != EXPR_CONSTANT
2231       || b == NULL || b->expr_type != EXPR_CONSTANT)
2232     return CMP_UNKNOWN;
2233
2234   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
2235     gfc_internal_error ("compare_bound(): Bad expression");
2236
2237   i = mpz_cmp (a->value.integer, b->value.integer);
2238
2239   if (i < 0)
2240     return CMP_LT;
2241   if (i > 0)
2242     return CMP_GT;
2243   return CMP_EQ;
2244 }
2245
2246
2247 /* Compare an integer expression with an integer.  */
2248
2249 static comparison
2250 compare_bound_int (gfc_expr * a, int b)
2251 {
2252   int i;
2253
2254   if (a == NULL || a->expr_type != EXPR_CONSTANT)
2255     return CMP_UNKNOWN;
2256
2257   if (a->ts.type != BT_INTEGER)
2258     gfc_internal_error ("compare_bound_int(): Bad expression");
2259
2260   i = mpz_cmp_si (a->value.integer, b);
2261
2262   if (i < 0)
2263     return CMP_LT;
2264   if (i > 0)
2265     return CMP_GT;
2266   return CMP_EQ;
2267 }
2268
2269
2270 /* Compare an integer expression with a mpz_t.  */
2271
2272 static comparison
2273 compare_bound_mpz_t (gfc_expr * a, mpz_t b)
2274 {
2275   int i;
2276
2277   if (a == NULL || a->expr_type != EXPR_CONSTANT)
2278     return CMP_UNKNOWN;
2279
2280   if (a->ts.type != BT_INTEGER)
2281     gfc_internal_error ("compare_bound_int(): Bad expression");
2282
2283   i = mpz_cmp (a->value.integer, b);
2284
2285   if (i < 0)
2286     return CMP_LT;
2287   if (i > 0)
2288     return CMP_GT;
2289   return CMP_EQ;
2290 }
2291
2292
2293 /* Compute the last value of a sequence given by a triplet.  
2294    Return 0 if it wasn't able to compute the last value, or if the
2295    sequence if empty, and 1 otherwise.  */
2296
2297 static int
2298 compute_last_value_for_triplet (gfc_expr * start, gfc_expr * end,
2299                                 gfc_expr * stride, mpz_t last)
2300 {
2301   mpz_t rem;
2302
2303   if (start == NULL || start->expr_type != EXPR_CONSTANT
2304       || end == NULL || end->expr_type != EXPR_CONSTANT
2305       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
2306     return 0;
2307
2308   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
2309       || (stride != NULL && stride->ts.type != BT_INTEGER))
2310     return 0;
2311
2312   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
2313     {
2314       if (compare_bound (start, end) == CMP_GT)
2315         return 0;
2316       mpz_set (last, end->value.integer);
2317       return 1;
2318     }
2319
2320   if (compare_bound_int (stride, 0) == CMP_GT)
2321     {
2322       /* Stride is positive */
2323       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
2324         return 0;
2325     }
2326   else
2327     {
2328       /* Stride is negative */
2329       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
2330         return 0;
2331     }
2332
2333   mpz_init (rem);
2334   mpz_sub (rem, end->value.integer, start->value.integer);
2335   mpz_tdiv_r (rem, rem, stride->value.integer);
2336   mpz_sub (last, end->value.integer, rem);
2337   mpz_clear (rem);
2338
2339   return 1;
2340 }
2341
2342
2343 /* Compare a single dimension of an array reference to the array
2344    specification.  */
2345
2346 static try
2347 check_dimension (int i, gfc_array_ref * ar, gfc_array_spec * as)
2348 {
2349   mpz_t last_value;
2350
2351 /* Given start, end and stride values, calculate the minimum and
2352    maximum referenced indexes.  */
2353
2354   switch (ar->type)
2355     {
2356     case AR_FULL:
2357       break;
2358
2359     case AR_ELEMENT:
2360       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
2361         goto bound;
2362       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
2363         goto bound;
2364
2365       break;
2366
2367     case AR_SECTION:
2368       if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
2369         {
2370           gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
2371           return FAILURE;
2372         }
2373
2374 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
2375 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
2376
2377       if (compare_bound (AR_START, AR_END) == CMP_EQ
2378           && (compare_bound (AR_START, as->lower[i]) == CMP_LT
2379               || compare_bound (AR_START, as->upper[i]) == CMP_GT))
2380         goto bound;
2381
2382       if (((compare_bound_int (ar->stride[i], 0) == CMP_GT
2383             || ar->stride[i] == NULL)
2384            && compare_bound (AR_START, AR_END) != CMP_GT)
2385           || (compare_bound_int (ar->stride[i], 0) == CMP_LT
2386               && compare_bound (AR_START, AR_END) != CMP_LT))
2387         {
2388           if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
2389             goto bound;
2390           if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
2391             goto bound;
2392         }
2393
2394       mpz_init (last_value);
2395       if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
2396                                           last_value))
2397         {
2398           if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT
2399               || compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
2400             {
2401               mpz_clear (last_value);
2402               goto bound;
2403             }
2404         }
2405       mpz_clear (last_value);
2406
2407 #undef AR_START
2408 #undef AR_END
2409
2410       break;
2411
2412     default:
2413       gfc_internal_error ("check_dimension(): Bad array reference");
2414     }
2415
2416   return SUCCESS;
2417
2418 bound:
2419   gfc_warning ("Array reference at %L is out of bounds", &ar->c_where[i]);
2420   return SUCCESS;
2421 }
2422
2423
2424 /* Compare an array reference with an array specification.  */
2425
2426 static try
2427 compare_spec_to_ref (gfc_array_ref * ar)
2428 {
2429   gfc_array_spec *as;
2430   int i;
2431
2432   as = ar->as;
2433   i = as->rank - 1;
2434   /* TODO: Full array sections are only allowed as actual parameters.  */
2435   if (as->type == AS_ASSUMED_SIZE
2436       && (/*ar->type == AR_FULL
2437           ||*/ (ar->type == AR_SECTION
2438               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
2439     {
2440       gfc_error ("Rightmost upper bound of assumed size array section"
2441                  " not specified at %L", &ar->where);
2442       return FAILURE;
2443     }
2444
2445   if (ar->type == AR_FULL)
2446     return SUCCESS;
2447
2448   if (as->rank != ar->dimen)
2449     {
2450       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
2451                  &ar->where, ar->dimen, as->rank);
2452       return FAILURE;
2453     }
2454
2455   for (i = 0; i < as->rank; i++)
2456     if (check_dimension (i, ar, as) == FAILURE)
2457       return FAILURE;
2458
2459   return SUCCESS;
2460 }
2461
2462
2463 /* Resolve one part of an array index.  */
2464
2465 try
2466 gfc_resolve_index (gfc_expr * index, int check_scalar)
2467 {
2468   gfc_typespec ts;
2469
2470   if (index == NULL)
2471     return SUCCESS;
2472
2473   if (gfc_resolve_expr (index) == FAILURE)
2474     return FAILURE;
2475
2476   if (check_scalar && index->rank != 0)
2477     {
2478       gfc_error ("Array index at %L must be scalar", &index->where);
2479       return FAILURE;
2480     }
2481
2482   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
2483     {
2484       gfc_error ("Array index at %L must be of INTEGER type",
2485                  &index->where);
2486       return FAILURE;
2487     }
2488
2489   if (index->ts.type == BT_REAL)
2490     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
2491                         &index->where) == FAILURE)
2492       return FAILURE;
2493
2494   if (index->ts.kind != gfc_index_integer_kind
2495       || index->ts.type != BT_INTEGER)
2496     {
2497       gfc_clear_ts (&ts);
2498       ts.type = BT_INTEGER;
2499       ts.kind = gfc_index_integer_kind;
2500
2501       gfc_convert_type_warn (index, &ts, 2, 0);
2502     }
2503
2504   return SUCCESS;
2505 }
2506
2507 /* Resolve a dim argument to an intrinsic function.  */
2508
2509 try
2510 gfc_resolve_dim_arg (gfc_expr *dim)
2511 {
2512   if (dim == NULL)
2513     return SUCCESS;
2514
2515   if (gfc_resolve_expr (dim) == FAILURE)
2516     return FAILURE;
2517
2518   if (dim->rank != 0)
2519     {
2520       gfc_error ("Argument dim at %L must be scalar", &dim->where);
2521       return FAILURE;
2522
2523     }
2524   if (dim->ts.type != BT_INTEGER)
2525     {
2526       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
2527       return FAILURE;
2528     }
2529   if (dim->ts.kind != gfc_index_integer_kind)
2530     {
2531       gfc_typespec ts;
2532
2533       ts.type = BT_INTEGER;
2534       ts.kind = gfc_index_integer_kind;
2535
2536       gfc_convert_type_warn (dim, &ts, 2, 0);
2537     }
2538
2539   return SUCCESS;
2540 }
2541
2542 /* Given an expression that contains array references, update those array
2543    references to point to the right array specifications.  While this is
2544    filled in during matching, this information is difficult to save and load
2545    in a module, so we take care of it here.
2546
2547    The idea here is that the original array reference comes from the
2548    base symbol.  We traverse the list of reference structures, setting
2549    the stored reference to references.  Component references can
2550    provide an additional array specification.  */
2551
2552 static void
2553 find_array_spec (gfc_expr * e)
2554 {
2555   gfc_array_spec *as;
2556   gfc_component *c;
2557   gfc_symbol *derived;
2558   gfc_ref *ref;
2559
2560   as = e->symtree->n.sym->as;
2561   derived = NULL;
2562
2563   for (ref = e->ref; ref; ref = ref->next)
2564     switch (ref->type)
2565       {
2566       case REF_ARRAY:
2567         if (as == NULL)
2568           gfc_internal_error ("find_array_spec(): Missing spec");
2569
2570         ref->u.ar.as = as;
2571         as = NULL;
2572         break;
2573
2574       case REF_COMPONENT:
2575         if (derived == NULL)
2576           derived = e->symtree->n.sym->ts.derived;
2577
2578         c = derived->components;
2579
2580         for (; c; c = c->next)
2581           if (c == ref->u.c.component)
2582             {
2583               /* Track the sequence of component references.  */
2584               if (c->ts.type == BT_DERIVED)
2585                 derived = c->ts.derived;
2586               break;
2587             }
2588
2589         if (c == NULL)
2590           gfc_internal_error ("find_array_spec(): Component not found");
2591
2592         if (c->dimension)
2593           {
2594             if (as != NULL)
2595               gfc_internal_error ("find_array_spec(): unused as(1)");
2596             as = c->as;
2597           }
2598
2599         break;
2600
2601       case REF_SUBSTRING:
2602         break;
2603       }
2604
2605   if (as != NULL)
2606     gfc_internal_error ("find_array_spec(): unused as(2)");
2607 }
2608
2609
2610 /* Resolve an array reference.  */
2611
2612 static try
2613 resolve_array_ref (gfc_array_ref * ar)
2614 {
2615   int i, check_scalar;
2616   gfc_expr *e;
2617
2618   for (i = 0; i < ar->dimen; i++)
2619     {
2620       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
2621
2622       if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
2623         return FAILURE;
2624       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
2625         return FAILURE;
2626       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
2627         return FAILURE;
2628
2629       e = ar->start[i];
2630
2631       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
2632         switch (e->rank)
2633           {
2634           case 0:
2635             ar->dimen_type[i] = DIMEN_ELEMENT;
2636             break;
2637
2638           case 1:
2639             ar->dimen_type[i] = DIMEN_VECTOR;
2640             if (e->expr_type == EXPR_VARIABLE
2641                    && e->symtree->n.sym->ts.type == BT_DERIVED)
2642               ar->start[i] = gfc_get_parentheses (e);
2643             break;
2644
2645           default:
2646             gfc_error ("Array index at %L is an array of rank %d",
2647                        &ar->c_where[i], e->rank);
2648             return FAILURE;
2649           }
2650     }
2651
2652   /* If the reference type is unknown, figure out what kind it is.  */
2653
2654   if (ar->type == AR_UNKNOWN)
2655     {
2656       ar->type = AR_ELEMENT;
2657       for (i = 0; i < ar->dimen; i++)
2658         if (ar->dimen_type[i] == DIMEN_RANGE
2659             || ar->dimen_type[i] == DIMEN_VECTOR)
2660           {
2661             ar->type = AR_SECTION;
2662             break;
2663           }
2664     }
2665
2666   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
2667     return FAILURE;
2668
2669   return SUCCESS;
2670 }
2671
2672
2673 static try
2674 resolve_substring (gfc_ref * ref)
2675 {
2676
2677   if (ref->u.ss.start != NULL)
2678     {
2679       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
2680         return FAILURE;
2681
2682       if (ref->u.ss.start->ts.type != BT_INTEGER)
2683         {
2684           gfc_error ("Substring start index at %L must be of type INTEGER",
2685                      &ref->u.ss.start->where);
2686           return FAILURE;
2687         }
2688
2689       if (ref->u.ss.start->rank != 0)
2690         {
2691           gfc_error ("Substring start index at %L must be scalar",
2692                      &ref->u.ss.start->where);
2693           return FAILURE;
2694         }
2695
2696       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
2697           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
2698               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
2699         {
2700           gfc_error ("Substring start index at %L is less than one",
2701                      &ref->u.ss.start->where);
2702           return FAILURE;
2703         }
2704     }
2705
2706   if (ref->u.ss.end != NULL)
2707     {
2708       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
2709         return FAILURE;
2710
2711       if (ref->u.ss.end->ts.type != BT_INTEGER)
2712         {
2713           gfc_error ("Substring end index at %L must be of type INTEGER",
2714                      &ref->u.ss.end->where);
2715           return FAILURE;
2716         }
2717
2718       if (ref->u.ss.end->rank != 0)
2719         {
2720           gfc_error ("Substring end index at %L must be scalar",
2721                      &ref->u.ss.end->where);
2722           return FAILURE;
2723         }
2724
2725       if (ref->u.ss.length != NULL
2726           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
2727           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
2728               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
2729         {
2730           gfc_error ("Substring end index at %L exceeds the string length",
2731                      &ref->u.ss.start->where);
2732           return FAILURE;
2733         }
2734     }
2735
2736   return SUCCESS;
2737 }
2738
2739
2740 /* Resolve subtype references.  */
2741
2742 static try
2743 resolve_ref (gfc_expr * expr)
2744 {
2745   int current_part_dimension, n_components, seen_part_dimension;
2746   gfc_ref *ref;
2747
2748   for (ref = expr->ref; ref; ref = ref->next)
2749     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
2750       {
2751         find_array_spec (expr);
2752         break;
2753       }
2754
2755   for (ref = expr->ref; ref; ref = ref->next)
2756     switch (ref->type)
2757       {
2758       case REF_ARRAY:
2759         if (resolve_array_ref (&ref->u.ar) == FAILURE)
2760           return FAILURE;
2761         break;
2762
2763       case REF_COMPONENT:
2764         break;
2765
2766       case REF_SUBSTRING:
2767         resolve_substring (ref);
2768         break;
2769       }
2770
2771   /* Check constraints on part references.  */
2772
2773   current_part_dimension = 0;
2774   seen_part_dimension = 0;
2775   n_components = 0;
2776
2777   for (ref = expr->ref; ref; ref = ref->next)
2778     {
2779       switch (ref->type)
2780         {
2781         case REF_ARRAY:
2782           switch (ref->u.ar.type)
2783             {
2784             case AR_FULL:
2785             case AR_SECTION:
2786               current_part_dimension = 1;
2787               break;
2788
2789             case AR_ELEMENT:
2790               current_part_dimension = 0;
2791               break;
2792
2793             case AR_UNKNOWN:
2794               gfc_internal_error ("resolve_ref(): Bad array reference");
2795             }
2796
2797           break;
2798
2799         case REF_COMPONENT:
2800           if ((current_part_dimension || seen_part_dimension)
2801               && ref->u.c.component->pointer)
2802             {
2803               gfc_error
2804                 ("Component to the right of a part reference with nonzero "
2805                  "rank must not have the POINTER attribute at %L",
2806                  &expr->where);
2807               return FAILURE;
2808             }
2809
2810           n_components++;
2811           break;
2812
2813         case REF_SUBSTRING:
2814           break;
2815         }
2816
2817       if (((ref->type == REF_COMPONENT && n_components > 1)
2818            || ref->next == NULL)
2819           && current_part_dimension
2820           && seen_part_dimension)
2821         {
2822
2823           gfc_error ("Two or more part references with nonzero rank must "
2824                      "not be specified at %L", &expr->where);
2825           return FAILURE;
2826         }
2827
2828       if (ref->type == REF_COMPONENT)
2829         {
2830           if (current_part_dimension)
2831             seen_part_dimension = 1;
2832
2833           /* reset to make sure */
2834           current_part_dimension = 0;
2835         }
2836     }
2837
2838   return SUCCESS;
2839 }
2840
2841
2842 /* Given an expression, determine its shape.  This is easier than it sounds.
2843    Leaves the shape array NULL if it is not possible to determine the shape.  */
2844
2845 static void
2846 expression_shape (gfc_expr * e)
2847 {
2848   mpz_t array[GFC_MAX_DIMENSIONS];
2849   int i;
2850
2851   if (e->rank == 0 || e->shape != NULL)
2852     return;
2853
2854   for (i = 0; i < e->rank; i++)
2855     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
2856       goto fail;
2857
2858   e->shape = gfc_get_shape (e->rank);
2859
2860   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
2861
2862   return;
2863
2864 fail:
2865   for (i--; i >= 0; i--)
2866     mpz_clear (array[i]);
2867 }
2868
2869
2870 /* Given a variable expression node, compute the rank of the expression by
2871    examining the base symbol and any reference structures it may have.  */
2872
2873 static void
2874 expression_rank (gfc_expr * e)
2875 {
2876   gfc_ref *ref;
2877   int i, rank;
2878
2879   if (e->ref == NULL)
2880     {
2881       if (e->expr_type == EXPR_ARRAY)
2882         goto done;
2883       /* Constructors can have a rank different from one via RESHAPE().  */
2884
2885       if (e->symtree == NULL)
2886         {
2887           e->rank = 0;
2888           goto done;
2889         }
2890
2891       e->rank = (e->symtree->n.sym->as == NULL)
2892                   ? 0 : e->symtree->n.sym->as->rank;
2893       goto done;
2894     }
2895
2896   rank = 0;
2897
2898   for (ref = e->ref; ref; ref = ref->next)
2899     {
2900       if (ref->type != REF_ARRAY)
2901         continue;
2902
2903       if (ref->u.ar.type == AR_FULL)
2904         {
2905           rank = ref->u.ar.as->rank;
2906           break;
2907         }
2908
2909       if (ref->u.ar.type == AR_SECTION)
2910         {
2911           /* Figure out the rank of the section.  */
2912           if (rank != 0)
2913             gfc_internal_error ("expression_rank(): Two array specs");
2914
2915           for (i = 0; i < ref->u.ar.dimen; i++)
2916             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
2917                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
2918               rank++;
2919
2920           break;
2921         }
2922     }
2923
2924   e->rank = rank;
2925
2926 done:
2927   expression_shape (e);
2928 }
2929
2930
2931 /* Resolve a variable expression.  */
2932
2933 static try
2934 resolve_variable (gfc_expr * e)
2935 {
2936   gfc_symbol *sym;
2937   try t;
2938
2939   t = SUCCESS;
2940
2941   if (e->symtree == NULL)
2942     return FAILURE;
2943
2944   if (e->ref && resolve_ref (e) == FAILURE)
2945     return FAILURE;
2946
2947   sym = e->symtree->n.sym;
2948   if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
2949     {
2950       e->ts.type = BT_PROCEDURE;
2951       return SUCCESS;
2952     }
2953
2954   if (sym->ts.type != BT_UNKNOWN)
2955     gfc_variable_attr (e, &e->ts);
2956   else
2957     {
2958       /* Must be a simple variable reference.  */
2959       if (gfc_set_default_type (sym, 1, NULL) == FAILURE)
2960         return FAILURE;
2961       e->ts = sym->ts;
2962     }
2963
2964   if (check_assumed_size_reference (sym, e))
2965     return FAILURE;
2966
2967   /* Deal with forward references to entries during resolve_code, to
2968      satisfy, at least partially, 12.5.2.5.  */
2969   if (gfc_current_ns->entries
2970         && current_entry_id == sym->entry_id
2971         && cs_base
2972         && cs_base->current
2973         && cs_base->current->op != EXEC_ENTRY)
2974     {
2975       gfc_entry_list *entry;
2976       gfc_formal_arglist *formal;
2977       int n;
2978       bool seen;
2979
2980       /* If the symbol is a dummy...  */
2981       if (sym->attr.dummy)
2982         {
2983           entry = gfc_current_ns->entries;
2984           seen = false;
2985
2986           /* ...test if the symbol is a parameter of previous entries.  */
2987           for (; entry && entry->id <= current_entry_id; entry = entry->next)
2988             for (formal = entry->sym->formal; formal; formal = formal->next)
2989               {
2990                 if (formal->sym && sym->name == formal->sym->name)
2991                   seen = true;
2992               }
2993
2994           /*  If it has not been seen as a dummy, this is an error.  */
2995           if (!seen)
2996             {
2997               if (specification_expr)
2998                 gfc_error ("Variable '%s',used in a specification expression, "
2999                            "is referenced at %L before the ENTRY statement "
3000                            "in which it is a parameter",
3001                            sym->name, &cs_base->current->loc);
3002               else
3003                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
3004                            "statement in which it is a parameter",
3005                            sym->name, &cs_base->current->loc);
3006               t = FAILURE;
3007             }
3008         }
3009
3010       /* Now do the same check on the specification expressions.  */
3011       specification_expr = 1;
3012       if (sym->ts.type == BT_CHARACTER
3013             && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
3014         t = FAILURE;
3015
3016       if (sym->as)
3017         for (n = 0; n < sym->as->rank; n++)
3018           {
3019              specification_expr = 1;
3020              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
3021                t = FAILURE;
3022              specification_expr = 1;
3023              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
3024                t = FAILURE;
3025           }
3026       specification_expr = 0;
3027
3028       if (t == SUCCESS)
3029         /* Update the symbol's entry level.  */
3030         sym->entry_id = current_entry_id + 1;
3031     }
3032
3033   return t;
3034 }
3035
3036
3037 /* Resolve an expression.  That is, make sure that types of operands agree
3038    with their operators, intrinsic operators are converted to function calls
3039    for overloaded types and unresolved function references are resolved.  */
3040
3041 try
3042 gfc_resolve_expr (gfc_expr * e)
3043 {
3044   try t;
3045
3046   if (e == NULL)
3047     return SUCCESS;
3048
3049   switch (e->expr_type)
3050     {
3051     case EXPR_OP:
3052       t = resolve_operator (e);
3053       break;
3054
3055     case EXPR_FUNCTION:
3056       t = resolve_function (e);
3057       break;
3058
3059     case EXPR_VARIABLE:
3060       t = resolve_variable (e);
3061       if (t == SUCCESS)
3062         expression_rank (e);
3063       break;
3064
3065     case EXPR_SUBSTRING:
3066       t = resolve_ref (e);
3067       break;
3068
3069     case EXPR_CONSTANT:
3070     case EXPR_NULL:
3071       t = SUCCESS;
3072       break;
3073
3074     case EXPR_ARRAY:
3075       t = FAILURE;
3076       if (resolve_ref (e) == FAILURE)
3077         break;
3078
3079       t = gfc_resolve_array_constructor (e);
3080       /* Also try to expand a constructor.  */
3081       if (t == SUCCESS)
3082         {
3083           expression_rank (e);
3084           gfc_expand_constructor (e);
3085         }
3086
3087       /* This provides the opportunity for the length of constructors with character
3088         valued function elements to propogate the string length to the expression.  */
3089       if (e->ts.type == BT_CHARACTER)
3090         gfc_resolve_character_array_constructor (e);
3091
3092       break;
3093
3094     case EXPR_STRUCTURE:
3095       t = resolve_ref (e);
3096       if (t == FAILURE)
3097         break;
3098
3099       t = resolve_structure_cons (e);
3100       if (t == FAILURE)
3101         break;
3102
3103       t = gfc_simplify_expr (e, 0);
3104       break;
3105
3106     default:
3107       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
3108     }
3109
3110   return t;
3111 }
3112
3113
3114 /* Resolve an expression from an iterator.  They must be scalar and have
3115    INTEGER or (optionally) REAL type.  */
3116
3117 static try
3118 gfc_resolve_iterator_expr (gfc_expr * expr, bool real_ok,
3119                            const char * name_msgid)
3120 {
3121   if (gfc_resolve_expr (expr) == FAILURE)
3122     return FAILURE;
3123
3124   if (expr->rank != 0)
3125     {
3126       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
3127       return FAILURE;
3128     }
3129
3130   if (!(expr->ts.type == BT_INTEGER
3131         || (expr->ts.type == BT_REAL && real_ok)))
3132     {
3133       if (real_ok)
3134         gfc_error ("%s at %L must be INTEGER or REAL", _(name_msgid),
3135                    &expr->where);
3136       else
3137         gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
3138       return FAILURE;
3139     }
3140   return SUCCESS;
3141 }
3142
3143
3144 /* Resolve the expressions in an iterator structure.  If REAL_OK is
3145    false allow only INTEGER type iterators, otherwise allow REAL types.  */
3146
3147 try
3148 gfc_resolve_iterator (gfc_iterator * iter, bool real_ok)
3149 {
3150
3151   if (iter->var->ts.type == BT_REAL)
3152     gfc_notify_std (GFC_STD_F95_DEL,
3153                     "Obsolete: REAL DO loop iterator at %L",
3154                     &iter->var->where);
3155
3156   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
3157       == FAILURE)
3158     return FAILURE;
3159
3160   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
3161     {
3162       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
3163                  &iter->var->where);
3164       return FAILURE;
3165     }
3166
3167   if (gfc_resolve_iterator_expr (iter->start, real_ok,
3168                                  "Start expression in DO loop") == FAILURE)
3169     return FAILURE;
3170
3171   if (gfc_resolve_iterator_expr (iter->end, real_ok,
3172                                  "End expression in DO loop") == FAILURE)
3173     return FAILURE;
3174
3175   if (gfc_resolve_iterator_expr (iter->step, real_ok,
3176                                  "Step expression in DO loop") == FAILURE)
3177     return FAILURE;
3178
3179   if (iter->step->expr_type == EXPR_CONSTANT)
3180     {
3181       if ((iter->step->ts.type == BT_INTEGER
3182            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
3183           || (iter->step->ts.type == BT_REAL
3184               && mpfr_sgn (iter->step->value.real) == 0))
3185         {
3186           gfc_error ("Step expression in DO loop at %L cannot be zero",
3187                      &iter->step->where);
3188           return FAILURE;
3189         }
3190     }
3191
3192   /* Convert start, end, and step to the same type as var.  */
3193   if (iter->start->ts.kind != iter->var->ts.kind
3194       || iter->start->ts.type != iter->var->ts.type)
3195     gfc_convert_type (iter->start, &iter->var->ts, 2);
3196
3197   if (iter->end->ts.kind != iter->var->ts.kind
3198       || iter->end->ts.type != iter->var->ts.type)
3199     gfc_convert_type (iter->end, &iter->var->ts, 2);
3200
3201   if (iter->step->ts.kind != iter->var->ts.kind
3202       || iter->step->ts.type != iter->var->ts.type)
3203     gfc_convert_type (iter->step, &iter->var->ts, 2);
3204
3205   return SUCCESS;
3206 }
3207
3208
3209 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
3210    to be a scalar INTEGER variable.  The subscripts and stride are scalar
3211    INTEGERs, and if stride is a constant it must be nonzero.  */
3212
3213 static void
3214 resolve_forall_iterators (gfc_forall_iterator * iter)
3215 {
3216
3217   while (iter)
3218     {
3219       if (gfc_resolve_expr (iter->var) == SUCCESS
3220           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
3221         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
3222                    &iter->var->where);
3223
3224       if (gfc_resolve_expr (iter->start) == SUCCESS
3225           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
3226         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
3227                    &iter->start->where);
3228       if (iter->var->ts.kind != iter->start->ts.kind)
3229         gfc_convert_type (iter->start, &iter->var->ts, 2);
3230
3231       if (gfc_resolve_expr (iter->end) == SUCCESS
3232           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
3233         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
3234                    &iter->end->where);
3235       if (iter->var->ts.kind != iter->end->ts.kind)
3236         gfc_convert_type (iter->end, &iter->var->ts, 2);
3237
3238       if (gfc_resolve_expr (iter->stride) == SUCCESS)
3239         {
3240           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
3241             gfc_error ("FORALL stride expression at %L must be a scalar %s",
3242                         &iter->stride->where, "INTEGER");
3243
3244           if (iter->stride->expr_type == EXPR_CONSTANT
3245               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
3246             gfc_error ("FORALL stride expression at %L cannot be zero",
3247                        &iter->stride->where);
3248         }
3249       if (iter->var->ts.kind != iter->stride->ts.kind)
3250         gfc_convert_type (iter->stride, &iter->var->ts, 2);
3251
3252       iter = iter->next;
3253     }
3254 }
3255
3256
3257 /* Given a pointer to a symbol that is a derived type, see if any components
3258    have the POINTER attribute.  The search is recursive if necessary.
3259    Returns zero if no pointer components are found, nonzero otherwise.  */
3260
3261 static int
3262 derived_pointer (gfc_symbol * sym)
3263 {
3264   gfc_component *c;
3265
3266   for (c = sym->components; c; c = c->next)
3267     {
3268       if (c->pointer)
3269         return 1;
3270
3271       if (c->ts.type == BT_DERIVED && derived_pointer (c->ts.derived))
3272         return 1;
3273     }
3274
3275   return 0;
3276 }
3277
3278
3279 /* Given a pointer to a symbol that is a derived type, see if it's
3280    inaccessible, i.e. if it's defined in another module and the components are
3281    PRIVATE.  The search is recursive if necessary.  Returns zero if no
3282    inaccessible components are found, nonzero otherwise.  */
3283
3284 static int
3285 derived_inaccessible (gfc_symbol *sym)
3286 {
3287   gfc_component *c;
3288
3289   if (sym->attr.use_assoc && sym->component_access == ACCESS_PRIVATE)
3290     return 1;
3291
3292   for (c = sym->components; c; c = c->next)
3293     {
3294         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
3295           return 1;
3296     }
3297
3298   return 0;
3299 }
3300
3301
3302 /* Resolve the argument of a deallocate expression.  The expression must be
3303    a pointer or a full array.  */
3304
3305 static try
3306 resolve_deallocate_expr (gfc_expr * e)
3307 {
3308   symbol_attribute attr;
3309   int allocatable;
3310   gfc_ref *ref;
3311
3312   if (gfc_resolve_expr (e) == FAILURE)
3313     return FAILURE;
3314
3315   attr = gfc_expr_attr (e);
3316   if (attr.pointer)
3317     return SUCCESS;
3318
3319   if (e->expr_type != EXPR_VARIABLE)
3320     goto bad;
3321
3322   allocatable = e->symtree->n.sym->attr.allocatable;
3323   for (ref = e->ref; ref; ref = ref->next)
3324     switch (ref->type)
3325       {
3326       case REF_ARRAY:
3327         if (ref->u.ar.type != AR_FULL)
3328           allocatable = 0;
3329         break;
3330
3331       case REF_COMPONENT:
3332         allocatable = (ref->u.c.component->as != NULL
3333                        && ref->u.c.component->as->type == AS_DEFERRED);
3334         break;
3335
3336       case REF_SUBSTRING:
3337         allocatable = 0;
3338         break;
3339       }
3340
3341   if (allocatable == 0)
3342     {
3343     bad:
3344       gfc_error ("Expression in DEALLOCATE statement at %L must be "
3345                  "ALLOCATABLE or a POINTER", &e->where);
3346     }
3347
3348   if (e->symtree->n.sym->attr.intent == INTENT_IN)
3349     {
3350       gfc_error ("Can't deallocate INTENT(IN) variable '%s' at %L",
3351                  e->symtree->n.sym->name, &e->where);
3352       return FAILURE;
3353     }
3354
3355   return SUCCESS;
3356 }
3357
3358 /* Returns true if the expression e contains a reference the symbol sym.  */
3359 static bool
3360 find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
3361 {
3362   gfc_actual_arglist *arg;
3363   gfc_ref *ref;
3364   int i;
3365   bool rv = false;
3366
3367   if (e == NULL)
3368     return rv;
3369
3370   switch (e->expr_type)
3371     {
3372     case EXPR_FUNCTION:
3373       for (arg = e->value.function.actual; arg; arg = arg->next)
3374         rv = rv || find_sym_in_expr (sym, arg->expr);
3375       break;
3376
3377     /* If the variable is not the same as the dependent, 'sym', and
3378        it is not marked as being declared and it is in the same
3379        namespace as 'sym', add it to the local declarations.  */
3380     case EXPR_VARIABLE:
3381       if (sym == e->symtree->n.sym)
3382         return true;
3383       break;
3384
3385     case EXPR_OP:
3386       rv = rv || find_sym_in_expr (sym, e->value.op.op1);
3387       rv = rv || find_sym_in_expr (sym, e->value.op.op2);
3388       break;
3389
3390     default:
3391       break;
3392     }
3393
3394   if (e->ref)
3395     {
3396       for (ref = e->ref; ref; ref = ref->next)
3397         {
3398           switch (ref->type)
3399             {
3400             case REF_ARRAY:
3401               for (i = 0; i < ref->u.ar.dimen; i++)
3402                 {
3403                   rv = rv || find_sym_in_expr (sym, ref->u.ar.start[i]);
3404                   rv = rv || find_sym_in_expr (sym, ref->u.ar.end[i]);
3405                   rv = rv || find_sym_in_expr (sym, ref->u.ar.stride[i]);
3406                 }
3407               break;
3408
3409             case REF_SUBSTRING:
3410               rv = rv || find_sym_in_expr (sym, ref->u.ss.start);
3411               rv = rv || find_sym_in_expr (sym, ref->u.ss.end);
3412               break;
3413
3414             case REF_COMPONENT:
3415               if (ref->u.c.component->ts.type == BT_CHARACTER
3416                     && ref->u.c.component->ts.cl->length->expr_type
3417                                                 != EXPR_CONSTANT)
3418                 rv = rv || find_sym_in_expr (sym, ref->u.c.component->ts.cl->length);
3419
3420               if (ref->u.c.component->as)
3421                 for (i = 0; i < ref->u.c.component->as->rank; i++)
3422                   {
3423                     rv = rv || find_sym_in_expr (sym, ref->u.c.component->as->lower[i]);
3424                     rv = rv || find_sym_in_expr (sym, ref->u.c.component->as->upper[i]);
3425                   }
3426               break;
3427             }
3428         }
3429     }
3430   return rv;
3431 }
3432
3433
3434 /* Given the expression node e for an allocatable/pointer of derived type to be
3435    allocated, get the expression node to be initialized afterwards (needed for
3436    derived types with default initializers, and derived types with allocatable
3437    components that need nullification.)  */
3438
3439 static gfc_expr *
3440 expr_to_initialize (gfc_expr * e)
3441 {
3442   gfc_expr *result;
3443   gfc_ref *ref;
3444   int i;
3445
3446   result = gfc_copy_expr (e);
3447
3448   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
3449   for (ref = result->ref; ref; ref = ref->next)
3450     if (ref->type == REF_ARRAY && ref->next == NULL)
3451       {
3452         ref->u.ar.type = AR_FULL;
3453
3454         for (i = 0; i < ref->u.ar.dimen; i++)
3455           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
3456
3457         result->rank = ref->u.ar.dimen;
3458         break;
3459       }
3460
3461   return result;
3462 }
3463
3464
3465 /* Resolve the expression in an ALLOCATE statement, doing the additional
3466    checks to see whether the expression is OK or not.  The expression must
3467    have a trailing array reference that gives the size of the array.  */
3468
3469 static try
3470 resolve_allocate_expr (gfc_expr * e, gfc_code * code)
3471 {
3472   int i, pointer, allocatable, dimension;
3473   symbol_attribute attr;
3474   gfc_ref *ref, *ref2;
3475   gfc_array_ref *ar;
3476   gfc_code *init_st;
3477   gfc_expr *init_e;
3478   gfc_symbol *sym;
3479   gfc_alloc *a;
3480
3481   if (gfc_resolve_expr (e) == FAILURE)
3482     return FAILURE;
3483
3484   if (code->expr && code->expr->expr_type == EXPR_VARIABLE)
3485     sym = code->expr->symtree->n.sym;
3486   else
3487     sym = NULL;
3488
3489   /* Make sure the expression is allocatable or a pointer.  If it is
3490      pointer, the next-to-last reference must be a pointer.  */
3491
3492   ref2 = NULL;
3493
3494   if (e->expr_type != EXPR_VARIABLE)
3495     {
3496       allocatable = 0;
3497
3498       attr = gfc_expr_attr (e);
3499       pointer = attr.pointer;
3500       dimension = attr.dimension;
3501
3502     }
3503   else
3504     {
3505       allocatable = e->symtree->n.sym->attr.allocatable;
3506       pointer = e->symtree->n.sym->attr.pointer;
3507       dimension = e->symtree->n.sym->attr.dimension;
3508
3509       if (sym == e->symtree->n.sym && sym->ts.type != BT_DERIVED)
3510         {
3511           gfc_error ("The STAT variable '%s' in an ALLOCATE statement must "
3512                      "not be allocated in the same statement at %L",
3513                       sym->name, &e->where);
3514           return FAILURE;
3515         }
3516
3517       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
3518         switch (ref->type)
3519           {
3520           case REF_ARRAY:
3521             if (ref->next != NULL)
3522               pointer = 0;
3523             break;
3524
3525           case REF_COMPONENT:
3526             allocatable = (ref->u.c.component->as != NULL
3527                            && ref->u.c.component->as->type == AS_DEFERRED);
3528
3529             pointer = ref->u.c.component->pointer;
3530             dimension = ref->u.c.component->dimension;
3531             break;
3532
3533           case REF_SUBSTRING:
3534             allocatable = 0;
3535             pointer = 0;
3536             break;
3537           }
3538     }
3539
3540   if (allocatable == 0 && pointer == 0)
3541     {
3542       gfc_error ("Expression in ALLOCATE statement at %L must be "
3543                  "ALLOCATABLE or a POINTER", &e->where);
3544       return FAILURE;
3545     }
3546
3547   if (e->symtree->n.sym->attr.intent == INTENT_IN)
3548     {
3549       gfc_error ("Can't allocate INTENT(IN) variable '%s' at %L",
3550                  e->symtree->n.sym->name, &e->where);
3551       return FAILURE;
3552     }
3553
3554   /* Add default initializer for those derived types that need them.  */
3555   if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
3556     {
3557         init_st = gfc_get_code ();
3558         init_st->loc = code->loc;
3559         init_st->op = EXEC_ASSIGN;
3560         init_st->expr = expr_to_initialize (e);
3561         init_st->expr2 = init_e;
3562         init_st->next = code->next;
3563         code->next = init_st;
3564     }
3565
3566   if (pointer && dimension == 0)
3567     return SUCCESS;
3568
3569   /* Make sure the next-to-last reference node is an array specification.  */
3570
3571   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
3572     {
3573       gfc_error ("Array specification required in ALLOCATE statement "
3574                  "at %L", &e->where);
3575       return FAILURE;
3576     }
3577
3578   /* Make sure that the array section reference makes sense in the
3579     context of an ALLOCATE specification.  */
3580
3581   ar = &ref2->u.ar;
3582
3583   for (i = 0; i < ar->dimen; i++)
3584     {
3585       if (ref2->u.ar.type == AR_ELEMENT)
3586         goto check_symbols;
3587
3588       switch (ar->dimen_type[i])
3589         {
3590         case DIMEN_ELEMENT:
3591           break;
3592
3593         case DIMEN_RANGE:
3594           if (ar->start[i] != NULL
3595               && ar->end[i] != NULL
3596               && ar->stride[i] == NULL)
3597             break;
3598
3599           /* Fall Through...  */
3600
3601         case DIMEN_UNKNOWN:
3602         case DIMEN_VECTOR:
3603           gfc_error ("Bad array specification in ALLOCATE statement at %L",
3604                      &e->where);
3605           return FAILURE;
3606         }
3607
3608 check_symbols:
3609
3610       for (a = code->ext.alloc_list; a; a = a->next)
3611         {
3612           sym = a->expr->symtree->n.sym;
3613
3614           /* TODO - check derived type components.  */
3615           if (sym->ts.type == BT_DERIVED)
3616             continue;
3617
3618           if ((ar->start[i] != NULL && find_sym_in_expr (sym, ar->start[i]))
3619                  || (ar->end[i] != NULL && find_sym_in_expr (sym, ar->end[i])))
3620             {
3621               gfc_error ("'%s' must not appear an the array specification at "
3622                          "%L in the same ALLOCATE statement where it is "
3623                          "itself allocated", sym->name, &ar->where);
3624               return FAILURE;
3625             }
3626         }
3627     }
3628
3629   return SUCCESS;
3630 }
3631
3632
3633 /************ SELECT CASE resolution subroutines ************/
3634
3635 /* Callback function for our mergesort variant.  Determines interval
3636    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
3637    op1 > op2.  Assumes we're not dealing with the default case.  
3638    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
3639    There are nine situations to check.  */
3640
3641 static int
3642 compare_cases (const gfc_case * op1, const gfc_case * op2)
3643 {
3644   int retval;
3645
3646   if (op1->low == NULL) /* op1 = (:L)  */
3647     {
3648       /* op2 = (:N), so overlap.  */
3649       retval = 0;
3650       /* op2 = (M:) or (M:N),  L < M  */
3651       if (op2->low != NULL
3652           && gfc_compare_expr (op1->high, op2->low) < 0)
3653         retval = -1;
3654     }
3655   else if (op1->high == NULL) /* op1 = (K:)  */
3656     {
3657       /* op2 = (M:), so overlap.  */
3658       retval = 0;
3659       /* op2 = (:N) or (M:N), K > N  */
3660       if (op2->high != NULL
3661           && gfc_compare_expr (op1->low, op2->high) > 0)
3662         retval = 1;
3663     }
3664   else /* op1 = (K:L)  */
3665     {
3666       if (op2->low == NULL)       /* op2 = (:N), K > N  */
3667         retval = (gfc_compare_expr (op1->low, op2->high) > 0) ? 1 : 0;
3668       else if (op2->high == NULL) /* op2 = (M:), L < M  */
3669         retval = (gfc_compare_expr (op1->high, op2->low) < 0) ? -1 : 0;
3670       else                        /* op2 = (M:N)  */
3671         {
3672           retval =  0;
3673           /* L < M  */
3674           if (gfc_compare_expr (op1->high, op2->low) < 0)
3675             retval =  -1;
3676           /* K > N  */
3677           else if (gfc_compare_expr (op1->low, op2->high) > 0)
3678             retval =  1;
3679         }
3680     }
3681
3682   return retval;
3683 }
3684
3685
3686 /* Merge-sort a double linked case list, detecting overlap in the
3687    process.  LIST is the head of the double linked case list before it
3688    is sorted.  Returns the head of the sorted list if we don't see any
3689    overlap, or NULL otherwise.  */
3690
3691 static gfc_case *
3692 check_case_overlap (gfc_case * list)
3693 {
3694   gfc_case *p, *q, *e, *tail;
3695   int insize, nmerges, psize, qsize, cmp, overlap_seen;
3696
3697   /* If the passed list was empty, return immediately.  */
3698   if (!list)
3699     return NULL;
3700
3701   overlap_seen = 0;
3702   insize = 1;
3703
3704   /* Loop unconditionally.  The only exit from this loop is a return
3705      statement, when we've finished sorting the case list.  */
3706   for (;;)
3707     {
3708       p = list;
3709       list = NULL;
3710       tail = NULL;
3711
3712       /* Count the number of merges we do in this pass.  */
3713       nmerges = 0;
3714
3715       /* Loop while there exists a merge to be done.  */
3716       while (p)
3717         {
3718           int i;
3719
3720           /* Count this merge.  */
3721           nmerges++;
3722
3723           /* Cut the list in two pieces by stepping INSIZE places
3724              forward in the list, starting from P.  */
3725           psize = 0;
3726           q = p;
3727           for (i = 0; i < insize; i++)
3728             {
3729               psize++;
3730               q = q->right;
3731               if (!q)
3732                 break;
3733             }
3734           qsize = insize;
3735
3736           /* Now we have two lists.  Merge them!  */
3737           while (psize > 0 || (qsize > 0 && q != NULL))
3738             {
3739
3740               /* See from which the next case to merge comes from.  */
3741               if (psize == 0)
3742                 {
3743                   /* P is empty so the next case must come from Q.  */
3744                   e = q;
3745                   q = q->right;
3746                   qsize--;
3747                 }
3748               else if (qsize == 0 || q == NULL)
3749                 {
3750                   /* Q is empty.  */
3751                   e = p;
3752                   p = p->right;
3753                   psize--;
3754                 }
3755               else
3756                 {
3757                   cmp = compare_cases (p, q);
3758                   if (cmp < 0)
3759                     {
3760                       /* The whole case range for P is less than the
3761                          one for Q.  */
3762                       e = p;
3763                       p = p->right;
3764                       psize--;
3765                     }
3766                   else if (cmp > 0)
3767                     {
3768                       /* The whole case range for Q is greater than
3769                          the case range for P.  */
3770                       e = q;
3771                       q = q->right;
3772                       qsize--;
3773                     }
3774                   else
3775                     {
3776                       /* The cases overlap, or they are the same
3777                          element in the list.  Either way, we must
3778                          issue an error and get the next case from P.  */
3779                       /* FIXME: Sort P and Q by line number.  */
3780                       gfc_error ("CASE label at %L overlaps with CASE "
3781                                  "label at %L", &p->where, &q->where);
3782                       overlap_seen = 1;
3783                       e = p;
3784                       p = p->right;
3785                       psize--;
3786                     }
3787                 }
3788
3789                 /* Add the next element to the merged list.  */
3790               if (tail)
3791                 tail->right = e;
3792               else
3793                 list = e;
3794               e->left = tail;
3795               tail = e;
3796             }
3797
3798           /* P has now stepped INSIZE places along, and so has Q.  So
3799              they're the same.  */
3800           p = q;
3801         }
3802       tail->right = NULL;
3803
3804       /* If we have done only one merge or none at all, we've
3805          finished sorting the cases.  */
3806       if (nmerges <= 1)
3807         {
3808           if (!overlap_seen)
3809             return list;
3810           else
3811             return NULL;
3812         }
3813
3814       /* Otherwise repeat, merging lists twice the size.  */
3815       insize *= 2;
3816     }
3817 }
3818
3819
3820 /* Check to see if an expression is suitable for use in a CASE statement.
3821    Makes sure that all case expressions are scalar constants of the same
3822    type.  Return FAILURE if anything is wrong.  */
3823
3824 static try
3825 validate_case_label_expr (gfc_expr * e, gfc_expr * case_expr)
3826 {
3827   if (e == NULL) return SUCCESS;
3828
3829   if (e->ts.type != case_expr->ts.type)
3830     {
3831       gfc_error ("Expression in CASE statement at %L must be of type %s",
3832                  &e->where, gfc_basic_typename (case_expr->ts.type));
3833       return FAILURE;
3834     }
3835
3836   /* C805 (R808) For a given case-construct, each case-value shall be of
3837      the same type as case-expr.  For character type, length differences
3838      are allowed, but the kind type parameters shall be the same.  */
3839
3840   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
3841     {
3842       gfc_error("Expression in CASE statement at %L must be kind %d",
3843                 &e->where, case_expr->ts.kind);
3844       return FAILURE;
3845     }
3846
3847   /* Convert the case value kind to that of case expression kind, if needed.
3848      FIXME:  Should a warning be issued?  */
3849   if (e->ts.kind != case_expr->ts.kind)
3850     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
3851
3852   if (e->rank != 0)
3853     {
3854       gfc_error ("Expression in CASE statement at %L must be scalar",
3855                  &e->where);
3856       return FAILURE;
3857     }
3858
3859   return SUCCESS;
3860 }
3861
3862
3863 /* Given a completely parsed select statement, we:
3864
3865      - Validate all expressions and code within the SELECT.
3866      - Make sure that the selection expression is not of the wrong type.
3867      - Make sure that no case ranges overlap.
3868      - Eliminate unreachable cases and unreachable code resulting from
3869        removing case labels.
3870
3871    The standard does allow unreachable cases, e.g. CASE (5:3).  But
3872    they are a hassle for code generation, and to prevent that, we just
3873    cut them out here.  This is not necessary for overlapping cases
3874    because they are illegal and we never even try to generate code.
3875
3876    We have the additional caveat that a SELECT construct could have
3877    been a computed GOTO in the source code. Fortunately we can fairly
3878    easily work around that here: The case_expr for a "real" SELECT CASE
3879    is in code->expr1, but for a computed GOTO it is in code->expr2. All
3880    we have to do is make sure that the case_expr is a scalar integer
3881    expression.  */
3882
3883 static void
3884 resolve_select (gfc_code * code)
3885 {
3886   gfc_code *body;
3887   gfc_expr *case_expr;
3888   gfc_case *cp, *default_case, *tail, *head;
3889   int seen_unreachable;
3890   int seen_logical;
3891   int ncases;
3892   bt type;
3893   try t;
3894
3895   if (code->expr == NULL)
3896     {
3897       /* This was actually a computed GOTO statement.  */
3898       case_expr = code->expr2;
3899       if (case_expr->ts.type != BT_INTEGER
3900           || case_expr->rank != 0)
3901         gfc_error ("Selection expression in computed GOTO statement "
3902                    "at %L must be a scalar integer expression",
3903                    &case_expr->where);
3904
3905       /* Further checking is not necessary because this SELECT was built
3906          by the compiler, so it should always be OK.  Just move the
3907          case_expr from expr2 to expr so that we can handle computed
3908          GOTOs as normal SELECTs from here on.  */
3909       code->expr = code->expr2;
3910       code->expr2 = NULL;
3911       return;
3912     }
3913
3914   case_expr = code->expr;
3915
3916   type = case_expr->ts.type;
3917   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
3918     {
3919       gfc_error ("Argument of SELECT statement at %L cannot be %s",
3920                  &case_expr->where, gfc_typename (&case_expr->ts));
3921
3922       /* Punt. Going on here just produce more garbage error messages.  */
3923       return;
3924     }
3925
3926   if (case_expr->rank != 0)
3927     {
3928       gfc_error ("Argument of SELECT statement at %L must be a scalar "
3929                  "expression", &case_expr->where);
3930
3931       /* Punt.  */
3932       return;
3933     }
3934
3935   /* PR 19168 has a long discussion concerning a mismatch of the kinds
3936      of the SELECT CASE expression and its CASE values.  Walk the lists
3937      of case values, and if we find a mismatch, promote case_expr to
3938      the appropriate kind.  */
3939
3940   if (type == BT_LOGICAL || type == BT_INTEGER)
3941     {
3942       for (body = code->block; body; body = body->block)
3943         {
3944           /* Walk the case label list.  */
3945           for (cp = body->ext.case_list; cp; cp = cp->next)
3946             {
3947               /* Intercept the DEFAULT case.  It does not have a kind.  */
3948               if (cp->low == NULL && cp->high == NULL)
3949                 continue;
3950
3951               /* Unreachable case ranges are discarded, so ignore.  */
3952               if (cp->low != NULL && cp->high != NULL
3953                   && cp->low != cp->high
3954                   && gfc_compare_expr (cp->low, cp->high) > 0)
3955                 continue;
3956
3957               /* FIXME: Should a warning be issued?  */
3958               if (cp->low != NULL
3959                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
3960                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
3961
3962               if (cp->high != NULL
3963                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
3964                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
3965             }
3966          }
3967     }
3968
3969   /* Assume there is no DEFAULT case.  */
3970   default_case = NULL;
3971   head = tail = NULL;
3972   ncases = 0;
3973   seen_logical = 0;
3974
3975   for (body = code->block; body; body = body->block)
3976     {
3977       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
3978       t = SUCCESS;
3979       seen_unreachable = 0;
3980
3981       /* Walk the case label list, making sure that all case labels
3982          are legal.  */
3983       for (cp = body->ext.case_list; cp; cp = cp->next)
3984         {
3985           /* Count the number of cases in the whole construct.  */
3986           ncases++;
3987
3988           /* Intercept the DEFAULT case.  */
3989           if (cp->low == NULL && cp->high == NULL)
3990             {
3991               if (default_case != NULL)
3992                 {
3993                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
3994                              "by a second DEFAULT CASE at %L",
3995                              &default_case->where, &cp->where);
3996                   t = FAILURE;
3997                   break;
3998                 }
3999               else
4000                 {
4001                   default_case = cp;
4002                   continue;
4003                 }
4004             }
4005
4006           /* Deal with single value cases and case ranges.  Errors are
4007              issued from the validation function.  */
4008           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
4009              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
4010             {
4011               t = FAILURE;
4012               break;
4013             }
4014
4015           if (type == BT_LOGICAL
4016               && ((cp->low == NULL || cp->high == NULL)
4017                   || cp->low != cp->high))
4018             {
4019               gfc_error
4020                 ("Logical range in CASE statement at %L is not allowed",
4021                  &cp->low->where);
4022               t = FAILURE;
4023               break;
4024             }
4025
4026           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
4027             {
4028               int value;
4029               value = cp->low->value.logical == 0 ? 2 : 1;
4030               if (value & seen_logical)
4031                 {
4032                   gfc_error ("constant logical value in CASE statement "
4033                              "is repeated at %L",
4034                              &cp->low->where);
4035                   t = FAILURE;
4036                   break;
4037                 }
4038               seen_logical |= value;
4039             }
4040
4041           if (cp->low != NULL && cp->high != NULL
4042               && cp->low != cp->high
4043               && gfc_compare_expr (cp->low, cp->high) > 0)
4044             {
4045               if (gfc_option.warn_surprising)
4046                 gfc_warning ("Range specification at %L can never "
4047                              "be matched", &cp->where);
4048
4049               cp->unreachable = 1;
4050               seen_unreachable = 1;
4051             }
4052           else
4053             {
4054               /* If the case range can be matched, it can also overlap with
4055                  other cases.  To make sure it does not, we put it in a
4056                  double linked list here.  We sort that with a merge sort
4057                  later on to detect any overlapping cases.  */
4058               if (!head)
4059                 {
4060                   head = tail = cp;
4061                   head->right = head->left = NULL;
4062                 }
4063               else
4064                 {
4065                   tail->right = cp;
4066                   tail->right->left = tail;
4067                   tail = tail->right;
4068                   tail->right = NULL;
4069                 }
4070             }
4071         }
4072
4073       /* It there was a failure in the previous case label, give up
4074          for this case label list.  Continue with the next block.  */
4075       if (t == FAILURE)
4076         continue;
4077
4078       /* See if any case labels that are unreachable have been seen.
4079          If so, we eliminate them.  This is a bit of a kludge because
4080          the case lists for a single case statement (label) is a
4081          single forward linked lists.  */
4082       if (seen_unreachable)
4083       {
4084         /* Advance until the first case in the list is reachable.  */
4085         while (body->ext.case_list != NULL
4086                && body->ext.case_list->unreachable)
4087           {
4088             gfc_case *n = body->ext.case_list;
4089             body->ext.case_list = body->ext.case_list->next;
4090             n->next = NULL;
4091             gfc_free_case_list (n);
4092           }
4093
4094         /* Strip all other unreachable cases.  */
4095         if (body->ext.case_list)
4096           {
4097             for (cp = body->ext.case_list; cp->next; cp = cp->next)
4098               {
4099                 if (cp->next->unreachable)
4100                   {
4101                     gfc_case *n = cp->next;
4102                     cp->next = cp->next->next;
4103                     n->next = NULL;
4104                     gfc_free_case_list (n);
4105                   }
4106               }
4107           }
4108       }
4109     }
4110
4111   /* See if there were overlapping cases.  If the check returns NULL,
4112      there was overlap.  In that case we don't do anything.  If head
4113      is non-NULL, we prepend the DEFAULT case.  The sorted list can
4114      then used during code generation for SELECT CASE constructs with
4115      a case expression of a CHARACTER type.  */
4116   if (head)
4117     {
4118       head = check_case_overlap (head);
4119
4120       /* Prepend the default_case if it is there.  */
4121       if (head != NULL && default_case)
4122         {
4123           default_case->left = NULL;
4124           default_case->right = head;
4125           head->left = default_case;
4126         }
4127     }
4128
4129   /* Eliminate dead blocks that may be the result if we've seen
4130      unreachable case labels for a block.  */
4131   for (body = code; body && body->block; body = body->block)
4132     {
4133       if (body->block->ext.case_list == NULL)
4134         {
4135           /* Cut the unreachable block from the code chain.  */
4136           gfc_code *c = body->block;
4137           body->block = c->block;
4138
4139           /* Kill the dead block, but not the blocks below it.  */
4140           c->block = NULL;
4141           gfc_free_statements (c);