OSDN Git Service

fortran/ChangeLog
[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 have 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 || a.volatile_
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                             "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 intrinsics 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             {
2802               if (ref->u.c.component->pointer)
2803                 {
2804                   gfc_error
2805                     ("Component to the right of a part reference with nonzero "
2806                      "rank must not have the POINTER attribute at %L",
2807                      &expr->where);
2808                   return FAILURE;
2809                 }
2810               else if (ref->u.c.component->allocatable)
2811                 {
2812                   gfc_error
2813                     ("Component to the right of a part reference with nonzero "
2814                      "rank must not have the ALLOCATABLE attribute at %L",
2815                      &expr->where);
2816                   return FAILURE;
2817                 }
2818             }
2819
2820           n_components++;
2821           break;
2822
2823         case REF_SUBSTRING:
2824           break;
2825         }
2826
2827       if (((ref->type == REF_COMPONENT && n_components > 1)
2828            || ref->next == NULL)
2829           && current_part_dimension
2830           && seen_part_dimension)
2831         {
2832
2833           gfc_error ("Two or more part references with nonzero rank must "
2834                      "not be specified at %L", &expr->where);
2835           return FAILURE;
2836         }
2837
2838       if (ref->type == REF_COMPONENT)
2839         {
2840           if (current_part_dimension)
2841             seen_part_dimension = 1;
2842
2843           /* reset to make sure */
2844           current_part_dimension = 0;
2845         }
2846     }
2847
2848   return SUCCESS;
2849 }
2850
2851
2852 /* Given an expression, determine its shape.  This is easier than it sounds.
2853    Leaves the shape array NULL if it is not possible to determine the shape.  */
2854
2855 static void
2856 expression_shape (gfc_expr * e)
2857 {
2858   mpz_t array[GFC_MAX_DIMENSIONS];
2859   int i;
2860
2861   if (e->rank == 0 || e->shape != NULL)
2862     return;
2863
2864   for (i = 0; i < e->rank; i++)
2865     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
2866       goto fail;
2867
2868   e->shape = gfc_get_shape (e->rank);
2869
2870   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
2871
2872   return;
2873
2874 fail:
2875   for (i--; i >= 0; i--)
2876     mpz_clear (array[i]);
2877 }
2878
2879
2880 /* Given a variable expression node, compute the rank of the expression by
2881    examining the base symbol and any reference structures it may have.  */
2882
2883 static void
2884 expression_rank (gfc_expr * e)
2885 {
2886   gfc_ref *ref;
2887   int i, rank;
2888
2889   if (e->ref == NULL)
2890     {
2891       if (e->expr_type == EXPR_ARRAY)
2892         goto done;
2893       /* Constructors can have a rank different from one via RESHAPE().  */
2894
2895       if (e->symtree == NULL)
2896         {
2897           e->rank = 0;
2898           goto done;
2899         }
2900
2901       e->rank = (e->symtree->n.sym->as == NULL)
2902                   ? 0 : e->symtree->n.sym->as->rank;
2903       goto done;
2904     }
2905
2906   rank = 0;
2907
2908   for (ref = e->ref; ref; ref = ref->next)
2909     {
2910       if (ref->type != REF_ARRAY)
2911         continue;
2912
2913       if (ref->u.ar.type == AR_FULL)
2914         {
2915           rank = ref->u.ar.as->rank;
2916           break;
2917         }
2918
2919       if (ref->u.ar.type == AR_SECTION)
2920         {
2921           /* Figure out the rank of the section.  */
2922           if (rank != 0)
2923             gfc_internal_error ("expression_rank(): Two array specs");
2924
2925           for (i = 0; i < ref->u.ar.dimen; i++)
2926             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
2927                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
2928               rank++;
2929
2930           break;
2931         }
2932     }
2933
2934   e->rank = rank;
2935
2936 done:
2937   expression_shape (e);
2938 }
2939
2940
2941 /* Resolve a variable expression.  */
2942
2943 static try
2944 resolve_variable (gfc_expr * e)
2945 {
2946   gfc_symbol *sym;
2947   try t;
2948
2949   t = SUCCESS;
2950
2951   if (e->symtree == NULL)
2952     return FAILURE;
2953
2954   if (e->ref && resolve_ref (e) == FAILURE)
2955     return FAILURE;
2956
2957   sym = e->symtree->n.sym;
2958   if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
2959     {
2960       e->ts.type = BT_PROCEDURE;
2961       return SUCCESS;
2962     }
2963
2964   if (sym->ts.type != BT_UNKNOWN)
2965     gfc_variable_attr (e, &e->ts);
2966   else
2967     {
2968       /* Must be a simple variable reference.  */
2969       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
2970         return FAILURE;
2971       e->ts = sym->ts;
2972     }
2973
2974   if (check_assumed_size_reference (sym, e))
2975     return FAILURE;
2976
2977   /* Deal with forward references to entries during resolve_code, to
2978      satisfy, at least partially, 12.5.2.5.  */
2979   if (gfc_current_ns->entries
2980         && current_entry_id == sym->entry_id
2981         && cs_base
2982         && cs_base->current
2983         && cs_base->current->op != EXEC_ENTRY)
2984     {
2985       gfc_entry_list *entry;
2986       gfc_formal_arglist *formal;
2987       int n;
2988       bool seen;
2989
2990       /* If the symbol is a dummy...  */
2991       if (sym->attr.dummy)
2992         {
2993           entry = gfc_current_ns->entries;
2994           seen = false;
2995
2996           /* ...test if the symbol is a parameter of previous entries.  */
2997           for (; entry && entry->id <= current_entry_id; entry = entry->next)
2998             for (formal = entry->sym->formal; formal; formal = formal->next)
2999               {
3000                 if (formal->sym && sym->name == formal->sym->name)
3001                   seen = true;
3002               }
3003
3004           /*  If it has not been seen as a dummy, this is an error.  */
3005           if (!seen)
3006             {
3007               if (specification_expr)
3008                 gfc_error ("Variable '%s',used in a specification expression, "
3009                            "is referenced at %L before the ENTRY statement "
3010                            "in which it is a parameter",
3011                            sym->name, &cs_base->current->loc);
3012               else
3013                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
3014                            "statement in which it is a parameter",
3015                            sym->name, &cs_base->current->loc);
3016               t = FAILURE;
3017             }
3018         }
3019
3020       /* Now do the same check on the specification expressions.  */
3021       specification_expr = 1;
3022       if (sym->ts.type == BT_CHARACTER
3023             && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
3024         t = FAILURE;
3025
3026       if (sym->as)
3027         for (n = 0; n < sym->as->rank; n++)
3028           {
3029              specification_expr = 1;
3030              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
3031                t = FAILURE;
3032              specification_expr = 1;
3033              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
3034                t = FAILURE;
3035           }
3036       specification_expr = 0;
3037
3038       if (t == SUCCESS)
3039         /* Update the symbol's entry level.  */
3040         sym->entry_id = current_entry_id + 1;
3041     }
3042
3043   return t;
3044 }
3045
3046
3047 /* Resolve an expression.  That is, make sure that types of operands agree
3048    with their operators, intrinsic operators are converted to function calls
3049    for overloaded types and unresolved function references are resolved.  */
3050
3051 try
3052 gfc_resolve_expr (gfc_expr * e)
3053 {
3054   try t;
3055
3056   if (e == NULL)
3057     return SUCCESS;
3058
3059   switch (e->expr_type)
3060     {
3061     case EXPR_OP:
3062       t = resolve_operator (e);
3063       break;
3064
3065     case EXPR_FUNCTION:
3066       t = resolve_function (e);
3067       break;
3068
3069     case EXPR_VARIABLE:
3070       t = resolve_variable (e);
3071       if (t == SUCCESS)
3072         expression_rank (e);
3073       break;
3074
3075     case EXPR_SUBSTRING:
3076       t = resolve_ref (e);
3077       break;
3078
3079     case EXPR_CONSTANT:
3080     case EXPR_NULL:
3081       t = SUCCESS;
3082       break;
3083
3084     case EXPR_ARRAY:
3085       t = FAILURE;
3086       if (resolve_ref (e) == FAILURE)
3087         break;
3088
3089       t = gfc_resolve_array_constructor (e);
3090       /* Also try to expand a constructor.  */
3091       if (t == SUCCESS)
3092         {
3093           expression_rank (e);
3094           gfc_expand_constructor (e);
3095         }
3096
3097       /* This provides the opportunity for the length of constructors with character
3098         valued function elements to propogate the string length to the expression.  */
3099       if (e->ts.type == BT_CHARACTER)
3100         gfc_resolve_character_array_constructor (e);
3101
3102       break;
3103
3104     case EXPR_STRUCTURE:
3105       t = resolve_ref (e);
3106       if (t == FAILURE)
3107         break;
3108
3109       t = resolve_structure_cons (e);
3110       if (t == FAILURE)
3111         break;
3112
3113       t = gfc_simplify_expr (e, 0);
3114       break;
3115
3116     default:
3117       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
3118     }
3119
3120   return t;
3121 }
3122
3123
3124 /* Resolve an expression from an iterator.  They must be scalar and have
3125    INTEGER or (optionally) REAL type.  */
3126
3127 static try
3128 gfc_resolve_iterator_expr (gfc_expr * expr, bool real_ok,
3129                            const char * name_msgid)
3130 {
3131   if (gfc_resolve_expr (expr) == FAILURE)
3132     return FAILURE;
3133
3134   if (expr->rank != 0)
3135     {
3136       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
3137       return FAILURE;
3138     }
3139
3140   if (!(expr->ts.type == BT_INTEGER
3141         || (expr->ts.type == BT_REAL && real_ok)))
3142     {
3143       if (real_ok)
3144         gfc_error ("%s at %L must be INTEGER or REAL", _(name_msgid),
3145                    &expr->where);
3146       else
3147         gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
3148       return FAILURE;
3149     }
3150   return SUCCESS;
3151 }
3152
3153
3154 /* Resolve the expressions in an iterator structure.  If REAL_OK is
3155    false allow only INTEGER type iterators, otherwise allow REAL types.  */
3156
3157 try
3158 gfc_resolve_iterator (gfc_iterator * iter, bool real_ok)
3159 {
3160
3161   if (iter->var->ts.type == BT_REAL)
3162     gfc_notify_std (GFC_STD_F95_DEL,
3163                     "Obsolete: REAL DO loop iterator at %L",
3164                     &iter->var->where);
3165
3166   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
3167       == FAILURE)
3168     return FAILURE;
3169
3170   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
3171     {
3172       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
3173                  &iter->var->where);
3174       return FAILURE;
3175     }
3176
3177   if (gfc_resolve_iterator_expr (iter->start, real_ok,
3178                                  "Start expression in DO loop") == FAILURE)
3179     return FAILURE;
3180
3181   if (gfc_resolve_iterator_expr (iter->end, real_ok,
3182                                  "End expression in DO loop") == FAILURE)
3183     return FAILURE;
3184
3185   if (gfc_resolve_iterator_expr (iter->step, real_ok,
3186                                  "Step expression in DO loop") == FAILURE)
3187     return FAILURE;
3188
3189   if (iter->step->expr_type == EXPR_CONSTANT)
3190     {
3191       if ((iter->step->ts.type == BT_INTEGER
3192            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
3193           || (iter->step->ts.type == BT_REAL
3194               && mpfr_sgn (iter->step->value.real) == 0))
3195         {
3196           gfc_error ("Step expression in DO loop at %L cannot be zero",
3197                      &iter->step->where);
3198           return FAILURE;
3199         }
3200     }
3201
3202   /* Convert start, end, and step to the same type as var.  */
3203   if (iter->start->ts.kind != iter->var->ts.kind
3204       || iter->start->ts.type != iter->var->ts.type)
3205     gfc_convert_type (iter->start, &iter->var->ts, 2);
3206
3207   if (iter->end->ts.kind != iter->var->ts.kind
3208       || iter->end->ts.type != iter->var->ts.type)
3209     gfc_convert_type (iter->end, &iter->var->ts, 2);
3210
3211   if (iter->step->ts.kind != iter->var->ts.kind
3212       || iter->step->ts.type != iter->var->ts.type)
3213     gfc_convert_type (iter->step, &iter->var->ts, 2);
3214
3215   return SUCCESS;
3216 }
3217
3218
3219 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
3220    to be a scalar INTEGER variable.  The subscripts and stride are scalar
3221    INTEGERs, and if stride is a constant it must be nonzero.  */
3222
3223 static void
3224 resolve_forall_iterators (gfc_forall_iterator * iter)
3225 {
3226
3227   while (iter)
3228     {
3229       if (gfc_resolve_expr (iter->var) == SUCCESS
3230           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
3231         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
3232                    &iter->var->where);
3233
3234       if (gfc_resolve_expr (iter->start) == SUCCESS
3235           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
3236         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
3237                    &iter->start->where);
3238       if (iter->var->ts.kind != iter->start->ts.kind)
3239         gfc_convert_type (iter->start, &iter->var->ts, 2);
3240
3241       if (gfc_resolve_expr (iter->end) == SUCCESS
3242           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
3243         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
3244                    &iter->end->where);
3245       if (iter->var->ts.kind != iter->end->ts.kind)
3246         gfc_convert_type (iter->end, &iter->var->ts, 2);
3247
3248       if (gfc_resolve_expr (iter->stride) == SUCCESS)
3249         {
3250           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
3251             gfc_error ("FORALL stride expression at %L must be a scalar %s",
3252                         &iter->stride->where, "INTEGER");
3253
3254           if (iter->stride->expr_type == EXPR_CONSTANT
3255               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
3256             gfc_error ("FORALL stride expression at %L cannot be zero",
3257                        &iter->stride->where);
3258         }
3259       if (iter->var->ts.kind != iter->stride->ts.kind)
3260         gfc_convert_type (iter->stride, &iter->var->ts, 2);
3261
3262       iter = iter->next;
3263     }
3264 }
3265
3266
3267 /* Given a pointer to a symbol that is a derived type, see if any components
3268    have the POINTER attribute.  The search is recursive if necessary.
3269    Returns zero if no pointer components are found, nonzero otherwise.  */
3270
3271 static int
3272 derived_pointer (gfc_symbol * sym)
3273 {
3274   gfc_component *c;
3275
3276   for (c = sym->components; c; c = c->next)
3277     {
3278       if (c->pointer)
3279         return 1;
3280
3281       if (c->ts.type == BT_DERIVED && derived_pointer (c->ts.derived))
3282         return 1;
3283     }
3284
3285   return 0;
3286 }
3287
3288
3289 /* Given a pointer to a symbol that is a derived type, see if it's
3290    inaccessible, i.e. if it's defined in another module and the components are
3291    PRIVATE.  The search is recursive if necessary.  Returns zero if no
3292    inaccessible components are found, nonzero otherwise.  */
3293
3294 static int
3295 derived_inaccessible (gfc_symbol *sym)
3296 {
3297   gfc_component *c;
3298
3299   if (sym->attr.use_assoc && sym->component_access == ACCESS_PRIVATE)
3300     return 1;
3301
3302   for (c = sym->components; c; c = c->next)
3303     {
3304         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
3305           return 1;
3306     }
3307
3308   return 0;
3309 }
3310
3311
3312 /* Resolve the argument of a deallocate expression.  The expression must be
3313    a pointer or a full array.  */
3314
3315 static try
3316 resolve_deallocate_expr (gfc_expr * e)
3317 {
3318   symbol_attribute attr;
3319   int allocatable;
3320   gfc_ref *ref;
3321
3322   if (gfc_resolve_expr (e) == FAILURE)
3323     return FAILURE;
3324
3325   attr = gfc_expr_attr (e);
3326   if (attr.pointer)
3327     return SUCCESS;
3328
3329   if (e->expr_type != EXPR_VARIABLE)
3330     goto bad;
3331
3332   allocatable = e->symtree->n.sym->attr.allocatable;
3333   for (ref = e->ref; ref; ref = ref->next)
3334     switch (ref->type)
3335       {
3336       case REF_ARRAY:
3337         if (ref->u.ar.type != AR_FULL)
3338           allocatable = 0;
3339         break;
3340
3341       case REF_COMPONENT:
3342         allocatable = (ref->u.c.component->as != NULL
3343                        && ref->u.c.component->as->type == AS_DEFERRED);
3344         break;
3345
3346       case REF_SUBSTRING:
3347         allocatable = 0;
3348         break;
3349       }
3350
3351   if (allocatable == 0)
3352     {
3353     bad:
3354       gfc_error ("Expression in DEALLOCATE statement at %L must be "
3355                  "ALLOCATABLE or a POINTER", &e->where);
3356     }
3357
3358   if (e->symtree->n.sym->attr.intent == INTENT_IN)
3359     {
3360       gfc_error ("Can't deallocate INTENT(IN) variable '%s' at %L",
3361                  e->symtree->n.sym->name, &e->where);
3362       return FAILURE;
3363     }
3364
3365   return SUCCESS;
3366 }
3367
3368 /* Returns true if the expression e contains a reference the symbol sym.  */
3369 static bool
3370 find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
3371 {
3372   gfc_actual_arglist *arg;
3373   gfc_ref *ref;
3374   int i;
3375   bool rv = false;
3376
3377   if (e == NULL)
3378     return rv;
3379
3380   switch (e->expr_type)
3381     {
3382     case EXPR_FUNCTION:
3383       for (arg = e->value.function.actual; arg; arg = arg->next)
3384         rv = rv || find_sym_in_expr (sym, arg->expr);
3385       break;
3386
3387     /* If the variable is not the same as the dependent, 'sym', and
3388        it is not marked as being declared and it is in the same
3389        namespace as 'sym', add it to the local declarations.  */
3390     case EXPR_VARIABLE:
3391       if (sym == e->symtree->n.sym)
3392         return true;
3393       break;
3394
3395     case EXPR_OP:
3396       rv = rv || find_sym_in_expr (sym, e->value.op.op1);
3397       rv = rv || find_sym_in_expr (sym, e->value.op.op2);
3398       break;
3399
3400     default:
3401       break;
3402     }
3403
3404   if (e->ref)
3405     {
3406       for (ref = e->ref; ref; ref = ref->next)
3407         {
3408           switch (ref->type)
3409             {
3410             case REF_ARRAY:
3411               for (i = 0; i < ref->u.ar.dimen; i++)
3412                 {
3413                   rv = rv || find_sym_in_expr (sym, ref->u.ar.start[i]);
3414                   rv = rv || find_sym_in_expr (sym, ref->u.ar.end[i]);
3415                   rv = rv || find_sym_in_expr (sym, ref->u.ar.stride[i]);
3416                 }
3417               break;
3418
3419             case REF_SUBSTRING:
3420               rv = rv || find_sym_in_expr (sym, ref->u.ss.start);
3421               rv = rv || find_sym_in_expr (sym, ref->u.ss.end);
3422               break;
3423
3424             case REF_COMPONENT:
3425               if (ref->u.c.component->ts.type == BT_CHARACTER
3426                     && ref->u.c.component->ts.cl->length->expr_type
3427                                                 != EXPR_CONSTANT)
3428                 rv = rv || find_sym_in_expr (sym, ref->u.c.component->ts.cl->length);
3429
3430               if (ref->u.c.component->as)
3431                 for (i = 0; i < ref->u.c.component->as->rank; i++)
3432                   {
3433                     rv = rv || find_sym_in_expr (sym, ref->u.c.component->as->lower[i]);
3434                     rv = rv || find_sym_in_expr (sym, ref->u.c.component->as->upper[i]);
3435                   }
3436               break;
3437             }
3438         }
3439     }
3440   return rv;
3441 }
3442
3443
3444 /* Given the expression node e for an allocatable/pointer of derived type to be
3445    allocated, get the expression node to be initialized afterwards (needed for
3446    derived types with default initializers, and derived types with allocatable
3447    components that need nullification.)  */
3448
3449 static gfc_expr *
3450 expr_to_initialize (gfc_expr * e)
3451 {
3452   gfc_expr *result;
3453   gfc_ref *ref;
3454   int i;
3455
3456   result = gfc_copy_expr (e);
3457
3458   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
3459   for (ref = result->ref; ref; ref = ref->next)
3460     if (ref->type == REF_ARRAY && ref->next == NULL)
3461       {
3462         ref->u.ar.type = AR_FULL;
3463
3464         for (i = 0; i < ref->u.ar.dimen; i++)
3465           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
3466
3467         result->rank = ref->u.ar.dimen;
3468         break;
3469       }
3470
3471   return result;
3472 }
3473
3474
3475 /* Resolve the expression in an ALLOCATE statement, doing the additional
3476    checks to see whether the expression is OK or not.  The expression must
3477    have a trailing array reference that gives the size of the array.  */
3478
3479 static try
3480 resolve_allocate_expr (gfc_expr * e, gfc_code * code)
3481 {
3482   int i, pointer, allocatable, dimension;
3483   symbol_attribute attr;
3484   gfc_ref *ref, *ref2;
3485   gfc_array_ref *ar;
3486   gfc_code *init_st;
3487   gfc_expr *init_e;
3488   gfc_symbol *sym;
3489   gfc_alloc *a;
3490
3491   if (gfc_resolve_expr (e) == FAILURE)
3492     return FAILURE;
3493
3494   if (code->expr && code->expr->expr_type == EXPR_VARIABLE)
3495     sym = code->expr->symtree->n.sym;
3496   else
3497     sym = NULL;
3498
3499   /* Make sure the expression is allocatable or a pointer.  If it is
3500      pointer, the next-to-last reference must be a pointer.  */
3501
3502   ref2 = NULL;
3503
3504   if (e->expr_type != EXPR_VARIABLE)
3505     {
3506       allocatable = 0;
3507
3508       attr = gfc_expr_attr (e);
3509       pointer = attr.pointer;
3510       dimension = attr.dimension;
3511
3512     }
3513   else
3514     {
3515       allocatable = e->symtree->n.sym->attr.allocatable;
3516       pointer = e->symtree->n.sym->attr.pointer;
3517       dimension = e->symtree->n.sym->attr.dimension;
3518
3519       if (sym == e->symtree->n.sym && sym->ts.type != BT_DERIVED)
3520         {
3521           gfc_error ("The STAT variable '%s' in an ALLOCATE statement must "
3522                      "not be allocated in the same statement at %L",
3523                       sym->name, &e->where);
3524           return FAILURE;
3525         }
3526
3527       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
3528         switch (ref->type)
3529           {
3530           case REF_ARRAY:
3531             if (ref->next != NULL)
3532               pointer = 0;
3533             break;
3534
3535           case REF_COMPONENT:
3536             allocatable = (ref->u.c.component->as != NULL
3537                            && ref->u.c.component->as->type == AS_DEFERRED);
3538
3539             pointer = ref->u.c.component->pointer;
3540             dimension = ref->u.c.component->dimension;
3541             break;
3542
3543           case REF_SUBSTRING:
3544             allocatable = 0;
3545             pointer = 0;
3546             break;
3547           }
3548     }
3549
3550   if (allocatable == 0 && pointer == 0)
3551     {
3552       gfc_error ("Expression in ALLOCATE statement at %L must be "
3553                  "ALLOCATABLE or a POINTER", &e->where);
3554       return FAILURE;
3555     }
3556
3557   if (e->symtree->n.sym->attr.intent == INTENT_IN)
3558     {
3559       gfc_error ("Can't allocate INTENT(IN) variable '%s' at %L",
3560                  e->symtree->n.sym->name, &e->where);
3561       return FAILURE;
3562     }
3563
3564   /* Add default initializer for those derived types that need them.  */
3565   if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
3566     {
3567         init_st = gfc_get_code ();
3568         init_st->loc = code->loc;
3569         init_st->op = EXEC_INIT_ASSIGN;
3570         init_st->expr = expr_to_initialize (e);
3571         init_st->expr2 = init_e;
3572         init_st->next = code->next;
3573         code->next = init_st;
3574     }
3575
3576   if (pointer && dimension == 0)
3577     return SUCCESS;
3578
3579   /* Make sure the next-to-last reference node is an array specification.  */
3580
3581   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
3582     {
3583       gfc_error ("Array specification required in ALLOCATE statement "
3584                  "at %L", &e->where);
3585       return FAILURE;
3586     }
3587
3588   /* Make sure that the array section reference makes sense in the
3589     context of an ALLOCATE specification.  */
3590
3591   ar = &ref2->u.ar;
3592
3593   for (i = 0; i < ar->dimen; i++)
3594     {
3595       if (ref2->u.ar.type == AR_ELEMENT)
3596         goto check_symbols;
3597
3598       switch (ar->dimen_type[i])
3599         {
3600         case DIMEN_ELEMENT:
3601           break;
3602
3603         case DIMEN_RANGE:
3604           if (ar->start[i] != NULL
3605               && ar->end[i] != NULL
3606               && ar->stride[i] == NULL)
3607             break;
3608
3609           /* Fall Through...  */
3610
3611         case DIMEN_UNKNOWN:
3612         case DIMEN_VECTOR:
3613           gfc_error ("Bad array specification in ALLOCATE statement at %L",
3614                      &e->where);
3615           return FAILURE;
3616         }
3617
3618 check_symbols:
3619
3620       for (a = code->ext.alloc_list; a; a = a->next)
3621         {
3622           sym = a->expr->symtree->n.sym;
3623
3624           /* TODO - check derived type components.  */
3625           if (sym->ts.type == BT_DERIVED)
3626             continue;
3627
3628           if ((ar->start[i] != NULL && find_sym_in_expr (sym, ar->start[i]))
3629                  || (ar->end[i] != NULL && find_sym_in_expr (sym, ar->end[i])))
3630             {
3631               gfc_error ("'%s' must not appear an the array specification at "
3632                          "%L in the same ALLOCATE statement where it is "
3633                          "itself allocated", sym->name, &ar->where);
3634               return FAILURE;
3635             }
3636         }
3637     }
3638
3639   return SUCCESS;
3640 }
3641
3642
3643 /************ SELECT CASE resolution subroutines ************/
3644
3645 /* Callback function for our mergesort variant.  Determines interval
3646    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
3647    op1 > op2.  Assumes we're not dealing with the default case.  
3648    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
3649    There are nine situations to check.  */
3650
3651 static int
3652 compare_cases (const gfc_case * op1, const gfc_case * op2)
3653 {
3654   int retval;
3655
3656   if (op1->low == NULL) /* op1 = (:L)  */
3657     {
3658       /* op2 = (:N), so overlap.  */
3659       retval = 0;
3660       /* op2 = (M:) or (M:N),  L < M  */
3661       if (op2->low != NULL
3662           && gfc_compare_expr (op1->high, op2->low) < 0)
3663         retval = -1;
3664     }
3665   else if (op1->high == NULL) /* op1 = (K:)  */
3666     {
3667       /* op2 = (M:), so overlap.  */
3668       retval = 0;
3669       /* op2 = (:N) or (M:N), K > N  */
3670       if (op2->high != NULL
3671           && gfc_compare_expr (op1->low, op2->high) > 0)
3672         retval = 1;
3673     }
3674   else /* op1 = (K:L)  */
3675     {
3676       if (op2->low == NULL)       /* op2 = (:N), K > N  */
3677         retval = (gfc_compare_expr (op1->low, op2->high) > 0) ? 1 : 0;
3678       else if (op2->high == NULL) /* op2 = (M:), L < M  */
3679         retval = (gfc_compare_expr (op1->high, op2->low) < 0) ? -1 : 0;
3680       else                        /* op2 = (M:N)  */
3681         {
3682           retval =  0;
3683           /* L < M  */
3684           if (gfc_compare_expr (op1->high, op2->low) < 0)
3685             retval =  -1;
3686           /* K > N  */
3687           else if (gfc_compare_expr (op1->low, op2->high) > 0)
3688             retval =  1;
3689         }
3690     }
3691
3692   return retval;
3693 }
3694
3695
3696 /* Merge-sort a double linked case list, detecting overlap in the
3697    process.  LIST is the head of the double linked case list before it
3698    is sorted.  Returns the head of the sorted list if we don't see any
3699    overlap, or NULL otherwise.  */
3700
3701 static gfc_case *
3702 check_case_overlap (gfc_case * list)
3703 {
3704   gfc_case *p, *q, *e, *tail;
3705   int insize, nmerges, psize, qsize, cmp, overlap_seen;
3706
3707   /* If the passed list was empty, return immediately.  */
3708   if (!list)
3709     return NULL;
3710
3711   overlap_seen = 0;
3712   insize = 1;
3713
3714   /* Loop unconditionally.  The only exit from this loop is a return
3715      statement, when we've finished sorting the case list.  */
3716   for (;;)
3717     {
3718       p = list;
3719       list = NULL;
3720       tail = NULL;
3721
3722       /* Count the number of merges we do in this pass.  */
3723       nmerges = 0;
3724
3725       /* Loop while there exists a merge to be done.  */
3726       while (p)
3727         {
3728           int i;
3729
3730           /* Count this merge.  */
3731           nmerges++;
3732
3733           /* Cut the list in two pieces by stepping INSIZE places
3734              forward in the list, starting from P.  */
3735           psize = 0;
3736           q = p;
3737           for (i = 0; i < insize; i++)
3738             {
3739               psize++;
3740               q = q->right;
3741               if (!q)
3742                 break;
3743             }
3744           qsize = insize;
3745
3746           /* Now we have two lists.  Merge them!  */
3747           while (psize > 0 || (qsize > 0 && q != NULL))
3748             {
3749
3750               /* See from which the next case to merge comes from.  */
3751               if (psize == 0)
3752                 {
3753                   /* P is empty so the next case must come from Q.  */
3754                   e = q;
3755                   q = q->right;
3756                   qsize--;
3757                 }
3758               else if (qsize == 0 || q == NULL)
3759                 {
3760                   /* Q is empty.  */
3761                   e = p;
3762                   p = p->right;
3763                   psize--;
3764                 }
3765               else
3766                 {
3767                   cmp = compare_cases (p, q);
3768                   if (cmp < 0)
3769                     {
3770                       /* The whole case range for P is less than the
3771                          one for Q.  */
3772                       e = p;
3773                       p = p->right;
3774                       psize--;
3775                     }
3776                   else if (cmp > 0)
3777                     {
3778                       /* The whole case range for Q is greater than
3779                          the case range for P.  */
3780                       e = q;
3781                       q = q->right;
3782                       qsize--;
3783                     }
3784                   else
3785                     {
3786                       /* The cases overlap, or they are the same
3787                          element in the list.  Either way, we must
3788                          issue an error and get the next case from P.  */
3789                       /* FIXME: Sort P and Q by line number.  */
3790                       gfc_error ("CASE label at %L overlaps with CASE "
3791                                  "label at %L", &p->where, &q->where);
3792                       overlap_seen = 1;
3793                       e = p;
3794                       p = p->right;
3795                       psize--;
3796                     }
3797                 }
3798
3799                 /* Add the next element to the merged list.  */
3800               if (tail)
3801                 tail->right = e;
3802               else
3803                 list = e;
3804               e->left = tail;
3805               tail = e;
3806             }
3807
3808           /* P has now stepped INSIZE places along, and so has Q.  So
3809              they're the same.  */
3810           p = q;
3811         }
3812       tail->right = NULL;
3813
3814       /* If we have done only one merge or none at all, we've
3815          finished sorting the cases.  */
3816       if (nmerges <= 1)
3817         {
3818           if (!overlap_seen)
3819             return list;
3820           else
3821             return NULL;
3822         }
3823
3824       /* Otherwise repeat, merging lists twice the size.  */
3825       insize *= 2;
3826     }
3827 }
3828
3829
3830 /* Check to see if an expression is suitable for use in a CASE statement.
3831    Makes sure that all case expressions are scalar constants of the same
3832    type.  Return FAILURE if anything is wrong.  */
3833
3834 static try
3835 validate_case_label_expr (gfc_expr * e, gfc_expr * case_expr)
3836 {
3837   if (e == NULL) return SUCCESS;
3838
3839   if (e->ts.type != case_expr->ts.type)
3840     {
3841       gfc_error ("Expression in CASE statement at %L must be of type %s",
3842                  &e->where, gfc_basic_typename (case_expr->ts.type));
3843       return FAILURE;
3844     }
3845
3846   /* C805 (R808) For a given case-construct, each case-value shall be of
3847      the same type as case-expr.  For character type, length differences
3848      are allowed, but the kind type parameters shall be the same.  */
3849
3850   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
3851     {
3852       gfc_error("Expression in CASE statement at %L must be kind %d",
3853                 &e->where, case_expr->ts.kind);
3854       return FAILURE;
3855     }
3856
3857   /* Convert the case value kind to that of case expression kind, if needed.
3858      FIXME:  Should a warning be issued?  */
3859   if (e->ts.kind != case_expr->ts.kind)
3860     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
3861
3862   if (e->rank != 0)
3863     {
3864       gfc_error ("Expression in CASE statement at %L must be scalar",
3865                  &e->where);
3866       return FAILURE;
3867     }
3868
3869   return SUCCESS;
3870 }
3871
3872
3873 /* Given a completely parsed select statement, we:
3874
3875      - Validate all expressions and code within the SELECT.
3876      - Make sure that the selection expression is not of the wrong type.
3877      - Make sure that no case ranges overlap.
3878      - Eliminate unreachable cases and unreachable code resulting from
3879        removing case labels.
3880
3881    The standard does allow unreachable cases, e.g. CASE (5:3).  But
3882    they are a hassle for code generation, and to prevent that, we just
3883    cut them out here.  This is not necessary for overlapping cases
3884    because they are illegal and we never even try to generate code.
3885
3886    We have the additional caveat that a SELECT construct could have
3887    been a computed GOTO in the source code. Fortunately we can fairly
3888    easily work around that here: The case_expr for a "real" SELECT CASE
3889    is in code->expr1, but for a computed GOTO it is in code->expr2. All
3890    we have to do is make sure that the case_expr is a scalar integer
3891    expression.  */
3892
3893 static void
3894 resolve_select (gfc_code * code)
3895 {
3896   gfc_code *body;
3897   gfc_expr *case_expr;
3898   gfc_case *cp, *default_case, *tail, *head;
3899   int seen_unreachable;
3900   int seen_logical;
3901   int ncases;
3902   bt type;
3903   try t;
3904
3905   if (code->expr == NULL)
3906     {
3907       /* This was actually a computed GOTO statement.  */
3908       case_expr = code->expr2;
3909       if (case_expr->ts.type != BT_INTEGER
3910           || case_expr->rank != 0)
3911         gfc_error ("Selection expression in computed GOTO statement "
3912                    "at %L must be a scalar integer expression",
3913                    &case_expr->where);
3914
3915       /* Further checking is not necessary because this SELECT was built
3916          by the compiler, so it should always be OK.  Just move the
3917          case_expr from expr2 to expr so that we can handle computed
3918          GOTOs as normal SELECTs from here on.  */
3919       code->expr = code->expr2;
3920       code->expr2 = NULL;
3921       return;
3922     }
3923
3924   case_expr = code->expr;
3925
3926   type = case_expr->ts.type;
3927   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
3928     {
3929       gfc_error ("Argument of SELECT statement at %L cannot be %s",
3930                  &case_expr->where, gfc_typename (&case_expr->ts));
3931
3932       /* Punt. Going on here just produce more garbage error messages.  */
3933       return;
3934     }
3935
3936   if (case_expr->rank != 0)
3937     {
3938       gfc_error ("Argument of SELECT statement at %L must be a scalar "
3939                  "expression", &case_expr->where);
3940
3941       /* Punt.  */
3942       return;
3943     }
3944
3945   /* PR 19168 has a long discussion concerning a mismatch of the kinds
3946      of the SELECT CASE expression and its CASE values.  Walk the lists
3947      of case values, and if we find a mismatch, promote case_expr to
3948      the appropriate kind.  */
3949
3950   if (type == BT_LOGICAL || type == BT_INTEGER)
3951     {
3952       for (body = code->block; body; body = body->block)
3953         {
3954           /* Walk the case label list.  */
3955           for (cp = body->ext.case_list; cp; cp = cp->next)
3956             {
3957               /* Intercept the DEFAULT case.  It does not have a kind.  */
3958               if (cp->low == NULL && cp->high == NULL)
3959                 continue;
3960
3961               /* Unreachable case ranges are discarded, so ignore.  */
3962               if (cp->low != NULL && cp->high != NULL
3963                   && cp->low != cp->high
3964                   && gfc_compare_expr (cp->low, cp->high) > 0)
3965                 continue;
3966
3967               /* FIXME: Should a warning be issued?  */
3968               if (cp->low != NULL
3969                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
3970                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
3971
3972               if (cp->high != NULL
3973                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
3974                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
3975             }
3976          }
3977     }
3978
3979   /* Assume there is no DEFAULT case.  */
3980   default_case = NULL;
3981   head = tail = NULL;
3982   ncases = 0;
3983   seen_logical = 0;
3984
3985   for (body = code->block; body; body = body->block)
3986     {
3987       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
3988       t = SUCCESS;
3989       seen_unreachable = 0;
3990
3991       /* Walk the case label list, making sure that all case labels
3992          are legal.  */
3993       for (cp = body->ext.case_list; cp; cp = cp->next)
3994         {
3995           /* Count the number of cases in the whole construct.  */
3996           ncases++;
3997
3998           /* Intercept the DEFAULT case.  */
3999           if (cp->low == NULL && cp->high == NULL)
4000             {
4001               if (default_case != NULL)
4002                 {
4003                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
4004                              "by a second DEFAULT CASE at %L",
4005                              &default_case->where, &cp->where);
4006                   t = FAILURE;
4007                   break;
4008                 }
4009               else
4010                 {
4011                   default_case = cp;
4012                   continue;
4013                 }
4014             }
4015
4016           /* Deal with single value cases and case ranges.  Errors are
4017              issued from the validation function.  */
4018           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
4019              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
4020             {
4021               t = FAILURE;
4022               break;
4023             }
4024
4025           if (type == BT_LOGICAL
4026               && ((cp->low == NULL || cp->high == NULL)
4027                   || cp->low != cp->high))
4028             {
4029               gfc_error
4030                 ("Logical range in CASE statement at %L is not allowed",
4031                  &cp->low->where);
4032               t = FAILURE;
4033               break;
4034             }
4035
4036           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
4037             {
4038               int value;
4039               value = cp->low->value.logical == 0 ? 2 : 1;
4040               if (value & seen_logical)
4041                 {
4042                   gfc_error ("constant logical value in CASE statement "
4043                              "is repeated at %L",
4044                              &cp->low->where);
4045                   t = FAILURE;
4046                   break;
4047                 }
4048               seen_logical |= value;
4049             }
4050
4051           if (cp->low != NULL && cp->high != NULL
4052               && cp->low != cp->high
4053               && gfc_compare_expr (cp->low, cp->high) > 0)
4054             {
4055               if (gfc_option.warn_surprising)
4056                 gfc_warning ("Range specification at %L can never "
4057                              "be matched", &cp->where);
4058
4059               cp->unreachable = 1;
4060               seen_unreachable = 1;
4061             }
4062           else
4063             {
4064               /* If the case range can be matched, it can also overlap with
4065                  other cases.  To make sure it does not, we put it in a
4066                  double linked list here.  We sort that with a merge sort
4067                  later on to detect any overlapping cases.  */
4068               if (!head)
4069                 {
4070                   head = tail = cp;
4071                   head->right = head->left = NULL;
4072                 }
4073               else
4074                 {
4075                   tail->right = cp;
4076                   tail->right->left = tail;
4077                   tail = tail->right;
4078                   tail->right = NULL;
4079                 }
4080             }
4081         }
4082
4083       /* It there was a failure in the previous case label, give up
4084          for this case label list.  Continue with the next block.  */
4085       if (t == FAILURE)
4086         continue;
4087
4088       /* See if any case labels that are unreachable have been seen.
4089          If so, we eliminate them.  This is a bit of a kludge because
4090          the case lists for a single case statement (label) is a
4091          single forward linked lists.  */
4092       if (seen_unreachable)
4093       {
4094         /* Advance until the first case in the list is reachable.  */
4095         while (body->ext.case_list != NULL
4096                && body->ext.case_list->unreachable)
4097           {
4098             gfc_case *n = body->ext.case_list;
4099             body->ext.case_list = body->ext.case_list->next;
4100             n->next = NULL;
4101             gfc_free_case_list (n);
4102           }
4103
4104         /* Strip all other unreachable cases.  */
4105         if (body->ext.case_list)
4106           {
4107             for (cp = body->ext.case_list; cp->next; cp = cp->next)
4108               {
4109                 if (cp->next->unreachable)
4110                   {
4111                     gfc_case *n = cp->next;
4112                     cp->next = cp->next->next;
4113                     n->next = NULL;
4114                     gfc_free_case_list (n);
4115                   }
4116               }
4117           }
4118       }
4119     }
4120
4121   /* See if there were overlapping cases.  If the check returns NULL,
4122      there was overlap.  In that case we don't do anything.  If head
4123      is non-NULL, we prepend the DEFAULT case.  The sorted list can
4124      then used during code generation for SELECT CASE constructs with
4125      a case expression of a CHARACTER type.  */
4126   if (head)
4127     {
4128       head = check_case_overlap (head);
4129
4130       /* Prepend the default_case if it is there.  */
4131       if (head != NULL && default_case)
4132         {
4133           default_case->left = NULL;
4134           default_case->right = head;
4135           head->left = default_case;
4136         }
4137     }
4138
4139   /* Eliminate dead blocks that may be the result if we've seen
4140      unreachable case labels for a block.  */
4141   for (body = code; body && body->block; body = body->block)
4142     {
4143       if (body->block->ext.case_list == NULL)
4144         {
4145           /* Cut the unreachable block from the code chain.  */
4146           gfc_code *c = body->block;
4147           body->block = c->block;
4148
4149           /* Kill the dead block, but not the blocks below it.  */
4150           c->block = NULL;
4151           gfc_free_statements (c);
4152         }
4153     }
4154
4155   /* More than two cases is legal but insane for logical selects.
4156      Issue a warning for it.  */
4157   if (gfc_option.warn_surprising && type == BT_LOGICAL
4158       && ncases > 2)
4159     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
4160                  &code->loc);
4161 }
4162
4163
4164 /* Resolve a transfer statement. This is making sure that:
4165    -- a derived type being transferred has only non-pointer components
4166    -- a derived type being transferred doesn't have private components, unless 
4167       it's being transferred from the module where the type was defined
4168    -- we're not trying to transfer a whole assumed size array.  */
4169
4170 static void
4171 resolve_transfer (gfc_code * code)
4172 {
4173   gfc_typespec *ts;
4174   gfc_symbol *sym;
4175   gfc_ref *ref;
4176   gfc_expr *exp;
4177
4178   exp = code->expr;
4179
4180   if (exp->expr_type != EXPR_VARIABLE
4181         && exp->expr_type != EXPR_FUNCTION)
4182     return;
4183
4184   sym = exp->symtree->n.sym;
4185   ts = &sym->ts;
4186
4187   /* Go to actual component transferred.  */
4188   for (ref = code->expr->ref; ref; ref = ref->next)
4189     if (ref->type == REF_COMPONENT)
4190       ts = &ref->u.c.component->ts;
4191
4192   if (ts->type == BT_DERIVED)
4193     {
4194       /* Check that transferred derived type doesn't contain POINTER
4195          components.  */
4196       if (derived_pointer (ts->derived))
4197         {
4198           gfc_error ("Data transfer element at %L cannot have "
4199                      "POINTER components", &code->loc);
4200           return;
4201         }
4202
4203       if (ts->derived->attr.alloc_comp)
4204         {
4205           gfc_error ("Data transfer element at %L cannot have "
4206                      "ALLOCATABLE components", &code->loc);
4207           return;
4208         }
4209
4210       if (derived_inaccessible (ts->derived))
4211         {
4212           gfc_error ("Data transfer element at %L cannot have "
4213                      "PRIVATE components",&code->loc);
4214           return;
4215         }
4216     }
4217
4218   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
4219       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
4220     {
4221       gfc_error ("Data transfer element at %L cannot be a full reference to "
4222                  "an assumed-size array", &code->loc);
4223       return;
4224     }
4225 }
4226
4227
4228 /*********** Toplevel code resolution subroutines ***********/
4229
4230 /* Given a branch to a label and a namespace, if the branch is conforming.
4231    The code node described where the branch is located.  */
4232
4233 static void
4234 resolve_branch (gfc_st_label * label, gfc_code * code)
4235 {
4236   gfc_code *block, *found;
4237   code_stack *stack;
4238   gfc_st_label *lp;
4239
4240   if (label == NULL)
4241     return;
4242   lp = label;
4243
4244   /* Step one: is this a valid branching target?  */
4245
4246   if (lp->defined == ST_LABEL_UNKNOWN)
4247     {
4248       gfc_error ("Label %d referenced at %L is never defined", lp->value,
4249                  &lp->where);
4250       return;
4251     }
4252
4253   if (lp->defined != ST_LABEL_TARGET)
4254     {
4255       gfc_error ("Statement at %L is not a valid branch target statement "
4256                  "for the branch statement at %L", &lp->where, &code->loc);
4257       return;
4258     }
4259
4260   /* Step two: make sure this branch is not a branch to itself ;-)  */
4261
4262   if (code->here == label)
4263     {
4264       gfc_warning ("Branch at %L causes an infinite loop", &code->loc);
4265       return;
4266     }
4267
4268   /* Step three: Try to find the label in the parse tree. To do this,
4269      we traverse the tree block-by-block: first the block that
4270      contains this GOTO, then the block that it is nested in, etc.  We
4271      can ignore other blocks because branching into another block is
4272      not allowed.  */
4273
4274   found = NULL;
4275
4276   for (stack = cs_base; stack; stack = stack->prev)
4277     {
4278       for (block = stack->head; block; block = block->next)
4279         {
4280           if (block->here == label)
4281             {
4282               found = block;
4283               break;
4284             }
4285         }
4286
4287       if (found)
4288         break;
4289     }
4290
4291   if (found == NULL)
4292     {
4293       /* The label is not in an enclosing block, so illegal.  This was
4294          allowed in Fortran 66, so we allow it as extension.  We also 
4295          forego further checks if we run into this.  */
4296       gfc_notify_std (GFC_STD_LEGACY,
4297                       "Label at %L is not in the same block as the "
4298                       "GOTO statement at %L", &lp->where, &code->loc);
4299       return;
4300     }
4301
4302   /* Step four: Make sure that the branching target is legal if
4303      the statement is an END {SELECT,DO,IF}.  */
4304
4305   if (found->op == EXEC_NOP)
4306     {
4307       for (stack = cs_base; stack; stack = stack->prev)
4308         if (stack->current->next == found)
4309           break;
4310
4311       if (stack == NULL)
4312         gfc_notify_std (GFC_STD_F95_DEL,
4313                         "Obsolete: GOTO at %L jumps to END of construct at %L",
4314                         &code->loc, &found->loc);
4315     }
4316 }
4317
4318
4319 /* Check whether EXPR1 has the same shape as EXPR2.  */
4320
4321 static try
4322 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
4323 {
4324   mpz_t shape[GFC_MAX_DIMENSIONS];
4325   mpz_t shape2[GFC_MAX_DIMENSIONS];
4326   try result = FAILURE;
4327   int i;
4328
4329   /* Compare the rank.  */
4330   if (expr1->rank != expr2->rank)
4331     return result;
4332
4333   /* Compare the size of each dimension.  */
4334   for (i=0; i<expr1->rank; i++)
4335     {
4336       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
4337         goto ignore;
4338
4339       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
4340         goto ignore;
4341
4342       if (mpz_cmp (shape[i], shape2[i]))
4343         goto over;
4344     }
4345
4346   /* When either of the two expression is an assumed size array, we
4347      ignore the comparison of dimension sizes.  */
4348 ignore:
4349   result = SUCCESS;
4350
4351 over:
4352   for (i--; i>=0; i--)
4353     {
4354       mpz_clear (shape[i]);
4355       mpz_clear (shape2[i]);
4356     }
4357   return result;
4358 }
4359
4360
4361 /* Check whether a WHERE assignment target or a WHERE mask expression
4362    has the same shape as the outmost WHERE mask expression.  */
4363
4364 static void
4365 resolve_where (gfc_code *code, gfc_expr *mask)
4366 {
4367   gfc_code *cblock;
4368   gfc_code *cnext;
4369   gfc_expr *e = NULL;
4370
4371   cblock = code->block;
4372
4373   /* Store the first WHERE mask-expr of the WHERE statement or construct.
4374      In case of nested WHERE, only the outmost one is stored.  */
4375   if (mask == NULL) /* outmost WHERE */
4376     e = cblock->expr;
4377   else /* inner WHERE */
4378     e = mask;
4379
4380   while (cblock)
4381     {
4382       if (cblock->expr)
4383         {
4384           /* Check if the mask-expr has a consistent shape with the
4385              outmost WHERE mask-expr.  */
4386           if (resolve_where_shape (cblock->expr, e) == FAILURE)
4387             gfc_error ("WHERE mask at %L has inconsistent shape",
4388                        &cblock->expr->where);
4389          }
4390
4391       /* the assignment statement of a WHERE statement, or the first
4392          statement in where-body-construct of a WHERE construct */
4393       cnext = cblock->next;
4394       while (cnext)
4395         {
4396           switch (cnext->op)
4397             {
4398             /* WHERE assignment statement */
4399             case EXEC_ASSIGN:
4400
4401               /* Check shape consistent for WHERE assignment target.  */
4402               if (e && resolve_where_shape (cnext->expr, e) == FAILURE)
4403                gfc_error ("WHERE assignment target at %L has "
4404                           "inconsistent shape", &cnext->expr->where);
4405               break;
4406
4407             /* WHERE or WHERE construct is part of a where-body-construct */
4408             case EXEC_WHERE:
4409               resolve_where (cnext, e);
4410               break;
4411
4412             default:
4413               gfc_error ("Unsupported statement inside WHERE at %L",
4414                          &cnext->loc);
4415             }
4416          /* the next statement within the same where-body-construct */
4417          cnext = cnext->next;
4418        }
4419     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
4420     cblock = cblock->block;
4421   }
4422 }
4423
4424
4425 /* Check whether the FORALL index appears in the expression or not.  */
4426
4427 static try
4428 gfc_find_forall_index (gfc_expr *expr, gfc_symbol *symbol)
4429 {
4430   gfc_array_ref ar;
4431   gfc_ref *tmp;
4432   gfc_actual_arglist *args;
4433   int i;
4434
4435   switch (expr->expr_type)
4436     {
4437     case EXPR_VARIABLE:
4438       gcc_assert (expr->symtree->n.sym);
4439
4440       /* A scalar assignment  */
4441       if (!expr->ref)
4442         {
4443           if (expr->symtree->n.sym == symbol)
4444             return SUCCESS;
4445           else
4446             return FAILURE;
4447         }
4448
4449       /* the expr is array ref, substring or struct component.  */
4450       tmp = expr->ref;
4451       while (tmp != NULL)
4452         {
4453           switch (tmp->type)
4454             {
4455             case  REF_ARRAY:
4456               /* Check if the symbol appears in the array subscript.  */
4457               ar = tmp->u.ar;
4458               for (i = 0; i < GFC_MAX_DIMENSIONS; i++)
4459                 {
4460                   if (ar.start[i])
4461                     if (gfc_find_forall_index (ar.start[i], symbol) == SUCCESS)
4462                       return SUCCESS;
4463
4464                   if (ar.end[i])
4465                     if (gfc_find_forall_index (ar.end[i], symbol) == SUCCESS)
4466                       return SUCCESS;
4467
4468                   if (ar.stride[i])
4469                     if (gfc_find_forall_index (ar.stride[i], symbol) == SUCCESS)
4470                       return SUCCESS;
4471                 }  /* end for  */
4472               break;
4473
4474             case REF_SUBSTRING:
4475               if (expr->symtree->n.sym == symbol)
4476                 return SUCCESS;
4477               tmp = expr->ref;
4478               /* Check if the symbol appears in the substring section.  */
4479               if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
4480                 return SUCCESS;
4481               if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
4482                 return SUCCESS;
4483               break;
4484
4485             case REF_COMPONENT:
4486               break;
4487
4488             default:
4489               gfc_error("expression reference type error at %L", &expr->where);
4490             }
4491           tmp = tmp->next;
4492         }
4493       break;
4494
4495     /* If the expression is a function call, then check if the symbol
4496        appears in the actual arglist of the function.  */
4497     case EXPR_FUNCTION:
4498       for (args = expr->value.function.actual; args; args = args->next)
4499         {
4500           if (gfc_find_forall_index(args->expr,symbol) == SUCCESS)
4501             return SUCCESS;
4502         }
4503       break;
4504
4505     /* It seems not to happen.  */
4506     case EXPR_SUBSTRING:
4507       if (expr->ref)
4508         {
4509           tmp = expr->ref;
4510           gcc_assert (expr->ref->type == REF_SUBSTRING);
4511           if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
4512             return SUCCESS;
4513           if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
4514             return SUCCESS;
4515         }
4516       break;
4517
4518     /* It seems not to happen.  */
4519     case EXPR_STRUCTURE:
4520     case EXPR_ARRAY:
4521       gfc_error ("Unsupported statement while finding forall index in "
4522                  "expression");
4523       break;
4524
4525     case EXPR_OP:
4526       /* Find the FORALL index in the first operand.  */
4527       if (expr->value.op.op1)
4528         {
4529           if (gfc_find_forall_index (expr->value.op.op1, symbol) == SUCCESS)
4530             return SUCCESS;
4531         }
4532
4533       /* Find the FORALL index in the second operand.  */
4534       if (expr->value.op.op2)
4535         {
4536           if (gfc_find_forall_index (expr->value.op.op2, symbol) == SUCCESS)
4537             return SUCCESS;
4538         }
4539       break;
4540
4541     default:
4542       break;
4543     }
4544
4545   return FAILURE;
4546 }
4547
4548
4549 /* Resolve assignment in FORALL construct.
4550    NVAR is the number of FORALL index variables, and VAR_EXPR records the
4551    FORALL index variables.  */
4552
4553 static void
4554 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
4555 {
4556   int n;
4557
4558   for (n = 0; n < nvar; n++)
4559     {
4560       gfc_symbol *forall_index;
4561
4562       forall_index = var_expr[n]->symtree->n.sym;
4563
4564       /* Check whether the assignment target is one of the FORALL index
4565          variable.  */
4566       if ((code->expr->expr_type == EXPR_VARIABLE)
4567           && (code->expr->symtree->n.sym == forall_index))
4568         gfc_error ("Assignment to a FORALL index variable at %L",
4569                    &code->expr->where);
4570       else
4571         {
4572           /* If one of the FORALL index variables doesn't appear in the
4573              assignment target, then there will be a many-to-one
4574              assignment.  */
4575           if (gfc_find_forall_index (code->expr, forall_index) == FAILURE)
4576             gfc_error ("The FORALL with index '%s' cause more than one "
4577                        "assignment to this object at %L",
4578                        var_expr[n]->symtree->name, &code->expr->where);
4579         }
4580     }
4581 }
4582
4583
4584 /* Resolve WHERE statement in FORALL construct.  */
4585
4586 static void
4587 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr){
4588   gfc_code *cblock;
4589   gfc_code *cnext;
4590
4591   cblock = code->block;
4592   while (cblock)
4593     {
4594       /* the assignment statement of a WHERE statement, or the first
4595          statement in where-body-construct of a WHERE construct */
4596       cnext = cblock->next;
4597       while (cnext)
4598         {
4599           switch (cnext->op)
4600             {
4601             /* WHERE assignment statement */
4602             case EXEC_ASSIGN:
4603               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
4604               break;
4605
4606             /* WHERE or WHERE construct is part of a where-body-construct */
4607             case EXEC_WHERE:
4608               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
4609               break;
4610
4611             default:
4612               gfc_error ("Unsupported statement inside WHERE at %L",
4613                          &cnext->loc);
4614             }
4615           /* the next statement within the same where-body-construct */
4616           cnext = cnext->next;
4617         }
4618       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
4619       cblock = cblock->block;
4620     }
4621 }
4622
4623
4624 /* Traverse the FORALL body to check whether the following errors exist:
4625    1. For assignment, check if a many-to-one assignment happens.
4626    2. For WHERE statement, check the WHERE body to see if there is any
4627       many-to-one assignment.  */
4628
4629 static void
4630 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
4631 {
4632   gfc_code *c;
4633
4634   c = code->block->next;
4635   while (c)
4636     {
4637       switch (c->op)
4638         {
4639         case EXEC_ASSIGN:
4640         case EXEC_POINTER_ASSIGN:
4641           gfc_resolve_assign_in_forall (c, nvar, var_expr);
4642           break;
4643
4644         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
4645            there is no need to handle it here.  */
4646         case EXEC_FORALL:
4647           break;
4648         case EXEC_WHERE:
4649           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
4650           break;
4651         default:
4652           break;
4653         }
4654       /* The next statement in the FORALL body.  */
4655       c = c->next;
4656     }
4657 }
4658
4659
4660 /* Given a FORALL construct, first resolve the FORALL iterator, then call
4661    gfc_resolve_forall_body to resolve the FORALL body.  */
4662
4663 static void
4664 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
4665 {
4666   static gfc_expr **var_expr;
4667   static int total_var = 0;
4668   static int nvar = 0;
4669   gfc_forall_iterator *fa;
4670   gfc_symbol *forall_index;
4671   gfc_code *next;
4672   int i;
4673
4674   /* Start to resolve a FORALL construct   */
4675   if (forall_save == 0)
4676     {
4677       /* Count the total number of FORALL index in the nested FORALL
4678          construct in order to allocate the VAR_EXPR with proper size.  */
4679       next = code;
4680       while ((next != NULL) && (next->op == EXEC_FORALL))
4681         {
4682           for (fa = next->ext.forall_iterator; fa; fa = fa->next)
4683             total_var ++;
4684           next = next->block->next;
4685         }
4686
4687       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
4688       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
4689     }
4690
4691   /* The information about FORALL iterator, including FORALL index start, end
4692      and stride. The FORALL index can not appear in start, end or stride.  */
4693   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
4694     {
4695       /* Check if any outer FORALL index name is the same as the current
4696          one.  */
4697       for (i = 0; i < nvar; i++)
4698         {
4699           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
4700             {
4701               gfc_error ("An outer FORALL construct already has an index "
4702                          "with this name %L", &fa->var->where);
4703             }
4704         }
4705
4706       /* Record the current FORALL index.  */
4707       var_expr[nvar] = gfc_copy_expr (fa->var);
4708
4709       forall_index = fa->var->symtree->n.sym;
4710
4711       /* Check if the FORALL index appears in start, end or stride.  */
4712       if (gfc_find_forall_index (fa->start, forall_index) == SUCCESS)
4713         gfc_error ("A FORALL index must not appear in a limit or stride "
4714                    "expression in the same FORALL at %L", &fa->start->where);
4715       if (gfc_find_forall_index (fa->end, forall_index) == SUCCESS)
4716         gfc_error ("A FORALL index must not appear in a limit or stride "
4717                    "expression in the same FORALL at %L", &fa->end->where);
4718       if (gfc_find_forall_index (fa->stride, forall_index) == SUCCESS)
4719         gfc_error ("A FORALL index must not appear in a limit or stride "
4720                    "expression in the same FORALL at %L", &fa->stride->where);
4721       nvar++;
4722     }
4723
4724   /* Resolve the FORALL body.  */
4725   gfc_resolve_forall_body (code, nvar, var_expr);
4726
4727   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
4728   gfc_resolve_blocks (code->block, ns);
4729
4730   /* Free VAR_EXPR after the whole FORALL construct resolved.  */
4731   for (i = 0; i < total_var; i++)
4732     gfc_free_expr (var_expr[i]);
4733
4734   /* Reset the counters.  */
4735   total_var = 0;
4736   nvar = 0;
4737 }
4738
4739
4740 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL ,GOTO and
4741    DO code nodes.  */
4742
4743 static void resolve_code (gfc_code *, gfc_namespace *);
4744
4745 void
4746 gfc_resolve_blocks (gfc_code * b, gfc_namespace * ns)
4747 {
4748   try t;
4749
4750   for (; b; b = b->block)
4751     {
4752       t = gfc_resolve_expr (b->expr);
4753       if (gfc_resolve_expr (b->expr2) == FAILURE)
4754         t = FAILURE;
4755
4756       switch (b->op)
4757         {
4758         case EXEC_IF:
4759           if (t == SUCCESS && b->expr != NULL
4760               && (b->expr->ts.type != BT_LOGICAL || b->expr->rank != 0))
4761             gfc_error
4762               ("IF clause at %L requires a scalar LOGICAL expression",
4763                &b->expr->where);
4764           break;
4765
4766         case EXEC_WHERE:
4767           if (t == SUCCESS
4768               && b->expr != NULL
4769               && (b->expr->ts.type != BT_LOGICAL
4770                   || b->expr->rank == 0))
4771             gfc_error
4772               ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
4773                &b->expr->where);
4774           break;
4775
4776         case EXEC_GOTO:
4777           resolve_branch (b->label, b);
4778           break;
4779
4780         case EXEC_SELECT:
4781         case EXEC_FORALL:
4782         case EXEC_DO:
4783         case EXEC_DO_WHILE:
4784         case EXEC_READ:
4785         case EXEC_WRITE:
4786         case EXEC_IOLENGTH:
4787           break;
4788
4789         case EXEC_OMP_ATOMIC:
4790         case EXEC_OMP_CRITICAL:
4791         case EXEC_OMP_DO:
4792         case EXEC_OMP_MASTER:
4793         case EXEC_OMP_ORDERED:
4794         case EXEC_OMP_PARALLEL:
4795         case EXEC_OMP_PARALLEL_DO:
4796         case EXEC_OMP_PARALLEL_SECTIONS:
4797         case EXEC_OMP_PARALLEL_WORKSHARE:
4798         case EXEC_OMP_SECTIONS:
4799         case EXEC_OMP_SINGLE:
4800         case EXEC_OMP_WORKSHARE:
4801           break;
4802
4803         default:
4804           gfc_internal_error ("resolve_block(): Bad block type");
4805         }
4806
4807       resolve_code (b->next, ns);
4808     }
4809 }
4810
4811
4812 /* Given a block of code, recursively resolve everything pointed to by this
4813    code block.  */
4814
4815 static void
4816 resolve_code (gfc_code * code, gfc_namespace * ns)
4817 {
4818   int omp_workshare_save;
4819   int forall_save;
4820   code_stack frame;
4821   gfc_alloc *a;
4822   try t;
4823
4824   frame.prev = cs_base;
4825   frame.head = code;
4826   cs_base = &frame;
4827
4828   for (; code; code = code->next)
4829     {
4830       frame.current = code;
4831       forall_save = forall_flag;
4832
4833       if (code->op == EXEC_FORALL)
4834         {
4835           forall_flag = 1;
4836           gfc_resolve_forall (code, ns, forall_save);
4837           forall_flag = 2;
4838         }
4839       else if (code->block)
4840         {
4841           omp_workshare_save = -1;
4842           switch (code->op)
4843             {
4844             case EXEC_OMP_PARALLEL_WORKSHARE:
4845               omp_workshare_save = omp_workshare_flag;
4846               omp_workshare_flag = 1;
4847               gfc_resolve_omp_parallel_blocks (code, ns);
4848               break;
4849             case EXEC_OMP_PARALLEL:
4850             case EXEC_OMP_PARALLEL_DO:
4851             case EXEC_OMP_PARALLEL_SECTIONS:
4852               omp_workshare_save = omp_workshare_flag;
4853               omp_workshare_flag = 0;
4854               gfc_resolve_omp_parallel_blocks (code, ns);
4855               break;
4856             case EXEC_OMP_DO:
4857               gfc_resolve_omp_do_blocks (code, ns);
4858               break;
4859             case EXEC_OMP_WORKSHARE:
4860               omp_workshare_save = omp_workshare_flag;
4861               omp_workshare_flag = 1;
4862               /* FALLTHROUGH */
4863             default:
4864               gfc_resolve_blocks (code->block, ns);
4865               break;
4866             }
4867
4868           if (omp_workshare_save != -1)
4869             omp_workshare_flag = omp_workshare_save;
4870         }
4871
4872       t = gfc_resolve_expr (code->expr);
4873       forall_flag = forall_save;
4874
4875       if (gfc_resolve_expr (code->expr2) == FAILURE)
4876         t = FAILURE;
4877
4878       switch (code->op)
4879         {
4880         case EXEC_NOP:
4881         case EXEC_CYCLE:
4882         case EXEC_PAUSE:
4883         case EXEC_STOP:
4884         case EXEC_EXIT:
4885         case EXEC_CONTINUE:
4886         case EXEC_DT_END:
4887           break;
4888
4889         case EXEC_ENTRY:
4890           /* Keep track of which entry we are up to.  */
4891           current_entry_id = code->ext.entry->id;
4892           break;
4893
4894         case EXEC_WHERE:
4895           resolve_where (code, NULL);
4896           break;
4897
4898         case EXEC_GOTO:
4899           if (code->expr != NULL)
4900             {
4901               if (code->expr->ts.type != BT_INTEGER)
4902                 gfc_error ("ASSIGNED GOTO statement at %L requires an INTEGER "
4903                        "variable", &code->expr->where);
4904               else if (code->expr->symtree->n.sym->attr.assign != 1)
4905                 gfc_error ("Variable '%s' has not been assigned a target label "
4906                         "at %L", code->expr->symtree->n.sym->name,
4907                         &code->expr->where);
4908             }
4909           else
4910             resolve_branch (code->label, code);
4911           break;
4912
4913         case EXEC_RETURN:
4914           if (code->expr != NULL
4915                 && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
4916             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
4917                        "INTEGER return specifier", &code->expr->where);
4918           break;
4919
4920         case EXEC_INIT_ASSIGN:
4921           break;
4922
4923         case EXEC_ASSIGN:
4924           if (t == FAILURE)
4925             break;
4926
4927           if (gfc_extend_assign (code, ns) == SUCCESS)
4928             {
4929               if (gfc_pure (NULL) && !gfc_pure (code->symtree->n.sym))
4930                 {
4931                   gfc_error ("Subroutine '%s' called instead of assignment at "
4932                              "%L must be PURE", code->symtree->n.sym->name,
4933                              &code->loc);
4934                   break;
4935                 }
4936               goto call;
4937             }
4938
4939           if (gfc_pure (NULL))
4940             {
4941               if (gfc_impure_variable (code->expr->symtree->n.sym))
4942                 {
4943                   gfc_error
4944                     ("Cannot assign to variable '%s' in PURE procedure at %L",
4945                      code->expr->symtree->n.sym->name, &code->expr->where);
4946                   break;
4947                 }
4948
4949               if (code->expr2->ts.type == BT_DERIVED
4950                   && derived_pointer (code->expr2->ts.derived))
4951                 {
4952                   gfc_error
4953                     ("Right side of assignment at %L is a derived type "
4954                      "containing a POINTER in a PURE procedure",
4955                      &code->expr2->where);
4956                   break;
4957                 }
4958             }
4959
4960           gfc_check_assign (code->expr, code->expr2, 1);
4961           break;
4962
4963         case EXEC_LABEL_ASSIGN:
4964           if (code->label->defined == ST_LABEL_UNKNOWN)
4965             gfc_error ("Label %d referenced at %L is never defined",
4966                        code->label->value, &code->label->where);
4967           if (t == SUCCESS
4968               && (code->expr->expr_type != EXPR_VARIABLE
4969                   || code->expr->symtree->n.sym->ts.type != BT_INTEGER
4970                   || code->expr->symtree->n.sym->ts.kind
4971                         != gfc_default_integer_kind
4972                   || code->expr->symtree->n.sym->as != NULL))
4973             gfc_error ("ASSIGN statement at %L requires a scalar "
4974                        "default INTEGER variable", &code->expr->where);
4975           break;
4976
4977         case EXEC_POINTER_ASSIGN:
4978           if (t == FAILURE)
4979             break;
4980
4981           gfc_check_pointer_assign (code->expr, code->expr2);
4982           break;
4983
4984         case EXEC_ARITHMETIC_IF:
4985           if (t == SUCCESS
4986               && code->expr->ts.type != BT_INTEGER
4987               && code->expr->ts.type != BT_REAL)
4988             gfc_error ("Arithmetic IF statement at %L requires a numeric "
4989                        "expression", &code->expr->where);
4990
4991           resolve_branch (code->label, code);
4992           resolve_branch (code->label2, code);
4993           resolve_branch (code->label3, code);
4994           break;
4995
4996         case EXEC_IF:
4997           if (t == SUCCESS && code->expr != NULL
4998               && (code->expr->ts.type != BT_LOGICAL
4999                   || code->expr->rank != 0))
5000             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
5001                        &code->expr->where);
5002           break;
5003
5004         case EXEC_CALL:
5005         call:
5006           resolve_call (code);
5007           break;
5008
5009         case EXEC_SELECT:
5010           /* Select is complicated. Also, a SELECT construct could be
5011              a transformed computed GOTO.  */
5012           resolve_select (code);
5013           break;
5014
5015         case EXEC_DO:
5016           if (code->ext.iterator != NULL)
5017             {
5018               gfc_iterator *iter = code->ext.iterator;
5019               if (gfc_resolve_iterator (iter, true) != FAILURE)
5020                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
5021             }
5022           break;
5023
5024         case EXEC_DO_WHILE:
5025           if (code->expr == NULL)
5026             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
5027           if (t == SUCCESS
5028               && (code->expr->rank != 0
5029                   || code->expr->ts.type != BT_LOGICAL))
5030             gfc_error ("Exit condition of DO WHILE loop at %L must be "
5031                        "a scalar LOGICAL expression", &code->expr->where);
5032           break;
5033
5034         case EXEC_ALLOCATE:
5035           if (t == SUCCESS && code->expr != NULL
5036               && code->expr->ts.type != BT_INTEGER)
5037             gfc_error ("STAT tag in ALLOCATE statement at %L must be "
5038                        "of type INTEGER", &code->expr->where);
5039
5040           for (a = code->ext.alloc_list; a; a = a->next)
5041             resolve_allocate_expr (a->expr, code);
5042
5043           break;
5044
5045         case EXEC_DEALLOCATE:
5046           if (t == SUCCESS && code->expr != NULL
5047               && code->expr->ts.type != BT_INTEGER)
5048             gfc_error
5049               ("STAT tag in DEALLOCATE statement at %L must be of type "
5050                "INTEGER", &code->expr->where);
5051
5052           for (a = code->ext.alloc_list; a; a = a->next)
5053             resolve_deallocate_expr (a->expr);
5054
5055           break;
5056
5057         case EXEC_OPEN:
5058           if (gfc_resolve_open (code->ext.open) == FAILURE)
5059             break;
5060
5061           resolve_branch (code->ext.open->err, code);
5062           break;
5063
5064         case EXEC_CLOSE:
5065           if (gfc_resolve_close (code->ext.close) == FAILURE)
5066             break;
5067
5068           resolve_branch (code->ext.close->err, code);
5069           break;
5070
5071         case EXEC_BACKSPACE:
5072         case EXEC_ENDFILE:
5073         case EXEC_REWIND:
5074         case EXEC_FLUSH:
5075           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
5076             break;
5077
5078           resolve_branch (code->ext.filepos->err, code);
5079           break;
5080
5081         case EXEC_INQUIRE:
5082           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
5083               break;
5084
5085           resolve_branch (code->ext.inquire->err, code);
5086           break;
5087
5088         case EXEC_IOLENGTH:
5089           gcc_assert (code->ext.inquire != NULL);
5090           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
5091             break;
5092
5093           resolve_branch (code->ext.inquire->err, code);
5094           break;
5095
5096         case EXEC_READ:
5097         case EXEC_WRITE:
5098           if (gfc_resolve_dt (code->ext.dt) == FAILURE)
5099             break;
5100
5101           resolve_branch (code->ext.dt->err, code);
5102           resolve_branch (code->ext.dt->end, code);
5103           resolve_branch (code->ext.dt->eor, code);
5104           break;
5105
5106         case EXEC_TRANSFER:
5107           resolve_transfer (code);
5108           break;
5109
5110         case EXEC_FORALL:
5111           resolve_forall_iterators (code->ext.forall_iterator);
5112
5113           if (code->expr != NULL && code->expr->ts.type != BT_LOGICAL)
5114             gfc_error
5115               ("FORALL mask clause at %L requires a LOGICAL expression",
5116                &code->expr->where);
5117           break;
5118
5119         case EXEC_OMP_ATOMIC:
5120         case EXEC_OMP_BARRIER:
5121         case EXEC_OMP_CRITICAL:
5122         case EXEC_OMP_FLUSH:
5123         case EXEC_OMP_DO:
5124         case EXEC_OMP_MASTER:
5125         case EXEC_OMP_ORDERED:
5126         case EXEC_OMP_SECTIONS:
5127         case EXEC_OMP_SINGLE:
5128         case EXEC_OMP_WORKSHARE:
5129           gfc_resolve_omp_directive (code, ns);
5130           break;
5131
5132         case EXEC_OMP_PARALLEL:
5133         case EXEC_OMP_PARALLEL_DO:
5134         case EXEC_OMP_PARALLEL_SECTIONS:
5135         case EXEC_OMP_PARALLEL_WORKSHARE:
5136           omp_workshare_save = omp_workshare_flag;
5137           omp_workshare_flag = 0;
5138           gfc_resolve_omp_directive (code, ns);
5139           omp_workshare_flag = omp_workshare_save;
5140           break;
5141
5142         default:
5143           gfc_internal_error ("resolve_code(): Bad statement code");
5144         }
5145     }
5146
5147   cs_base = frame.prev;
5148 }
5149
5150
5151 /* Resolve initial values and make sure they are compatible with
5152    the variable.  */
5153
5154 static void
5155 resolve_values (gfc_symbol * sym)
5156 {
5157
5158   if (sym->value == NULL)
5159     return;
5160
5161   if (gfc_resolve_expr (sym->value) == FAILURE)
5162     return;
5163
5164   gfc_check_assign_symbol (sym, sym->value);
5165 }
5166
5167
5168 /* Resolve an index expression.  */
5169
5170 static try
5171 resolve_index_expr (gfc_expr * e)
5172 {
5173   if (gfc_resolve_expr (e) == FAILURE)
5174     return FAILURE;
5175
5176   if (gfc_simplify_expr (e, 0) == FAILURE)
5177     return FAILURE;
5178
5179   if (gfc_specification_expr (e) == FAILURE)
5180     return FAILURE;
5181
5182   return SUCCESS;
5183 }
5184
5185 /* Resolve a charlen structure.  */
5186
5187 static try
5188 resolve_charlen (gfc_charlen *cl)
5189 {
5190   if (cl->resolved)
5191     return SUCCESS;
5192
5193   cl->resolved = 1;
5194
5195   specification_expr = 1;
5196
5197   if (resolve_index_expr (cl->length) == FAILURE)
5198     {
5199       specification_expr = 0;
5200       return FAILURE;
5201     }
5202
5203   return SUCCESS;
5204 }
5205
5206
5207 /* Test for non-constant shape arrays. */
5208
5209 static bool
5210 is_non_constant_shape_array (gfc_symbol *sym)
5211 {
5212   gfc_expr *e;
5213   int i;
5214   bool not_constant;
5215
5216   not_constant = false;
5217   if (sym->as != NULL)
5218     {
5219       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
5220          has not been simplified; parameter array references.  Do the
5221          simplification now.  */
5222       for (i = 0; i < sym->as->rank; i++)
5223         {
5224           e = sym->as->lower[i];
5225           if (e && (resolve_index_expr (e) == FAILURE
5226                 || !gfc_is_constant_expr (e)))
5227             not_constant = true;
5228
5229           e = sym->as->upper[i];
5230           if (e && (resolve_index_expr (e) == FAILURE
5231                 || !gfc_is_constant_expr (e)))
5232             not_constant = true;
5233         }
5234     }
5235   return not_constant;
5236 }
5237
5238
5239 /* Assign the default initializer to a derived type variable or result.  */
5240
5241 static void
5242 apply_default_init (gfc_symbol *sym)
5243 {
5244   gfc_expr *lval;
5245   gfc_expr *init = NULL;
5246   gfc_code *init_st;
5247   gfc_namespace *ns = sym->ns;
5248
5249   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
5250     return;
5251
5252   if (sym->ts.type == BT_DERIVED && sym->ts.derived)
5253     init = gfc_default_initializer (&sym->ts);
5254
5255   if (init == NULL)
5256     return;
5257
5258   /* Search for the function namespace if this is a contained
5259      function without an explicit result.  */
5260   if (sym->attr.function && sym == sym->result
5261         && sym->name != sym->ns->proc_name->name)
5262     {
5263       ns = ns->contained;
5264       for (;ns; ns = ns->sibling)
5265         if (strcmp (ns->proc_name->name, sym->name) == 0)
5266           break;
5267     }
5268
5269   if (ns == NULL)
5270     {
5271       gfc_free_expr (init);
5272       return;
5273     }
5274
5275   /* Build an l-value expression for the result.  */
5276   lval = gfc_get_expr ();
5277   lval->expr_type = EXPR_VARIABLE;
5278   lval->where = sym->declared_at;
5279   lval->ts = sym->ts;
5280   lval->symtree = gfc_find_symtree (sym->ns->sym_root, sym->name);
5281
5282   /* It will always be a full array.  */
5283   lval->rank = sym->as ? sym->as->rank : 0;
5284   if (lval->rank)
5285     {
5286       lval->ref = gfc_get_ref ();
5287       lval->ref->type = REF_ARRAY;
5288       lval->ref->u.ar.type = AR_FULL;
5289       lval->ref->u.ar.dimen = lval->rank;
5290       lval->ref->u.ar.where = sym->declared_at;
5291       lval->ref->u.ar.as = sym->as;
5292     }
5293
5294   /* Add the code at scope entry.  */
5295   init_st = gfc_get_code ();
5296   init_st->next = ns->code;
5297   ns->code = init_st;
5298
5299   /* Assign the default initializer to the l-value.  */
5300   init_st->loc = sym->declared_at;
5301   init_st->op = EXEC_INIT_ASSIGN;
5302   init_st->expr = lval;
5303   init_st->expr2 = init;
5304 }
5305
5306
5307 /* Resolution of common features of flavors variable and procedure. */
5308
5309 static try
5310 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
5311 {
5312   /* Constraints on deferred shape variable.  */
5313   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
5314     {
5315       if (sym->attr.allocatable)
5316         {
5317           if (sym->attr.dimension)
5318             gfc_error ("Allocatable array '%s' at %L must have "
5319                        "a deferred shape", sym->name, &sym->declared_at);
5320           else
5321             gfc_error ("Scalar object '%s' at %L may not be ALLOCATABLE",
5322                        sym->name, &sym->declared_at);
5323             return FAILURE;
5324         }
5325
5326       if (sym->attr.pointer && sym->attr.dimension)
5327         {
5328           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
5329                      sym->name, &sym->declared_at);
5330           return FAILURE;
5331         }
5332
5333     }
5334   else
5335     {
5336       if (!mp_flag && !sym->attr.allocatable
5337              && !sym->attr.pointer && !sym->attr.dummy)
5338         {
5339           gfc_error ("Array '%s' at %L cannot have a deferred shape",
5340                      sym->name, &sym->declared_at);
5341           return FAILURE;
5342          }
5343     }
5344   return SUCCESS;
5345 }
5346
5347 /* Resolve symbols with flavor variable.  */
5348
5349 static try
5350 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
5351 {
5352   int flag;
5353   int i;
5354   gfc_expr *e;
5355   gfc_expr *constructor_expr;
5356   const char * auto_save_msg;
5357
5358   auto_save_msg = "automatic object '%s' at %L cannot have the "
5359                   "SAVE attribute";
5360
5361   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
5362     return FAILURE;
5363
5364   /* Set this flag to check that variables are parameters of all entries.
5365      This check is effected by the call to gfc_resolve_expr through
5366      is_non_constant_shape_array.  */
5367   specification_expr = 1;
5368
5369   if (!sym->attr.use_assoc
5370         && !sym->attr.allocatable
5371         && !sym->attr.pointer
5372         && is_non_constant_shape_array (sym))
5373     {
5374         /* The shape of a main program or module array needs to be constant.  */
5375         if (sym->ns->proc_name
5376               && (sym->ns->proc_name->attr.flavor == FL_MODULE
5377                     || sym->ns->proc_name->attr.is_main_program))
5378           {
5379             gfc_error ("The module or main program array '%s' at %L must "
5380                        "have constant shape", sym->name, &sym->declared_at);
5381             specification_expr = 0;
5382             return FAILURE;
5383           }
5384     }
5385
5386   if (sym->ts.type == BT_CHARACTER)
5387     {
5388       /* Make sure that character string variables with assumed length are
5389          dummy arguments.  */
5390       e = sym->ts.cl->length;
5391       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
5392         {
5393           gfc_error ("Entity with assumed character length at %L must be a "
5394                      "dummy argument or a PARAMETER", &sym->declared_at);
5395           return FAILURE;
5396         }
5397
5398       if (e && sym->attr.save && !gfc_is_constant_expr (e))
5399         {
5400           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
5401           return FAILURE;
5402         }
5403
5404       if (!gfc_is_constant_expr (e)
5405             && !(e->expr_type == EXPR_VARIABLE
5406             && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
5407             && sym->ns->proc_name
5408             && (sym->ns->proc_name->attr.flavor == FL_MODULE
5409                   || sym->ns->proc_name->attr.is_main_program)
5410             && !sym->attr.use_assoc)
5411         {
5412           gfc_error ("'%s' at %L must have constant character length "
5413                      "in this context", sym->name, &sym->declared_at);
5414           return FAILURE;
5415         }
5416     }
5417
5418   /* Can the symbol have an initializer?  */
5419   flag = 0;
5420   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
5421         || sym->attr.intrinsic || sym->attr.result)
5422     flag = 1;
5423   else if (sym->attr.dimension && !sym->attr.pointer)
5424     {
5425       /* Don't allow initialization of automatic arrays.  */
5426       for (i = 0; i < sym->as->rank; i++)
5427         {
5428           if (sym->as->lower[i] == NULL
5429                 || sym->as->lower[i]->expr_type != EXPR_CONSTANT
5430                 || sym->as->upper[i] == NULL
5431                 || sym->as->upper[i]->expr_type != EXPR_CONSTANT)
5432             {
5433               flag = 1;
5434               break;
5435             }
5436         }
5437
5438       /* Also, they must not have the SAVE attribute.  */
5439       if (flag && sym->attr.save)
5440         {
5441           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
5442           return FAILURE;
5443         }
5444   }
5445
5446   /* Reject illegal initializers.  */
5447   if (sym->value && flag)
5448     {
5449       if (sym->attr.allocatable)
5450         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
5451                    sym->name, &sym->declared_at);
5452       else if (sym->attr.external)
5453         gfc_error ("External '%s' at %L cannot have an initializer",
5454                    sym->name, &sym->declared_at);
5455       else if (sym->attr.dummy)
5456         gfc_error ("Dummy '%s' at %L cannot have an initializer",
5457                    sym->name, &sym->declared_at);
5458       else if (sym->attr.intrinsic)
5459         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
5460                    sym->name, &sym->declared_at);
5461       else if (sym->attr.result)
5462         gfc_error ("Function result '%s' at %L cannot have an initializer",
5463                    sym->name, &sym->declared_at);
5464       else
5465         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
5466                    sym->name, &sym->declared_at);
5467       return FAILURE;
5468     }
5469
5470   /* Check to see if a derived type is blocked from being host associated
5471      by the presence of another class I symbol in the same namespace.
5472      14.6.1.3 of the standard and the discussion on comp.lang.fortran.  */
5473   if (sym->ts.type == BT_DERIVED && sym->ns != sym->ts.derived->ns)
5474     {
5475       gfc_symbol *s;
5476       gfc_find_symbol (sym->ts.derived->name, sym->ns, 0, &s);
5477       if (s && (s->attr.flavor != FL_DERIVED
5478                   || !gfc_compare_derived_types (s, sym->ts.derived)))
5479         {
5480           gfc_error ("The type %s cannot be host associated at %L because "
5481                      "it is blocked by an incompatible object of the same "
5482                      "name at %L", sym->ts.derived->name, &sym->declared_at,
5483                      &s->declared_at);
5484           return FAILURE;
5485         }
5486     }
5487
5488   /* 4th constraint in section 11.3:  "If an object of a type for which
5489      component-initialization is specified (R429) appears in the
5490      specification-part of a module and does not have the ALLOCATABLE
5491      or POINTER attribute, the object shall have the SAVE attribute."  */
5492
5493   constructor_expr = NULL;
5494   if (sym->ts.type == BT_DERIVED && !(sym->value || flag))
5495         constructor_expr = gfc_default_initializer (&sym->ts);
5496
5497   if (sym->ns->proc_name
5498         && sym->ns->proc_name->attr.flavor == FL_MODULE
5499         && constructor_expr
5500         && !sym->ns->save_all && !sym->attr.save
5501         && !sym->attr.pointer && !sym->attr.allocatable)
5502     {
5503       gfc_error("Object '%s' at %L must have the SAVE attribute %s",
5504                 sym->name, &sym->declared_at,
5505                 "for default initialization of a component");
5506       return FAILURE;
5507     }
5508
5509   /* Assign default initializer.  */
5510   if (sym->ts.type == BT_DERIVED
5511         && !sym->value
5512         && !sym->attr.pointer
5513         && !sym->attr.allocatable
5514         && (!flag || sym->attr.intent == INTENT_OUT))
5515     sym->value = gfc_default_initializer (&sym->ts);
5516
5517   return SUCCESS;
5518 }
5519
5520
5521 /* Resolve a procedure.  */
5522
5523 static try
5524 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
5525 {
5526   gfc_formal_arglist *arg;
5527
5528   if (sym->attr.function
5529         && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
5530     return FAILURE;
5531
5532   if (sym->attr.proc == PROC_ST_FUNCTION)
5533     {
5534       if (sym->ts.type == BT_CHARACTER)
5535         {
5536           gfc_charlen *cl = sym->ts.cl;
5537           if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
5538             {
5539               gfc_error ("Character-valued statement function '%s' at %L must "
5540                          "have constant length", sym->name, &sym->declared_at);
5541               return FAILURE;
5542             }
5543         }
5544     }
5545
5546   /* Ensure that derived type for are not of a private type.  Internal
5547      module procedures are excluded by 2.2.3.3 - ie. they are not
5548      externally accessible and can access all the objects accessible in
5549      the host. */
5550   if (!(sym->ns->parent
5551             && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
5552         && gfc_check_access(sym->attr.access, sym->ns->default_access))
5553     {
5554       for (arg = sym->formal; arg; arg = arg->next)
5555         {
5556           if (arg->sym
5557                 && arg->sym->ts.type == BT_DERIVED
5558                 && !arg->sym->ts.derived->attr.use_assoc
5559                 && !gfc_check_access(arg->sym->ts.derived->attr.access,
5560                         arg->sym->ts.derived->ns->default_access))
5561             {
5562               gfc_error_now ("'%s' is of a PRIVATE type and cannot be "
5563                              "a dummy argument of '%s', which is "
5564                              "PUBLIC at %L", arg->sym->name, sym->name,
5565                              &sym->declared_at);
5566               /* Stop this message from recurring.  */
5567               arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
5568               return FAILURE;
5569             }
5570         }
5571     }
5572
5573   /* An external symbol may not have an initializer because it is taken to be
5574      a procedure.  */
5575   if (sym->attr.external && sym->value)
5576     {
5577       gfc_error ("External object '%s' at %L may not have an initializer",
5578                  sym->name, &sym->declared_at);
5579       return FAILURE;
5580     }
5581
5582   /* An elemental function is required to return a scalar 12.7.1  */
5583   if (sym->attr.elemental && sym->attr.function && sym->as)
5584     {
5585       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
5586                  "result", sym->name, &sym->declared_at);
5587       /* Reset so that the error only occurs once.  */
5588       sym->attr.elemental = 0;
5589       return FAILURE;
5590     }
5591
5592   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
5593      char-len-param shall not be array-valued, pointer-valued, recursive
5594      or pure.  ....snip... A character value of * may only be used in the
5595      following ways: (i) Dummy arg of procedure - dummy associates with
5596      actual length; (ii) To declare a named constant; or (iii) External
5597      function - but length must be declared in calling scoping unit.  */
5598   if (sym->attr.function
5599         && sym->ts.type == BT_CHARACTER
5600         && sym->ts.cl && sym->ts.cl->length == NULL)
5601     {
5602       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
5603              || (sym->attr.recursive) || (sym->attr.pure))
5604         {
5605           if (sym->as && sym->as->rank)
5606             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5607                        "array-valued", sym->name, &sym->declared_at);
5608
5609           if (sym->attr.pointer)
5610             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5611                        "pointer-valued", sym->name, &sym->declared_at);
5612
5613           if (sym->attr.pure)
5614             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5615                        "pure", sym->name, &sym->declared_at);
5616
5617           if (sym->attr.recursive)
5618             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5619                        "recursive", sym->name, &sym->declared_at);
5620
5621           return FAILURE;
5622         }
5623
5624       /* Appendix B.2 of the standard.  Contained functions give an
5625          error anyway.  Fixed-form is likely to be F77/legacy.  */
5626       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
5627         gfc_notify_std (GFC_STD_F95_OBS, "CHARACTER(*) function "
5628                         "'%s' at %L is obsolescent in fortran 95",
5629                         sym->name, &sym->declared_at);
5630     }
5631   return SUCCESS;
5632 }
5633
5634
5635 /* Resolve the components of a derived type.  */
5636
5637 static try
5638 resolve_fl_derived (gfc_symbol *sym)
5639 {
5640   gfc_component *c;
5641   gfc_dt_list * dt_list;
5642   int i;
5643
5644   for (c = sym->components; c != NULL; c = c->next)
5645     {
5646       if (c->ts.type == BT_CHARACTER)
5647         {
5648          if (c->ts.cl->length == NULL
5649              || (resolve_charlen (c->ts.cl) == FAILURE)
5650              || !gfc_is_constant_expr (c->ts.cl->length))
5651            {
5652              gfc_error ("Character length of component '%s' needs to "
5653                         "be a constant specification expression at %L",
5654                         c->name,
5655                         c->ts.cl->length ? &c->ts.cl->length->where : &c->loc);
5656              return FAILURE;
5657            }
5658         }
5659
5660       if (c->ts.type == BT_DERIVED
5661             && sym->component_access != ACCESS_PRIVATE
5662             && gfc_check_access(sym->attr.access, sym->ns->default_access)
5663             && !c->ts.derived->attr.use_assoc
5664             && !gfc_check_access(c->ts.derived->attr.access,
5665                                  c->ts.derived->ns->default_access))
5666         {
5667           gfc_error ("The component '%s' is a PRIVATE type and cannot be "
5668                      "a component of '%s', which is PUBLIC at %L",
5669                       c->name, sym->name, &sym->declared_at);
5670           return FAILURE;
5671         }
5672
5673       if (sym->attr.sequence)
5674         {
5675           if (c->ts.type == BT_DERIVED && c->ts.derived->attr.sequence == 0)
5676             {
5677               gfc_error ("Component %s of SEQUENCE type declared at %L does "
5678                          "not have the SEQUENCE attribute",
5679                          c->ts.derived->name, &sym->declared_at);
5680               return FAILURE;
5681             }
5682         }
5683
5684       if (c->ts.type == BT_DERIVED && c->pointer
5685             && c->ts.derived->components == NULL)
5686         {
5687           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
5688                      "that has not been declared", c->name, sym->name,
5689                      &c->loc);
5690           return FAILURE;
5691         }
5692
5693       if (c->pointer || c->allocatable ||  c->as == NULL)
5694         continue;
5695
5696       for (i = 0; i < c->as->rank; i++)
5697         {
5698           if (c->as->lower[i] == NULL
5699                 || !gfc_is_constant_expr (c->as->lower[i])
5700                 || (resolve_index_expr (c->as->lower[i]) == FAILURE)
5701                 || c->as->upper[i] == NULL
5702                 || (resolve_index_expr (c->as->upper[i]) == FAILURE)
5703                 || !gfc_is_constant_expr (c->as->upper[i]))
5704             {
5705               gfc_error ("Component '%s' of '%s' at %L must have "
5706                          "constant array bounds",
5707                          c->name, sym->name, &c->loc);
5708               return FAILURE;
5709             }
5710         }
5711     }
5712
5713   /* Add derived type to the derived type list.  */
5714   for (dt_list = sym->ns->derived_types; dt_list; dt_list = dt_list->next)
5715     if (sym == dt_list->derived)
5716       break;
5717
5718   if (dt_list == NULL)
5719     {
5720       dt_list = gfc_get_dt_list ();
5721       dt_list->next = sym->ns->derived_types;
5722       dt_list->derived = sym;
5723       sym->ns->derived_types = dt_list;
5724     }
5725
5726   return SUCCESS;
5727 }
5728
5729
5730 static try
5731 resolve_fl_namelist (gfc_symbol *sym)
5732 {
5733   gfc_namelist *nl;
5734   gfc_symbol *nlsym;
5735
5736   /* Reject PRIVATE objects in a PUBLIC namelist.  */
5737   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
5738     {
5739       for (nl = sym->namelist; nl; nl = nl->next)
5740         {
5741           if (!nl->sym->attr.use_assoc
5742                 && !(sym->ns->parent == nl->sym->ns)
5743                        && !gfc_check_access(nl->sym->attr.access,
5744                                             nl->sym->ns->default_access))
5745             {
5746               gfc_error ("PRIVATE symbol '%s' cannot be member of "
5747                          "PUBLIC namelist at %L", nl->sym->name,
5748                          &sym->declared_at);
5749               return FAILURE;
5750             }
5751         }
5752     }
5753
5754   /* Reject namelist arrays that are not constant shape.  */
5755   for (nl = sym->namelist; nl; nl = nl->next)
5756     {
5757       if (is_non_constant_shape_array (nl->sym))
5758         {
5759           gfc_error ("The array '%s' must have constant shape to be "
5760                      "a NAMELIST object at %L", nl->sym->name,
5761                      &sym->declared_at);
5762           return FAILURE;
5763         }
5764     }
5765
5766   /* Namelist objects cannot have allocatable components.  */
5767   for (nl = sym->namelist; nl; nl = nl->next)
5768     {
5769       if (nl->sym->ts.type == BT_DERIVED
5770             && nl->sym->ts.derived->attr.alloc_comp)
5771         {
5772           gfc_error ("NAMELIST object '%s' at %L cannot have ALLOCATABLE "
5773                      "components", nl->sym->name, &sym->declared_at);
5774           return FAILURE;
5775         }
5776     }
5777
5778   /* 14.1.2 A module or internal procedure represent local entities
5779      of the same type as a namelist member and so are not allowed.
5780      Note that this is sometimes caught by check_conflict so the
5781      same message has been used.  */
5782   for (nl = sym->namelist; nl; nl = nl->next)
5783     {
5784       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
5785         continue;
5786       nlsym = NULL;
5787       if (sym->ns->parent && nl->sym && nl->sym->name)
5788         gfc_find_symbol (nl->sym->name, sym->ns->parent, 0, &nlsym);
5789       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
5790         {
5791           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
5792                      "attribute in '%s' at %L", nlsym->name,
5793                      &sym->declared_at);
5794           return FAILURE;
5795         }
5796     }
5797
5798   return SUCCESS;
5799 }
5800
5801
5802 static try
5803 resolve_fl_parameter (gfc_symbol *sym)
5804 {
5805   /* A parameter array's shape needs to be constant.  */
5806   if (sym->as != NULL && !gfc_is_compile_time_shape (sym->as))
5807     {
5808       gfc_error ("Parameter array '%s' at %L cannot be automatic "
5809                  "or assumed shape", sym->name, &sym->declared_at);
5810       return FAILURE;
5811     }
5812
5813   /* Make sure a parameter that has been implicitly typed still
5814      matches the implicit type, since PARAMETER statements can precede
5815      IMPLICIT statements.  */
5816   if (sym->attr.implicit_type
5817         && !gfc_compare_types (&sym->ts,
5818                                gfc_get_default_type (sym, sym->ns)))
5819     {
5820       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
5821                  "later IMPLICIT type", sym->name, &sym->declared_at);
5822       return FAILURE;
5823     }
5824
5825   /* Make sure the types of derived parameters are consistent.  This
5826      type checking is deferred until resolution because the type may
5827      refer to a derived type from the host.  */
5828   if (sym->ts.type == BT_DERIVED
5829         && !gfc_compare_types (&sym->ts, &sym->value->ts))
5830     {
5831       gfc_error ("Incompatible derived type in PARAMETER at %L",
5832                  &sym->value->where);
5833       return FAILURE;
5834     }
5835   return SUCCESS;
5836 }
5837
5838
5839 /* Do anything necessary to resolve a symbol.  Right now, we just
5840    assume that an otherwise unknown symbol is a variable.  This sort
5841    of thing commonly happens for symbols in module.  */
5842
5843 static void
5844 resolve_symbol (gfc_symbol * sym)
5845 {
5846   /* Zero if we are checking a formal namespace.  */
5847   static int formal_ns_flag = 1;
5848   int formal_ns_save, check_constant, mp_flag;
5849   gfc_symtree *symtree;
5850   gfc_symtree *this_symtree;
5851   gfc_namespace *ns;
5852   gfc_component *c;
5853
5854   if (sym->attr.flavor == FL_UNKNOWN)
5855     {
5856
5857     /* If we find that a flavorless symbol is an interface in one of the
5858        parent namespaces, find its symtree in this namespace, free the
5859        symbol and set the symtree to point to the interface symbol.  */
5860       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
5861         {
5862           symtree = gfc_find_symtree (ns->sym_root, sym->name);
5863           if (symtree && symtree->n.sym->generic)
5864             {
5865               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
5866                                                sym->name);
5867               sym->refs--;
5868               if (!sym->refs)
5869                 gfc_free_symbol (sym);
5870               symtree->n.sym->refs++;
5871               this_symtree->n.sym = symtree->n.sym;
5872               return;
5873             }
5874         }
5875
5876       /* Otherwise give it a flavor according to such attributes as
5877          it has.  */
5878       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
5879         sym->attr.flavor = FL_VARIABLE;
5880       else
5881         {
5882           sym->attr.flavor = FL_PROCEDURE;
5883           if (sym->attr.dimension)
5884             sym->attr.function = 1;
5885         }
5886     }
5887
5888   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
5889     return;
5890
5891   /* Symbols that are module procedures with results (functions) have
5892      the types and array specification copied for type checking in
5893      procedures that call them, as well as for saving to a module
5894      file.  These symbols can't stand the scrutiny that their results
5895      can.  */
5896   mp_flag = (sym->result != NULL && sym->result != sym);
5897
5898   /* Assign default type to symbols that need one and don't have one.  */
5899   if (sym->ts.type == BT_UNKNOWN)
5900     {
5901       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
5902         gfc_set_default_type (sym, 1, NULL);
5903
5904       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
5905         {
5906           /* The specific case of an external procedure should emit an error
5907              in the case that there is no implicit type.  */
5908           if (!mp_flag)
5909             gfc_set_default_type (sym, sym->attr.external, NULL);
5910           else
5911             {
5912               /* Result may be in another namespace.  */
5913               resolve_symbol (sym->result);
5914
5915               sym->ts = sym->result->ts;
5916               sym->as = gfc_copy_array_spec (sym->result->as);
5917               sym->attr.dimension = sym->result->attr.dimension;
5918               sym->attr.pointer = sym->result->attr.pointer;
5919               sym->attr.allocatable = sym->result->attr.allocatable;
5920             }
5921         }
5922     }
5923
5924   /* Assumed size arrays and assumed shape arrays must be dummy
5925      arguments.  */
5926
5927   if (sym->as != NULL
5928       && (sym->as->type == AS_ASSUMED_SIZE
5929           || sym->as->type == AS_ASSUMED_SHAPE)
5930       && sym->attr.dummy == 0)
5931     {
5932       if (sym->as->type == AS_ASSUMED_SIZE)
5933         gfc_error ("Assumed size array at %L must be a dummy argument",
5934                    &sym->declared_at);
5935       else
5936         gfc_error ("Assumed shape array at %L must be a dummy argument",
5937                    &sym->declared_at);
5938       return;
5939     }
5940
5941   /* Make sure symbols with known intent or optional are really dummy
5942      variable.  Because of ENTRY statement, this has to be deferred
5943      until resolution time.  */
5944
5945   if (!sym->attr.dummy
5946       && (sym->attr.optional
5947           || sym->attr.intent != INTENT_UNKNOWN))
5948     {
5949       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
5950       return;
5951     }
5952
5953   /* If a derived type symbol has reached this point, without its
5954      type being declared, we have an error.  Notice that most
5955      conditions that produce undefined derived types have already
5956      been dealt with.  However, the likes of:
5957      implicit type(t) (t) ..... call foo (t) will get us here if
5958      the type is not declared in the scope of the implicit
5959      statement. Change the type to BT_UNKNOWN, both because it is so
5960      and to prevent an ICE.  */
5961   if (sym->ts.type == BT_DERIVED
5962         && sym->ts.derived->components == NULL)
5963     {
5964       gfc_error ("The derived type '%s' at %L is of type '%s', "
5965                  "which has not been defined", sym->name,
5966                   &sym->declared_at, sym->ts.derived->name);
5967       sym->ts.type = BT_UNKNOWN;
5968       return;
5969     }
5970
5971   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
5972      default initialization is defined (5.1.2.4.4).  */
5973   if (sym->ts.type == BT_DERIVED
5974         && sym->attr.dummy
5975         && sym->attr.intent == INTENT_OUT
5976         && sym->as
5977         && sym->as->type == AS_ASSUMED_SIZE)
5978     {
5979       for (c = sym->ts.derived->components; c; c = c->next)
5980         {
5981           if (c->initializer)
5982             {
5983               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
5984                          "ASSUMED SIZE and so cannot have a default initializer",
5985                          sym->name, &sym->declared_at);
5986               return;
5987             }
5988         }
5989     }
5990
5991   switch (sym->attr.flavor)
5992     {
5993     case FL_VARIABLE:
5994       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
5995         return;
5996       break;
5997
5998     case FL_PROCEDURE:
5999       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
6000         return;
6001       break;
6002
6003     case FL_NAMELIST:
6004       if (resolve_fl_namelist (sym) == FAILURE)
6005         return;
6006       break;
6007
6008     case FL_PARAMETER:
6009       if (resolve_fl_parameter (sym) == FAILURE)
6010         return;
6011       break;
6012
6013     default:
6014       break;
6015     }
6016
6017   /* Make sure that intrinsic exist */
6018   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
6019       && ! gfc_intrinsic_name(sym->name, 0)
6020       && ! gfc_intrinsic_name(sym->name, 1))
6021     gfc_error("Intrinsic at %L does not exist", &sym->declared_at);
6022
6023   /* Resolve array specifier. Check as well some constraints
6024      on COMMON blocks.  */
6025
6026   check_constant = sym->attr.in_common && !sym->attr.pointer;
6027   gfc_resolve_array_spec (sym->as, check_constant);
6028
6029   /* Resolve formal namespaces.  */
6030
6031   if (formal_ns_flag && sym != NULL && sym->formal_ns != NULL)
6032     {
6033       formal_ns_save = formal_ns_flag;
6034       formal_ns_flag = 0;
6035       gfc_resolve (sym->formal_ns);
6036       formal_ns_flag = formal_ns_save;
6037     }
6038
6039   /* Check threadprivate restrictions.  */
6040   if (sym->attr.threadprivate && !sym->attr.save
6041       && (!sym->attr.in_common
6042           && sym->module == NULL
6043           && (sym->ns->proc_name == NULL
6044               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
6045     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
6046
6047   /* If we have come this far we can apply default-initializers, as
6048      described in 14.7.5, to those variables that have not already
6049      been assigned one.  */
6050   if (sym->ts.type == BT_DERIVED
6051         && sym->attr.referenced
6052         && sym->ns == gfc_current_ns
6053         && !sym->value
6054         && !sym->attr.allocatable
6055         && !sym->attr.alloc_comp)
6056     {
6057       symbol_attribute *a = &sym->attr;
6058
6059       if ((!a->save && !a->dummy && !a->pointer
6060                 && !a->in_common && !a->use_assoc
6061                 && !(a->function && sym != sym->result))
6062              ||
6063           (a->dummy && a->intent == INTENT_OUT))
6064         apply_default_init (sym);
6065     }
6066 }
6067
6068
6069
6070 /************* Resolve DATA statements *************/
6071
6072 static struct
6073 {
6074   gfc_data_value *vnode;
6075   unsigned int left;
6076 }
6077 values;
6078
6079
6080 /* Advance the values structure to point to the next value in the data list.  */
6081
6082 static try
6083 next_data_value (void)
6084 {
6085   while (values.left == 0)
6086     {
6087       if (values.vnode->next == NULL)
6088         return FAILURE;
6089
6090       values.vnode = values.vnode->next;
6091       values.left = values.vnode->repeat;
6092     }
6093
6094   return SUCCESS;
6095 }
6096
6097
6098 static try
6099 check_data_variable (gfc_data_variable * var, locus * where)
6100 {
6101   gfc_expr *e;
6102   mpz_t size;
6103   mpz_t offset;
6104   try t;
6105   ar_type mark = AR_UNKNOWN;
6106   int i;
6107   mpz_t section_index[GFC_MAX_DIMENSIONS];
6108   gfc_ref *ref;
6109   gfc_array_ref *ar;
6110
6111   if (gfc_resolve_expr (var->expr) == FAILURE)
6112     return FAILURE;
6113
6114   ar = NULL;
6115   mpz_init_set_si (offset, 0);
6116   e = var->expr;
6117
6118   if (e->expr_type != EXPR_VARIABLE)
6119     gfc_internal_error ("check_data_variable(): Bad expression");
6120
6121   if (e->symtree->n.sym->ns->is_block_data
6122         && !e->symtree->n.sym->attr.in_common)
6123     {
6124       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
6125                  e->symtree->n.sym->name, &e->symtree->n.sym->declared_at);
6126     }
6127
6128   if (e->rank == 0)
6129     {
6130       mpz_init_set_ui (size, 1);
6131       ref = NULL;
6132     }
6133   else
6134     {
6135       ref = e->ref;
6136
6137       /* Find the array section reference.  */
6138       for (ref = e->ref; ref; ref = ref->next)
6139         {
6140           if (ref->type != REF_ARRAY)
6141             continue;
6142           if (ref->u.ar.type == AR_ELEMENT)
6143             continue;
6144           break;
6145         }
6146       gcc_assert (ref);
6147
6148       /* Set marks according to the reference pattern.  */
6149       switch (ref->u.ar.type)
6150         {
6151         case AR_FULL:
6152           mark = AR_FULL;
6153           break;
6154
6155         case AR_SECTION:
6156           ar = &ref->u.ar;
6157           /* Get the start position of array section.  */
6158           gfc_get_section_index (ar, section_index, &offset);
6159           mark = AR_SECTION;
6160           break;
6161
6162         default:
6163           gcc_unreachable ();
6164         }
6165
6166       if (gfc_array_size (e, &size) == FAILURE)
6167         {
6168           gfc_error ("Nonconstant array section at %L in DATA statement",
6169                      &e->where);
6170           mpz_clear (offset);
6171           return FAILURE;
6172         }
6173     }
6174
6175   t = SUCCESS;
6176
6177   while (mpz_cmp_ui (size, 0) > 0)
6178     {
6179       if (next_data_value () == FAILURE)
6180         {
6181           gfc_error ("DATA statement at %L has more variables than values",
6182                      where);
6183           t = FAILURE;
6184           break;
6185         }
6186
6187       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
6188       if (t == FAILURE)
6189         break;
6190
6191       /* If we have more than one element left in the repeat count,
6192          and we have more than one element left in the target variable,
6193          then create a range assignment.  */
6194       /* ??? Only done for full arrays for now, since array sections
6195          seem tricky.  */
6196       if (mark == AR_FULL && ref && ref->next == NULL
6197           && values.left > 1 && mpz_cmp_ui (size, 1) > 0)
6198         {
6199           mpz_t range;
6200
6201           if (mpz_cmp_ui (size, values.left) >= 0)
6202             {
6203               mpz_init_set_ui (range, values.left);
6204               mpz_sub_ui (size, size, values.left);
6205               values.left = 0;
6206             }
6207           else
6208             {
6209               mpz_init_set (range, size);
6210               values.left -= mpz_get_ui (size);
6211               mpz_set_ui (size, 0);
6212             }
6213
6214           gfc_assign_data_value_range (var->expr, values.vnode->expr,
6215                                        offset, range);
6216
6217           mpz_add (offset, offset, range);
6218           mpz_clear (range);
6219         }
6220
6221       /* Assign initial value to symbol.  */
6222       else
6223         {
6224           values.left -= 1;
6225           mpz_sub_ui (size, size, 1);
6226
6227           gfc_assign_data_value (var->expr, values.vnode->expr, offset);
6228
6229           if (mark == AR_FULL)
6230             mpz_add_ui (offset, offset, 1);
6231
6232           /* Modify the array section indexes and recalculate the offset
6233              for next element.  */
6234           else if (mark == AR_SECTION)
6235             gfc_advance_section (section_index, ar, &offset);
6236         }
6237     }
6238
6239   if (mark == AR_SECTION)
6240     {
6241       for (i = 0; i < ar->dimen; i++)
6242         mpz_clear (section_index[i]);
6243     }
6244
6245   mpz_clear (size);
6246   mpz_clear (offset);
6247
6248   return t;
6249 }
6250
6251
6252 static try traverse_data_var (gfc_data_variable *, locus *);
6253
6254 /* Iterate over a list of elements in a DATA statement.  */
6255
6256 static try
6257 traverse_data_list (gfc_data_variable * var, locus * where)
6258 {
6259   mpz_t trip;
6260   iterator_stack frame;
6261   gfc_expr *e;
6262
6263   mpz_init (frame.value);
6264
6265   mpz_init_set (trip, var->iter.end->value.integer);
6266   mpz_sub (trip, trip, var->iter.start->value.integer);
6267   mpz_add (trip, trip, var->iter.step->value.integer);
6268
6269   mpz_div (trip, trip, var->iter.step->value.integer);
6270
6271   mpz_set (frame.value, var->iter.start->value.integer);
6272
6273   frame.prev = iter_stack;
6274   frame.variable = var->iter.var->symtree;
6275   iter_stack = &frame;
6276
6277   while (mpz_cmp_ui (trip, 0) > 0)
6278     {
6279       if (traverse_data_var (var->list, where) == FAILURE)
6280         {
6281           mpz_clear (trip);
6282           return FAILURE;
6283         }
6284
6285       e = gfc_copy_expr (var->expr);
6286       if (gfc_simplify_expr (e, 1) == FAILURE)
6287         {
6288           gfc_free_expr (e);
6289           return FAILURE;
6290         }
6291
6292       mpz_add (frame.value, frame.value, var->iter.step->value.integer);
6293
6294       mpz_sub_ui (trip, trip, 1);
6295     }
6296
6297   mpz_clear (trip);
6298   mpz_clear (frame.value);
6299
6300   iter_stack = frame.prev;
6301   return SUCCESS;
6302 }
6303
6304
6305 /* Type resolve variables in the variable list of a DATA statement.  */
6306
6307 static try
6308 traverse_data_var (gfc_data_variable * var, locus * where)
6309 {
6310   try t;
6311
6312   for (; var; var = var->next)
6313     {
6314       if (var->expr == NULL)
6315         t = traverse_data_list (var, where);
6316       else
6317         t = check_data_variable (var, where);
6318
6319       if (t == FAILURE)
6320         return FAILURE;
6321     }
6322
6323   return SUCCESS;
6324 }
6325
6326
6327 /* Resolve the expressions and iterators associated with a data statement.
6328    This is separate from the assignment checking because data lists should
6329    only be resolved once.  */
6330
6331 static try
6332 resolve_data_variables (gfc_data_variable * d)
6333 {
6334   for (; d; d = d->next)
6335     {
6336       if (d->list == NULL)
6337         {
6338           if (gfc_resolve_expr (d->expr) == FAILURE)
6339             return FAILURE;
6340         }
6341       else
6342         {
6343           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
6344             return FAILURE;
6345
6346           if (d->iter.start->expr_type != EXPR_CONSTANT
6347               || d->iter.end->expr_type != EXPR_CONSTANT
6348               || d->iter.step->expr_type != EXPR_CONSTANT)
6349             gfc_internal_error ("resolve_data_variables(): Bad iterator");
6350
6351           if (resolve_data_variables (d->list) == FAILURE)
6352             return FAILURE;
6353         }
6354     }
6355
6356   return SUCCESS;
6357 }
6358
6359
6360 /* Resolve a single DATA statement.  We implement this by storing a pointer to
6361    the value list into static variables, and then recursively traversing the
6362    variables list, expanding iterators and such.  */
6363
6364 static void
6365 resolve_data (gfc_data * d)
6366 {
6367   if (resolve_data_variables (d->var) == FAILURE)
6368     return;
6369
6370   values.vnode = d->value;
6371   values.left = (d->value == NULL) ? 0 : d->value->repeat;
6372
6373   if (traverse_data_var (d->var, &d->where) == FAILURE)
6374     return;
6375
6376   /* At this point, we better not have any values left.  */
6377
6378   if (next_data_value () == SUCCESS)
6379     gfc_error ("DATA statement at %L has more values than variables",
6380                &d->where);
6381 }
6382
6383
6384 /* Determines if a variable is not 'pure', ie not assignable within a pure
6385    procedure.  Returns zero if assignment is OK, nonzero if there is a problem.
6386  */
6387
6388 int
6389 gfc_impure_variable (gfc_symbol * sym)
6390 {
6391   if (sym->attr.use_assoc || sym->attr.in_common)
6392     return 1;
6393
6394   if (sym->ns != gfc_current_ns)
6395     return !sym->attr.function;
6396
6397   /* TODO: Check storage association through EQUIVALENCE statements */
6398
6399   return 0;
6400 }
6401
6402
6403 /* Test whether a symbol is pure or not.  For a NULL pointer, checks the
6404    symbol of the current procedure.  */
6405
6406 int
6407 gfc_pure (gfc_symbol * sym)
6408 {
6409   symbol_attribute attr;
6410
6411   if (sym == NULL)
6412     sym = gfc_current_ns->proc_name;
6413   if (sym == NULL)
6414     return 0;
6415
6416   attr = sym->attr;
6417
6418   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
6419 }
6420
6421
6422 /* Test whether the current procedure is elemental or not.  */
6423
6424 int
6425 gfc_elemental (gfc_symbol * sym)
6426 {
6427   symbol_attribute attr;
6428
6429   if (sym == NULL)
6430     sym = gfc_current_ns->proc_name;
6431   if (sym == NULL)
6432     return 0;
6433   attr = sym->attr;
6434
6435   return attr.flavor == FL_PROCEDURE && attr.elemental;
6436 }
6437
6438
6439 /* Warn about unused labels.  */
6440
6441 static void
6442 warn_unused_fortran_label (gfc_st_label * label)
6443 {
6444   if (label == NULL)
6445     return;
6446
6447   warn_unused_fortran_label (label->left);
6448
6449   if (label->defined == ST_LABEL_UNKNOWN)
6450     return;
6451
6452   switch (label->referenced)
6453     {
6454     case ST_LABEL_UNKNOWN:
6455       gfc_warning ("Label %d at %L defined but not used", label->value,
6456                    &label->where);
6457       break;
6458
6459     case ST_LABEL_BAD_TARGET:
6460       gfc_warning ("Label %d at %L defined but cannot be used",
6461                    label->value, &label->where);
6462       break;
6463
6464     default:
6465       break;
6466     }
6467
6468   warn_unused_fortran_label (label->right);
6469 }
6470
6471
6472 /* Returns the sequence type of a symbol or sequence.  */
6473
6474 static seq_type
6475 sequence_type (gfc_typespec ts)
6476 {
6477   seq_type result;
6478   gfc_component *c;
6479
6480   switch (ts.type)
6481   {
6482     case BT_DERIVED:
6483
6484       if (ts.derived->components == NULL)
6485         return SEQ_NONDEFAULT;
6486
6487       result = sequence_type (ts.derived->components->ts);
6488       for (c = ts.derived->components->next; c; c = c->next)
6489         if (sequence_type (c->ts) != result)
6490           return SEQ_MIXED;
6491
6492       return result;
6493
6494     case BT_CHARACTER:
6495       if (ts.kind != gfc_default_character_kind)
6496           return SEQ_NONDEFAULT;
6497
6498       return SEQ_CHARACTER;
6499
6500     case BT_INTEGER:
6501       if (ts.kind != gfc_default_integer_kind)
6502           return SEQ_NONDEFAULT;
6503
6504       return SEQ_NUMERIC;
6505
6506     case BT_REAL:
6507       if (!(ts.kind == gfc_default_real_kind
6508              || ts.kind == gfc_default_double_kind))
6509           return SEQ_NONDEFAULT;
6510
6511       return SEQ_NUMERIC;
6512
6513     case BT_COMPLEX:
6514       if (ts.kind != gfc_default_complex_kind)
6515           return SEQ_NONDEFAULT;
6516
6517       return SEQ_NUMERIC;
6518
6519     case BT_LOGICAL:
6520       if (ts.kind != gfc_default_logical_kind)
6521           return SEQ_NONDEFAULT;
6522
6523       return SEQ_NUMERIC;
6524
6525     default:
6526       return SEQ_NONDEFAULT;
6527   }
6528 }
6529
6530
6531 /* Resolve derived type EQUIVALENCE object.  */
6532
6533 static try
6534 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
6535 {
6536   gfc_symbol *d;
6537   gfc_component *c = derived->components;
6538
6539   if (!derived)
6540     return SUCCESS;
6541
6542   /* Shall not be an object of nonsequence derived type.  */
6543   if (!derived->attr.sequence)
6544     {
6545       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
6546                  "attribute to be an EQUIVALENCE object", sym->name, &e->where);
6547       return FAILURE;
6548     }
6549
6550   /* Shall not have allocatable components. */
6551   if (derived->attr.alloc_comp)
6552     {
6553       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
6554                  "components to be an EQUIVALENCE object",sym->name, &e->where);
6555       return FAILURE;
6556     }
6557
6558   for (; c ; c = c->next)
6559     {
6560       d = c->ts.derived;
6561       if (d && (resolve_equivalence_derived (c->ts.derived, sym, e) == FAILURE))
6562         return FAILURE;
6563
6564       /* Shall not be an object of sequence derived type containing a pointer
6565          in the structure.  */
6566       if (c->pointer)
6567         {
6568           gfc_error ("Derived type variable '%s' at %L with pointer component(s) "
6569                      "cannot be an EQUIVALENCE object", sym->name, &e->where);
6570           return FAILURE;
6571         }
6572
6573       if (c->initializer)
6574         {
6575           gfc_error ("Derived type variable '%s' at %L with default initializer "
6576                      "cannot be an EQUIVALENCE object", sym->name, &e->where);
6577           return FAILURE;
6578         }
6579     }
6580   return SUCCESS;
6581 }
6582
6583
6584 /* Resolve equivalence object. 
6585    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
6586    an allocatable array, an object of nonsequence derived type, an object of
6587    sequence derived type containing a pointer at any level of component
6588    selection, an automatic object, a function name, an entry name, a result
6589    name, a named constant, a structure component, or a subobject of any of
6590    the preceding objects.  A substring shall not have length zero.  A
6591    derived type shall not have components with default initialization nor
6592    shall two objects of an equivalence group be initialized.
6593    The simple constraints are done in symbol.c(check_conflict) and the rest
6594    are implemented here.  */
6595
6596 static void
6597 resolve_equivalence (gfc_equiv *eq)
6598 {
6599   gfc_symbol *sym;
6600   gfc_symbol *derived;
6601   gfc_symbol *first_sym;
6602   gfc_expr *e;
6603   gfc_ref *r;
6604   locus *last_where = NULL;
6605   seq_type eq_type, last_eq_type;
6606   gfc_typespec *last_ts;
6607   int object;
6608   const char *value_name;
6609   const char *msg;
6610
6611   value_name = NULL;
6612   last_ts = &eq->expr->symtree->n.sym->ts;
6613
6614   first_sym = eq->expr->symtree->n.sym;
6615
6616   for (object = 1; eq; eq = eq->eq, object++)
6617     {
6618       e = eq->expr;
6619
6620       e->ts = e->symtree->n.sym->ts;
6621       /* match_varspec might not know yet if it is seeing
6622          array reference or substring reference, as it doesn't
6623          know the types.  */
6624       if (e->ref && e->ref->type == REF_ARRAY)
6625         {
6626           gfc_ref *ref = e->ref;
6627           sym = e->symtree->n.sym;
6628
6629           if (sym->attr.dimension)
6630             {
6631               ref->u.ar.as = sym->as;
6632               ref = ref->next;
6633             }
6634
6635           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
6636           if (e->ts.type == BT_CHARACTER
6637               && ref
6638               && ref->type == REF_ARRAY
6639               && ref->u.ar.dimen == 1
6640               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
6641               && ref->u.ar.stride[0] == NULL)
6642             {
6643               gfc_expr *start = ref->u.ar.start[0];
6644               gfc_expr *end = ref->u.ar.end[0];
6645               void *mem = NULL;
6646
6647               /* Optimize away the (:) reference.  */
6648               if (start == NULL && end == NULL)
6649                 {
6650                   if (e->ref == ref)
6651                     e->ref = ref->next;
6652                   else
6653                     e->ref->next = ref->next;
6654                   mem = ref;
6655                 }
6656               else
6657                 {
6658                   ref->type = REF_SUBSTRING;
6659                   if (start == NULL)
6660                     start = gfc_int_expr (1);
6661                   ref->u.ss.start = start;
6662                   if (end == NULL && e->ts.cl)
6663                     end = gfc_copy_expr (e->ts.cl->length);
6664                   ref->u.ss.end = end;
6665                   ref->u.ss.length = e->ts.cl;
6666                   e->ts.cl = NULL;
6667                 }
6668               ref = ref->next;
6669               gfc_free (mem);
6670             }
6671
6672           /* Any further ref is an error.  */
6673           if (ref)
6674             {
6675               gcc_assert (ref->type == REF_ARRAY);
6676               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
6677                          &ref->u.ar.where);
6678               continue;
6679             }
6680         }
6681
6682       if (gfc_resolve_expr (e) == FAILURE)
6683         continue;
6684
6685       sym = e->symtree->n.sym;
6686
6687       /* An equivalence statement cannot have more than one initialized
6688          object.  */
6689       if (sym->value)
6690         {
6691           if (value_name != NULL)
6692             {
6693               gfc_error ("Initialized objects '%s' and '%s' cannot both "
6694                          "be in the EQUIVALENCE statement at %L",
6695                          value_name, sym->name, &e->where);
6696               continue;
6697             }
6698           else
6699             value_name = sym->name;
6700         }
6701
6702       /* Shall not equivalence common block variables in a PURE procedure.  */
6703       if (sym->ns->proc_name
6704             && sym->ns->proc_name->attr.pure
6705             && sym->attr.in_common)
6706         {
6707           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
6708                      "object in the pure procedure '%s'",
6709                      sym->name, &e->where, sym->ns->proc_name->name);
6710           break;
6711         }
6712
6713       /* Shall not be a named constant.  */
6714       if (e->expr_type == EXPR_CONSTANT)
6715         {
6716           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
6717                      "object", sym->name, &e->where);
6718           continue;
6719         }
6720
6721       derived = e->ts.derived;
6722       if (derived && resolve_equivalence_derived (derived, sym, e) == FAILURE)
6723         continue;
6724
6725       /* Check that the types correspond correctly:
6726          Note 5.28:
6727          A numeric sequence structure may be equivalenced to another sequence
6728          structure, an object of default integer type, default real type, double
6729          precision real type, default logical type such that components of the
6730          structure ultimately only become associated to objects of the same
6731          kind. A character sequence structure may be equivalenced to an object
6732          of default character kind or another character sequence structure.
6733          Other objects may be equivalenced only to objects of the same type and
6734          kind parameters.  */
6735
6736       /* Identical types are unconditionally OK.  */
6737       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
6738         goto identical_types;
6739
6740       last_eq_type = sequence_type (*last_ts);
6741       eq_type = sequence_type (sym->ts);
6742
6743       /* Since the pair of objects is not of the same type, mixed or
6744          non-default sequences can be rejected.  */
6745
6746       msg = "Sequence %s with mixed components in EQUIVALENCE "
6747             "statement at %L with different type objects";
6748       if ((object ==2
6749                && last_eq_type == SEQ_MIXED
6750                && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
6751                                   last_where) == FAILURE)
6752            ||  (eq_type == SEQ_MIXED
6753                && gfc_notify_std (GFC_STD_GNU, msg,sym->name,
6754                                   &e->where) == FAILURE))
6755         continue;
6756
6757       msg = "Non-default type object or sequence %s in EQUIVALENCE "
6758             "statement at %L with objects of different type";
6759       if ((object ==2
6760                && last_eq_type == SEQ_NONDEFAULT
6761                && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
6762                                   last_where) == FAILURE)
6763            ||  (eq_type == SEQ_NONDEFAULT
6764                && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6765                                   &e->where) == FAILURE))
6766         continue;
6767
6768       msg ="Non-CHARACTER object '%s' in default CHARACTER "
6769            "EQUIVALENCE statement at %L";
6770       if (last_eq_type == SEQ_CHARACTER
6771             && eq_type != SEQ_CHARACTER
6772             && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6773                                   &e->where) == FAILURE)
6774                 continue;
6775
6776       msg ="Non-NUMERIC object '%s' in default NUMERIC "
6777            "EQUIVALENCE statement at %L";
6778       if (last_eq_type == SEQ_NUMERIC
6779             && eq_type != SEQ_NUMERIC
6780             && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6781                                   &e->where) == FAILURE)
6782                 continue;
6783
6784   identical_types:
6785       last_ts =&sym->ts;
6786       last_where = &e->where;
6787
6788       if (!e->ref)
6789         continue;
6790
6791       /* Shall not be an automatic array.  */
6792       if (e->ref->type == REF_ARRAY
6793           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
6794         {
6795           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
6796                      "an EQUIVALENCE object", sym->name, &e->where);
6797           continue;
6798         }
6799
6800       r = e->ref;
6801       while (r)
6802         {
6803           /* Shall not be a structure component.  */
6804           if (r->type == REF_COMPONENT)
6805             {
6806               gfc_error ("Structure component '%s' at %L cannot be an "
6807                          "EQUIVALENCE object",
6808                          r->u.c.component->name, &e->where);
6809               break;
6810             }
6811
6812           /* A substring shall not have length zero.  */
6813           if (r->type == REF_SUBSTRING)
6814             {
6815               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
6816                 {
6817                   gfc_error ("Substring at %L has length zero",
6818                              &r->u.ss.start->where);
6819                   break;
6820                 }
6821             }
6822           r = r->next;
6823         }
6824     }
6825 }
6826
6827
6828 /* Resolve function and ENTRY types, issue diagnostics if needed. */
6829
6830 static void
6831 resolve_fntype (gfc_namespace * ns)
6832 {
6833   gfc_entry_list *el;
6834   gfc_symbol *sym;
6835
6836   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
6837     return;
6838
6839   /* If there are any entries, ns->proc_name is the entry master
6840      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
6841   if (ns->entries)
6842     sym = ns->entries->sym;
6843   else
6844     sym = ns->proc_name;
6845   if (sym->result == sym
6846       && sym->ts.type == BT_UNKNOWN
6847       && gfc_set_default_type (sym, 0, NULL) == FAILURE
6848       && !sym->attr.untyped)
6849     {
6850       gfc_error ("Function '%s' at %L has no IMPLICIT type",
6851                  sym->name, &sym->declared_at);
6852       sym->attr.untyped = 1;
6853     }
6854
6855   if (sym->ts.type == BT_DERIVED && !sym->ts.derived->attr.use_assoc
6856       && !gfc_check_access (sym->ts.derived->attr.access,
6857                             sym->ts.derived->ns->default_access)
6858       && gfc_check_access (sym->attr.access, sym->ns->default_access))
6859     {
6860       gfc_error ("PUBLIC function '%s' at %L cannot be of PRIVATE type '%s'",
6861                  sym->name, &sym->declared_at, sym->ts.derived->name);
6862     }
6863
6864   /* Make sure that the type of a module derived type function is in the
6865      module namespace, by copying it from the namespace's derived type
6866      list, if necessary.  */
6867   if (sym->ts.type == BT_DERIVED
6868         && sym->ns->proc_name->attr.flavor == FL_MODULE
6869         && sym->ts.derived->ns
6870         && sym->ns != sym->ts.derived->ns)
6871     {
6872       gfc_dt_list *dt = sym->ns->derived_types;
6873
6874       for (; dt; dt = dt->next)
6875         if (gfc_compare_derived_types (sym->ts.derived, dt->derived))
6876           sym->ts.derived = dt->derived;
6877     }
6878
6879   if (ns->entries)
6880     for (el = ns->entries->next; el; el = el->next)
6881       {
6882         if (el->sym->result == el->sym
6883             && el->sym->ts.type == BT_UNKNOWN
6884             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
6885             && !el->sym->attr.untyped)
6886           {
6887             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
6888                        el->sym->name, &el->sym->declared_at);
6889             el->sym->attr.untyped = 1;
6890           }
6891       }
6892 }
6893
6894 /* 12.3.2.1.1 Defined operators.  */
6895
6896 static void
6897 gfc_resolve_uops(gfc_symtree *symtree)
6898 {
6899   gfc_interface *itr;
6900   gfc_symbol *sym;
6901   gfc_formal_arglist *formal;
6902
6903   if (symtree == NULL)
6904     return;
6905
6906   gfc_resolve_uops (symtree->left);
6907   gfc_resolve_uops (symtree->right);
6908
6909   for (itr = symtree->n.uop->operator; itr; itr = itr->next)
6910     {
6911       sym = itr->sym;
6912       if (!sym->attr.function)
6913         gfc_error("User operator procedure '%s' at %L must be a FUNCTION",
6914                   sym->name, &sym->declared_at);
6915
6916       if (sym->ts.type == BT_CHARACTER
6917             && !(sym->ts.cl && sym->ts.cl->length)
6918             && !(sym->result && sym->result->ts.cl && sym->result->ts.cl->length))
6919         gfc_error("User operator procedure '%s' at %L cannot be assumed character "
6920                   "length", sym->name, &sym->declared_at);
6921
6922       formal = sym->formal;
6923       if (!formal || !formal->sym)
6924         {
6925           gfc_error("User operator procedure '%s' at %L must have at least "
6926                     "one argument", sym->name, &sym->declared_at);
6927           continue;
6928         }
6929
6930       if (formal->sym->attr.intent != INTENT_IN)
6931         gfc_error ("First argument of operator interface at %L must be "
6932                    "INTENT(IN)", &sym->declared_at);
6933
6934       if (formal->sym->attr.optional)
6935         gfc_error ("First argument of operator interface at %L cannot be "
6936                    "optional", &sym->declared_at);
6937
6938       formal = formal->next;
6939       if (!formal || !formal->sym)
6940         continue;
6941
6942       if (formal->sym->attr.intent != INTENT_IN)
6943         gfc_error ("Second argument of operator interface at %L must be "
6944                    "INTENT(IN)", &sym->declared_at);
6945
6946       if (formal->sym->attr.optional)
6947         gfc_error ("Second argument of operator interface at %L cannot be "
6948                    "optional", &sym->declared_at);
6949
6950       if (formal->next)
6951         gfc_error ("Operator interface at %L must have, at most, two "
6952                    "arguments", &sym->declared_at);
6953     }
6954 }
6955
6956
6957 /* Examine all of the expressions associated with a program unit,
6958    assign types to all intermediate expressions, make sure that all
6959    assignments are to compatible types and figure out which names
6960    refer to which functions or subroutines.  It doesn't check code
6961    block, which is handled by resolve_code.  */
6962
6963 static void
6964 resolve_types (gfc_namespace * ns)
6965 {
6966   gfc_namespace *n;
6967   gfc_charlen *cl;
6968   gfc_data *d;
6969   gfc_equiv *eq;
6970
6971   gfc_current_ns = ns;
6972
6973   resolve_entries (ns);
6974
6975   resolve_contained_functions (ns);
6976
6977   gfc_traverse_ns (ns, resolve_symbol);
6978
6979   resolve_fntype (ns);
6980
6981   for (n = ns->contained; n; n = n->sibling)
6982     {
6983       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
6984         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
6985                    "also be PURE", n->proc_name->name,
6986                    &n->proc_name->declared_at);
6987
6988       resolve_types (n);
6989     }
6990
6991   forall_flag = 0;
6992   gfc_check_interfaces (ns);
6993
6994   for (cl = ns->cl_list; cl; cl = cl->next)
6995     resolve_charlen (cl);
6996
6997   gfc_traverse_ns (ns, resolve_values);
6998
6999   if (ns->save_all)
7000     gfc_save_all (ns);
7001
7002   iter_stack = NULL;
7003   for (d = ns->data; d; d = d->next)
7004     resolve_data (d);
7005
7006   iter_stack = NULL;
7007   gfc_traverse_ns (ns, gfc_formalize_init_value);
7008
7009   for (eq = ns->equiv; eq; eq = eq->next)
7010     resolve_equivalence (eq);
7011
7012   /* Warn about unused labels.  */
7013   if (warn_unused_label)
7014     warn_unused_fortran_label (ns->st_labels);
7015
7016   gfc_resolve_uops (ns->uop_root);
7017 }
7018
7019
7020 /* Call resolve_code recursively.  */
7021
7022 static void
7023 resolve_codes (gfc_namespace * ns)
7024 {
7025   gfc_namespace *n;
7026
7027   for (n = ns->contained; n; n = n->sibling)
7028     resolve_codes (n);
7029
7030   gfc_current_ns = ns;
7031   cs_base = NULL;
7032   /* Set to an out of range value.  */
7033   current_entry_id = -1;
7034   resolve_code (ns->code, ns);
7035 }
7036
7037
7038 /* This function is called after a complete program unit has been compiled.
7039    Its purpose is to examine all of the expressions associated with a program
7040    unit, assign types to all intermediate expressions, make sure that all
7041    assignments are to compatible types and figure out which names refer to
7042    which functions or subroutines.  */
7043
7044 void
7045 gfc_resolve (gfc_namespace * ns)
7046 {
7047   gfc_namespace *old_ns;
7048
7049   old_ns = gfc_current_ns;
7050
7051   resolve_types (ns);
7052   resolve_codes (ns);
7053
7054   gfc_current_ns = old_ns;
7055 }