OSDN Git Service

2009-10-21 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009
3    Free Software Foundation, 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 3, 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 COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32
33 /* Types used in equivalence statements.  */
34
35 typedef enum seq_type
36 {
37   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
38 }
39 seq_type;
40
41 /* Stack to keep track of the nesting of blocks as we move through the
42    code.  See resolve_branch() and resolve_code().  */
43
44 typedef struct code_stack
45 {
46   struct gfc_code *head, *current;
47   struct code_stack *prev;
48
49   /* This bitmap keeps track of the targets valid for a branch from
50      inside this block except for END {IF|SELECT}s of enclosing
51      blocks.  */
52   bitmap reachable_labels;
53 }
54 code_stack;
55
56 static code_stack *cs_base = NULL;
57
58
59 /* Nonzero if we're inside a FORALL block.  */
60
61 static int forall_flag;
62
63 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
64
65 static int omp_workshare_flag;
66
67 /* Nonzero if we are processing a formal arglist. The corresponding function
68    resets the flag each time that it is read.  */
69 static int formal_arg_flag = 0;
70
71 /* True if we are resolving a specification expression.  */
72 static int specification_expr = 0;
73
74 /* The id of the last entry seen.  */
75 static int current_entry_id;
76
77 /* We use bitmaps to determine if a branch target is valid.  */
78 static bitmap_obstack labels_obstack;
79
80 int
81 gfc_is_formal_arg (void)
82 {
83   return formal_arg_flag;
84 }
85
86 /* Is the symbol host associated?  */
87 static bool
88 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
89 {
90   for (ns = ns->parent; ns; ns = ns->parent)
91     {      
92       if (sym->ns == ns)
93         return true;
94     }
95
96   return false;
97 }
98
99 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
100    an ABSTRACT derived-type.  If where is not NULL, an error message with that
101    locus is printed, optionally using name.  */
102
103 static gfc_try
104 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
105 {
106   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
107     {
108       if (where)
109         {
110           if (name)
111             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
112                        name, where, ts->u.derived->name);
113           else
114             gfc_error ("ABSTRACT type '%s' used at %L",
115                        ts->u.derived->name, where);
116         }
117
118       return FAILURE;
119     }
120
121   return SUCCESS;
122 }
123
124
125 /* Resolve types of formal argument lists.  These have to be done early so that
126    the formal argument lists of module procedures can be copied to the
127    containing module before the individual procedures are resolved
128    individually.  We also resolve argument lists of procedures in interface
129    blocks because they are self-contained scoping units.
130
131    Since a dummy argument cannot be a non-dummy procedure, the only
132    resort left for untyped names are the IMPLICIT types.  */
133
134 static void
135 resolve_formal_arglist (gfc_symbol *proc)
136 {
137   gfc_formal_arglist *f;
138   gfc_symbol *sym;
139   int i;
140
141   if (proc->result != NULL)
142     sym = proc->result;
143   else
144     sym = proc;
145
146   if (gfc_elemental (proc)
147       || sym->attr.pointer || sym->attr.allocatable
148       || (sym->as && sym->as->rank > 0))
149     {
150       proc->attr.always_explicit = 1;
151       sym->attr.always_explicit = 1;
152     }
153
154   formal_arg_flag = 1;
155
156   for (f = proc->formal; f; f = f->next)
157     {
158       sym = f->sym;
159
160       if (sym == NULL)
161         {
162           /* Alternate return placeholder.  */
163           if (gfc_elemental (proc))
164             gfc_error ("Alternate return specifier in elemental subroutine "
165                        "'%s' at %L is not allowed", proc->name,
166                        &proc->declared_at);
167           if (proc->attr.function)
168             gfc_error ("Alternate return specifier in function "
169                        "'%s' at %L is not allowed", proc->name,
170                        &proc->declared_at);
171           continue;
172         }
173
174       if (sym->attr.if_source != IFSRC_UNKNOWN)
175         resolve_formal_arglist (sym);
176
177       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
178         {
179           if (gfc_pure (proc) && !gfc_pure (sym))
180             {
181               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
182                          "also be PURE", sym->name, &sym->declared_at);
183               continue;
184             }
185
186           if (gfc_elemental (proc))
187             {
188               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
189                          "procedure", &sym->declared_at);
190               continue;
191             }
192
193           if (sym->attr.function
194                 && sym->ts.type == BT_UNKNOWN
195                 && sym->attr.intrinsic)
196             {
197               gfc_intrinsic_sym *isym;
198               isym = gfc_find_function (sym->name);
199               if (isym == NULL || !isym->specific)
200                 {
201                   gfc_error ("Unable to find a specific INTRINSIC procedure "
202                              "for the reference '%s' at %L", sym->name,
203                              &sym->declared_at);
204                 }
205               sym->ts = isym->ts;
206             }
207
208           continue;
209         }
210
211       if (sym->ts.type == BT_UNKNOWN)
212         {
213           if (!sym->attr.function || sym->result == sym)
214             gfc_set_default_type (sym, 1, sym->ns);
215         }
216
217       gfc_resolve_array_spec (sym->as, 0);
218
219       /* We can't tell if an array with dimension (:) is assumed or deferred
220          shape until we know if it has the pointer or allocatable attributes.
221       */
222       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
223           && !(sym->attr.pointer || sym->attr.allocatable))
224         {
225           sym->as->type = AS_ASSUMED_SHAPE;
226           for (i = 0; i < sym->as->rank; i++)
227             sym->as->lower[i] = gfc_int_expr (1);
228         }
229
230       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
231           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
232           || sym->attr.optional)
233         {
234           proc->attr.always_explicit = 1;
235           if (proc->result)
236             proc->result->attr.always_explicit = 1;
237         }
238
239       /* If the flavor is unknown at this point, it has to be a variable.
240          A procedure specification would have already set the type.  */
241
242       if (sym->attr.flavor == FL_UNKNOWN)
243         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
244
245       if (gfc_pure (proc) && !sym->attr.pointer
246           && sym->attr.flavor != FL_PROCEDURE)
247         {
248           if (proc->attr.function && sym->attr.intent != INTENT_IN)
249             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
250                        "INTENT(IN)", sym->name, proc->name,
251                        &sym->declared_at);
252
253           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
254             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
255                        "have its INTENT specified", sym->name, proc->name,
256                        &sym->declared_at);
257         }
258
259       if (gfc_elemental (proc))
260         {
261           if (sym->as != NULL)
262             {
263               gfc_error ("Argument '%s' of elemental procedure at %L must "
264                          "be scalar", sym->name, &sym->declared_at);
265               continue;
266             }
267
268           if (sym->attr.pointer)
269             {
270               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
271                          "have the POINTER attribute", sym->name,
272                          &sym->declared_at);
273               continue;
274             }
275
276           if (sym->attr.flavor == FL_PROCEDURE)
277             {
278               gfc_error ("Dummy procedure '%s' not allowed in elemental "
279                          "procedure '%s' at %L", sym->name, proc->name,
280                          &sym->declared_at);
281               continue;
282             }
283         }
284
285       /* Each dummy shall be specified to be scalar.  */
286       if (proc->attr.proc == PROC_ST_FUNCTION)
287         {
288           if (sym->as != NULL)
289             {
290               gfc_error ("Argument '%s' of statement function at %L must "
291                          "be scalar", sym->name, &sym->declared_at);
292               continue;
293             }
294
295           if (sym->ts.type == BT_CHARACTER)
296             {
297               gfc_charlen *cl = sym->ts.u.cl;
298               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
299                 {
300                   gfc_error ("Character-valued argument '%s' of statement "
301                              "function at %L must have constant length",
302                              sym->name, &sym->declared_at);
303                   continue;
304                 }
305             }
306         }
307     }
308   formal_arg_flag = 0;
309 }
310
311
312 /* Work function called when searching for symbols that have argument lists
313    associated with them.  */
314
315 static void
316 find_arglists (gfc_symbol *sym)
317 {
318   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
319     return;
320
321   resolve_formal_arglist (sym);
322 }
323
324
325 /* Given a namespace, resolve all formal argument lists within the namespace.
326  */
327
328 static void
329 resolve_formal_arglists (gfc_namespace *ns)
330 {
331   if (ns == NULL)
332     return;
333
334   gfc_traverse_ns (ns, find_arglists);
335 }
336
337
338 static void
339 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
340 {
341   gfc_try t;
342
343   /* If this namespace is not a function or an entry master function,
344      ignore it.  */
345   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
346       || sym->attr.entry_master)
347     return;
348
349   /* Try to find out of what the return type is.  */
350   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
351     {
352       t = gfc_set_default_type (sym->result, 0, ns);
353
354       if (t == FAILURE && !sym->result->attr.untyped)
355         {
356           if (sym->result == sym)
357             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
358                        sym->name, &sym->declared_at);
359           else if (!sym->result->attr.proc_pointer)
360             gfc_error ("Result '%s' of contained function '%s' at %L has "
361                        "no IMPLICIT type", sym->result->name, sym->name,
362                        &sym->result->declared_at);
363           sym->result->attr.untyped = 1;
364         }
365     }
366
367   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
368      type, lists the only ways a character length value of * can be used:
369      dummy arguments of procedures, named constants, and function results
370      in external functions.  Internal function results and results of module
371      procedures are not on this list, ergo, not permitted.  */
372
373   if (sym->result->ts.type == BT_CHARACTER)
374     {
375       gfc_charlen *cl = sym->result->ts.u.cl;
376       if (!cl || !cl->length)
377         {
378           /* See if this is a module-procedure and adapt error message
379              accordingly.  */
380           bool module_proc;
381           gcc_assert (ns->parent && ns->parent->proc_name);
382           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
383
384           gfc_error ("Character-valued %s '%s' at %L must not be"
385                      " assumed length",
386                      module_proc ? _("module procedure")
387                                  : _("internal function"),
388                      sym->name, &sym->declared_at);
389         }
390     }
391 }
392
393
394 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
395    introduce duplicates.  */
396
397 static void
398 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
399 {
400   gfc_formal_arglist *f, *new_arglist;
401   gfc_symbol *new_sym;
402
403   for (; new_args != NULL; new_args = new_args->next)
404     {
405       new_sym = new_args->sym;
406       /* See if this arg is already in the formal argument list.  */
407       for (f = proc->formal; f; f = f->next)
408         {
409           if (new_sym == f->sym)
410             break;
411         }
412
413       if (f)
414         continue;
415
416       /* Add a new argument.  Argument order is not important.  */
417       new_arglist = gfc_get_formal_arglist ();
418       new_arglist->sym = new_sym;
419       new_arglist->next = proc->formal;
420       proc->formal  = new_arglist;
421     }
422 }
423
424
425 /* Flag the arguments that are not present in all entries.  */
426
427 static void
428 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
429 {
430   gfc_formal_arglist *f, *head;
431   head = new_args;
432
433   for (f = proc->formal; f; f = f->next)
434     {
435       if (f->sym == NULL)
436         continue;
437
438       for (new_args = head; new_args; new_args = new_args->next)
439         {
440           if (new_args->sym == f->sym)
441             break;
442         }
443
444       if (new_args)
445         continue;
446
447       f->sym->attr.not_always_present = 1;
448     }
449 }
450
451
452 /* Resolve alternate entry points.  If a symbol has multiple entry points we
453    create a new master symbol for the main routine, and turn the existing
454    symbol into an entry point.  */
455
456 static void
457 resolve_entries (gfc_namespace *ns)
458 {
459   gfc_namespace *old_ns;
460   gfc_code *c;
461   gfc_symbol *proc;
462   gfc_entry_list *el;
463   char name[GFC_MAX_SYMBOL_LEN + 1];
464   static int master_count = 0;
465
466   if (ns->proc_name == NULL)
467     return;
468
469   /* No need to do anything if this procedure doesn't have alternate entry
470      points.  */
471   if (!ns->entries)
472     return;
473
474   /* We may already have resolved alternate entry points.  */
475   if (ns->proc_name->attr.entry_master)
476     return;
477
478   /* If this isn't a procedure something has gone horribly wrong.  */
479   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
480
481   /* Remember the current namespace.  */
482   old_ns = gfc_current_ns;
483
484   gfc_current_ns = ns;
485
486   /* Add the main entry point to the list of entry points.  */
487   el = gfc_get_entry_list ();
488   el->sym = ns->proc_name;
489   el->id = 0;
490   el->next = ns->entries;
491   ns->entries = el;
492   ns->proc_name->attr.entry = 1;
493
494   /* If it is a module function, it needs to be in the right namespace
495      so that gfc_get_fake_result_decl can gather up the results. The
496      need for this arose in get_proc_name, where these beasts were
497      left in their own namespace, to keep prior references linked to
498      the entry declaration.*/
499   if (ns->proc_name->attr.function
500       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
501     el->sym->ns = ns;
502
503   /* Do the same for entries where the master is not a module
504      procedure.  These are retained in the module namespace because
505      of the module procedure declaration.  */
506   for (el = el->next; el; el = el->next)
507     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
508           && el->sym->attr.mod_proc)
509       el->sym->ns = ns;
510   el = ns->entries;
511
512   /* Add an entry statement for it.  */
513   c = gfc_get_code ();
514   c->op = EXEC_ENTRY;
515   c->ext.entry = el;
516   c->next = ns->code;
517   ns->code = c;
518
519   /* Create a new symbol for the master function.  */
520   /* Give the internal function a unique name (within this file).
521      Also include the function name so the user has some hope of figuring
522      out what is going on.  */
523   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
524             master_count++, ns->proc_name->name);
525   gfc_get_ha_symbol (name, &proc);
526   gcc_assert (proc != NULL);
527
528   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
529   if (ns->proc_name->attr.subroutine)
530     gfc_add_subroutine (&proc->attr, proc->name, NULL);
531   else
532     {
533       gfc_symbol *sym;
534       gfc_typespec *ts, *fts;
535       gfc_array_spec *as, *fas;
536       gfc_add_function (&proc->attr, proc->name, NULL);
537       proc->result = proc;
538       fas = ns->entries->sym->as;
539       fas = fas ? fas : ns->entries->sym->result->as;
540       fts = &ns->entries->sym->result->ts;
541       if (fts->type == BT_UNKNOWN)
542         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
543       for (el = ns->entries->next; el; el = el->next)
544         {
545           ts = &el->sym->result->ts;
546           as = el->sym->as;
547           as = as ? as : el->sym->result->as;
548           if (ts->type == BT_UNKNOWN)
549             ts = gfc_get_default_type (el->sym->result->name, NULL);
550
551           if (! gfc_compare_types (ts, fts)
552               || (el->sym->result->attr.dimension
553                   != ns->entries->sym->result->attr.dimension)
554               || (el->sym->result->attr.pointer
555                   != ns->entries->sym->result->attr.pointer))
556             break;
557           else if (as && fas && ns->entries->sym->result != el->sym->result
558                       && gfc_compare_array_spec (as, fas) == 0)
559             gfc_error ("Function %s at %L has entries with mismatched "
560                        "array specifications", ns->entries->sym->name,
561                        &ns->entries->sym->declared_at);
562           /* The characteristics need to match and thus both need to have
563              the same string length, i.e. both len=*, or both len=4.
564              Having both len=<variable> is also possible, but difficult to
565              check at compile time.  */
566           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
567                    && (((ts->u.cl->length && !fts->u.cl->length)
568                         ||(!ts->u.cl->length && fts->u.cl->length))
569                        || (ts->u.cl->length
570                            && ts->u.cl->length->expr_type
571                               != fts->u.cl->length->expr_type)
572                        || (ts->u.cl->length
573                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
574                            && mpz_cmp (ts->u.cl->length->value.integer,
575                                        fts->u.cl->length->value.integer) != 0)))
576             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
577                             "entries returning variables of different "
578                             "string lengths", ns->entries->sym->name,
579                             &ns->entries->sym->declared_at);
580         }
581
582       if (el == NULL)
583         {
584           sym = ns->entries->sym->result;
585           /* All result types the same.  */
586           proc->ts = *fts;
587           if (sym->attr.dimension)
588             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
589           if (sym->attr.pointer)
590             gfc_add_pointer (&proc->attr, NULL);
591         }
592       else
593         {
594           /* Otherwise the result will be passed through a union by
595              reference.  */
596           proc->attr.mixed_entry_master = 1;
597           for (el = ns->entries; el; el = el->next)
598             {
599               sym = el->sym->result;
600               if (sym->attr.dimension)
601                 {
602                   if (el == ns->entries)
603                     gfc_error ("FUNCTION result %s can't be an array in "
604                                "FUNCTION %s at %L", sym->name,
605                                ns->entries->sym->name, &sym->declared_at);
606                   else
607                     gfc_error ("ENTRY result %s can't be an array in "
608                                "FUNCTION %s at %L", sym->name,
609                                ns->entries->sym->name, &sym->declared_at);
610                 }
611               else if (sym->attr.pointer)
612                 {
613                   if (el == ns->entries)
614                     gfc_error ("FUNCTION result %s can't be a POINTER in "
615                                "FUNCTION %s at %L", sym->name,
616                                ns->entries->sym->name, &sym->declared_at);
617                   else
618                     gfc_error ("ENTRY result %s can't be a POINTER in "
619                                "FUNCTION %s at %L", sym->name,
620                                ns->entries->sym->name, &sym->declared_at);
621                 }
622               else
623                 {
624                   ts = &sym->ts;
625                   if (ts->type == BT_UNKNOWN)
626                     ts = gfc_get_default_type (sym->name, NULL);
627                   switch (ts->type)
628                     {
629                     case BT_INTEGER:
630                       if (ts->kind == gfc_default_integer_kind)
631                         sym = NULL;
632                       break;
633                     case BT_REAL:
634                       if (ts->kind == gfc_default_real_kind
635                           || ts->kind == gfc_default_double_kind)
636                         sym = NULL;
637                       break;
638                     case BT_COMPLEX:
639                       if (ts->kind == gfc_default_complex_kind)
640                         sym = NULL;
641                       break;
642                     case BT_LOGICAL:
643                       if (ts->kind == gfc_default_logical_kind)
644                         sym = NULL;
645                       break;
646                     case BT_UNKNOWN:
647                       /* We will issue error elsewhere.  */
648                       sym = NULL;
649                       break;
650                     default:
651                       break;
652                     }
653                   if (sym)
654                     {
655                       if (el == ns->entries)
656                         gfc_error ("FUNCTION result %s can't be of type %s "
657                                    "in FUNCTION %s at %L", sym->name,
658                                    gfc_typename (ts), ns->entries->sym->name,
659                                    &sym->declared_at);
660                       else
661                         gfc_error ("ENTRY result %s can't be of type %s "
662                                    "in FUNCTION %s at %L", sym->name,
663                                    gfc_typename (ts), ns->entries->sym->name,
664                                    &sym->declared_at);
665                     }
666                 }
667             }
668         }
669     }
670   proc->attr.access = ACCESS_PRIVATE;
671   proc->attr.entry_master = 1;
672
673   /* Merge all the entry point arguments.  */
674   for (el = ns->entries; el; el = el->next)
675     merge_argument_lists (proc, el->sym->formal);
676
677   /* Check the master formal arguments for any that are not
678      present in all entry points.  */
679   for (el = ns->entries; el; el = el->next)
680     check_argument_lists (proc, el->sym->formal);
681
682   /* Use the master function for the function body.  */
683   ns->proc_name = proc;
684
685   /* Finalize the new symbols.  */
686   gfc_commit_symbols ();
687
688   /* Restore the original namespace.  */
689   gfc_current_ns = old_ns;
690 }
691
692
693 static bool
694 has_default_initializer (gfc_symbol *der)
695 {
696   gfc_component *c;
697
698   gcc_assert (der->attr.flavor == FL_DERIVED);
699   for (c = der->components; c; c = c->next)
700     if ((c->ts.type != BT_DERIVED && c->initializer)
701         || (c->ts.type == BT_DERIVED
702             && (!c->attr.pointer && has_default_initializer (c->ts.u.derived))))
703       break;
704
705   return c != NULL;
706 }
707
708 /* Resolve common variables.  */
709 static void
710 resolve_common_vars (gfc_symbol *sym, bool named_common)
711 {
712   gfc_symbol *csym = sym;
713
714   for (; csym; csym = csym->common_next)
715     {
716       if (csym->value || csym->attr.data)
717         {
718           if (!csym->ns->is_block_data)
719             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
720                             "but only in BLOCK DATA initialization is "
721                             "allowed", csym->name, &csym->declared_at);
722           else if (!named_common)
723             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
724                             "in a blank COMMON but initialization is only "
725                             "allowed in named common blocks", csym->name,
726                             &csym->declared_at);
727         }
728
729       if (csym->ts.type != BT_DERIVED)
730         continue;
731
732       if (!(csym->ts.u.derived->attr.sequence
733             || csym->ts.u.derived->attr.is_bind_c))
734         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
735                        "has neither the SEQUENCE nor the BIND(C) "
736                        "attribute", csym->name, &csym->declared_at);
737       if (csym->ts.u.derived->attr.alloc_comp)
738         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
739                        "has an ultimate component that is "
740                        "allocatable", csym->name, &csym->declared_at);
741       if (has_default_initializer (csym->ts.u.derived))
742         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
743                        "may not have default initializer", csym->name,
744                        &csym->declared_at);
745
746       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
747         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
748     }
749 }
750
751 /* Resolve common blocks.  */
752 static void
753 resolve_common_blocks (gfc_symtree *common_root)
754 {
755   gfc_symbol *sym;
756
757   if (common_root == NULL)
758     return;
759
760   if (common_root->left)
761     resolve_common_blocks (common_root->left);
762   if (common_root->right)
763     resolve_common_blocks (common_root->right);
764
765   resolve_common_vars (common_root->n.common->head, true);
766
767   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
768   if (sym == NULL)
769     return;
770
771   if (sym->attr.flavor == FL_PARAMETER)
772     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
773                sym->name, &common_root->n.common->where, &sym->declared_at);
774
775   if (sym->attr.intrinsic)
776     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
777                sym->name, &common_root->n.common->where);
778   else if (sym->attr.result
779            ||(sym->attr.function && gfc_current_ns->proc_name == sym))
780     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
781                     "that is also a function result", sym->name,
782                     &common_root->n.common->where);
783   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
784            && sym->attr.proc != PROC_ST_FUNCTION)
785     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
786                     "that is also a global procedure", sym->name,
787                     &common_root->n.common->where);
788 }
789
790
791 /* Resolve contained function types.  Because contained functions can call one
792    another, they have to be worked out before any of the contained procedures
793    can be resolved.
794
795    The good news is that if a function doesn't already have a type, the only
796    way it can get one is through an IMPLICIT type or a RESULT variable, because
797    by definition contained functions are contained namespace they're contained
798    in, not in a sibling or parent namespace.  */
799
800 static void
801 resolve_contained_functions (gfc_namespace *ns)
802 {
803   gfc_namespace *child;
804   gfc_entry_list *el;
805
806   resolve_formal_arglists (ns);
807
808   for (child = ns->contained; child; child = child->sibling)
809     {
810       /* Resolve alternate entry points first.  */
811       resolve_entries (child);
812
813       /* Then check function return types.  */
814       resolve_contained_fntype (child->proc_name, child);
815       for (el = child->entries; el; el = el->next)
816         resolve_contained_fntype (el->sym, child);
817     }
818 }
819
820
821 /* Resolve all of the elements of a structure constructor and make sure that
822    the types are correct.  */
823
824 static gfc_try
825 resolve_structure_cons (gfc_expr *expr)
826 {
827   gfc_constructor *cons;
828   gfc_component *comp;
829   gfc_try t;
830   symbol_attribute a;
831
832   t = SUCCESS;
833   cons = expr->value.constructor;
834   /* A constructor may have references if it is the result of substituting a
835      parameter variable.  In this case we just pull out the component we
836      want.  */
837   if (expr->ref)
838     comp = expr->ref->u.c.sym->components;
839   else
840     comp = expr->ts.u.derived->components;
841
842   /* See if the user is trying to invoke a structure constructor for one of
843      the iso_c_binding derived types.  */
844   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
845       && expr->ts.u.derived->ts.is_iso_c && cons && cons->expr != NULL)
846     {
847       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
848                  expr->ts.u.derived->name, &(expr->where));
849       return FAILURE;
850     }
851
852   for (; comp; comp = comp->next, cons = cons->next)
853     {
854       int rank;
855
856       if (!cons->expr)
857         continue;
858
859       if (gfc_resolve_expr (cons->expr) == FAILURE)
860         {
861           t = FAILURE;
862           continue;
863         }
864
865       rank = comp->as ? comp->as->rank : 0;
866       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
867           && (comp->attr.allocatable || cons->expr->rank))
868         {
869           gfc_error ("The rank of the element in the derived type "
870                      "constructor at %L does not match that of the "
871                      "component (%d/%d)", &cons->expr->where,
872                      cons->expr->rank, rank);
873           t = FAILURE;
874         }
875
876       /* If we don't have the right type, try to convert it.  */
877
878       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
879         {
880           t = FAILURE;
881           if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
882             gfc_error ("The element in the derived type constructor at %L, "
883                        "for pointer component '%s', is %s but should be %s",
884                        &cons->expr->where, comp->name,
885                        gfc_basic_typename (cons->expr->ts.type),
886                        gfc_basic_typename (comp->ts.type));
887           else
888             t = gfc_convert_type (cons->expr, &comp->ts, 1);
889         }
890
891       if (cons->expr->expr_type == EXPR_NULL
892           && !(comp->attr.pointer || comp->attr.allocatable
893                || comp->attr.proc_pointer
894                || (comp->ts.type == BT_CLASS
895                    && (comp->ts.u.derived->components->attr.pointer
896                        || comp->ts.u.derived->components->attr.allocatable))))
897         {
898           t = FAILURE;
899           gfc_error ("The NULL in the derived type constructor at %L is "
900                      "being applied to component '%s', which is neither "
901                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
902                      comp->name);
903         }
904
905       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
906         continue;
907
908       a = gfc_expr_attr (cons->expr);
909
910       if (!a.pointer && !a.target)
911         {
912           t = FAILURE;
913           gfc_error ("The element in the derived type constructor at %L, "
914                      "for pointer component '%s' should be a POINTER or "
915                      "a TARGET", &cons->expr->where, comp->name);
916         }
917     }
918
919   return t;
920 }
921
922
923 /****************** Expression name resolution ******************/
924
925 /* Returns 0 if a symbol was not declared with a type or
926    attribute declaration statement, nonzero otherwise.  */
927
928 static int
929 was_declared (gfc_symbol *sym)
930 {
931   symbol_attribute a;
932
933   a = sym->attr;
934
935   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
936     return 1;
937
938   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
939       || a.optional || a.pointer || a.save || a.target || a.volatile_
940       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
941     return 1;
942
943   return 0;
944 }
945
946
947 /* Determine if a symbol is generic or not.  */
948
949 static int
950 generic_sym (gfc_symbol *sym)
951 {
952   gfc_symbol *s;
953
954   if (sym->attr.generic ||
955       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
956     return 1;
957
958   if (was_declared (sym) || sym->ns->parent == NULL)
959     return 0;
960
961   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
962   
963   if (s != NULL)
964     {
965       if (s == sym)
966         return 0;
967       else
968         return generic_sym (s);
969     }
970
971   return 0;
972 }
973
974
975 /* Determine if a symbol is specific or not.  */
976
977 static int
978 specific_sym (gfc_symbol *sym)
979 {
980   gfc_symbol *s;
981
982   if (sym->attr.if_source == IFSRC_IFBODY
983       || sym->attr.proc == PROC_MODULE
984       || sym->attr.proc == PROC_INTERNAL
985       || sym->attr.proc == PROC_ST_FUNCTION
986       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
987       || sym->attr.external)
988     return 1;
989
990   if (was_declared (sym) || sym->ns->parent == NULL)
991     return 0;
992
993   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
994
995   return (s == NULL) ? 0 : specific_sym (s);
996 }
997
998
999 /* Figure out if the procedure is specific, generic or unknown.  */
1000
1001 typedef enum
1002 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1003 proc_type;
1004
1005 static proc_type
1006 procedure_kind (gfc_symbol *sym)
1007 {
1008   if (generic_sym (sym))
1009     return PTYPE_GENERIC;
1010
1011   if (specific_sym (sym))
1012     return PTYPE_SPECIFIC;
1013
1014   return PTYPE_UNKNOWN;
1015 }
1016
1017 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1018    is nonzero when matching actual arguments.  */
1019
1020 static int need_full_assumed_size = 0;
1021
1022 static bool
1023 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1024 {
1025   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1026       return false;
1027
1028   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1029      What should it be?  */
1030   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1031           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1032                && (e->ref->u.ar.type == AR_FULL))
1033     {
1034       gfc_error ("The upper bound in the last dimension must "
1035                  "appear in the reference to the assumed size "
1036                  "array '%s' at %L", sym->name, &e->where);
1037       return true;
1038     }
1039   return false;
1040 }
1041
1042
1043 /* Look for bad assumed size array references in argument expressions
1044   of elemental and array valued intrinsic procedures.  Since this is
1045   called from procedure resolution functions, it only recurses at
1046   operators.  */
1047
1048 static bool
1049 resolve_assumed_size_actual (gfc_expr *e)
1050 {
1051   if (e == NULL)
1052    return false;
1053
1054   switch (e->expr_type)
1055     {
1056     case EXPR_VARIABLE:
1057       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1058         return true;
1059       break;
1060
1061     case EXPR_OP:
1062       if (resolve_assumed_size_actual (e->value.op.op1)
1063           || resolve_assumed_size_actual (e->value.op.op2))
1064         return true;
1065       break;
1066
1067     default:
1068       break;
1069     }
1070   return false;
1071 }
1072
1073
1074 /* Check a generic procedure, passed as an actual argument, to see if
1075    there is a matching specific name.  If none, it is an error, and if
1076    more than one, the reference is ambiguous.  */
1077 static int
1078 count_specific_procs (gfc_expr *e)
1079 {
1080   int n;
1081   gfc_interface *p;
1082   gfc_symbol *sym;
1083         
1084   n = 0;
1085   sym = e->symtree->n.sym;
1086
1087   for (p = sym->generic; p; p = p->next)
1088     if (strcmp (sym->name, p->sym->name) == 0)
1089       {
1090         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1091                                        sym->name);
1092         n++;
1093       }
1094
1095   if (n > 1)
1096     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1097                &e->where);
1098
1099   if (n == 0)
1100     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1101                "argument at %L", sym->name, &e->where);
1102
1103   return n;
1104 }
1105
1106
1107 /* See if a call to sym could possibly be a not allowed RECURSION because of
1108    a missing RECURIVE declaration.  This means that either sym is the current
1109    context itself, or sym is the parent of a contained procedure calling its
1110    non-RECURSIVE containing procedure.
1111    This also works if sym is an ENTRY.  */
1112
1113 static bool
1114 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1115 {
1116   gfc_symbol* proc_sym;
1117   gfc_symbol* context_proc;
1118   gfc_namespace* real_context;
1119
1120   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1121
1122   /* If we've got an ENTRY, find real procedure.  */
1123   if (sym->attr.entry && sym->ns->entries)
1124     proc_sym = sym->ns->entries->sym;
1125   else
1126     proc_sym = sym;
1127
1128   /* If sym is RECURSIVE, all is well of course.  */
1129   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1130     return false;
1131
1132   /* Find the context procedure's "real" symbol if it has entries.
1133      We look for a procedure symbol, so recurse on the parents if we don't
1134      find one (like in case of a BLOCK construct).  */
1135   for (real_context = context; ; real_context = real_context->parent)
1136     {
1137       /* We should find something, eventually!  */
1138       gcc_assert (real_context);
1139
1140       context_proc = (real_context->entries ? real_context->entries->sym
1141                                             : real_context->proc_name);
1142
1143       /* In some special cases, there may not be a proc_name, like for this
1144          invalid code:
1145          real(bad_kind()) function foo () ...
1146          when checking the call to bad_kind ().
1147          In these cases, we simply return here and assume that the
1148          call is ok.  */
1149       if (!context_proc)
1150         return false;
1151
1152       if (context_proc->attr.flavor != FL_LABEL)
1153         break;
1154     }
1155
1156   /* A call from sym's body to itself is recursion, of course.  */
1157   if (context_proc == proc_sym)
1158     return true;
1159
1160   /* The same is true if context is a contained procedure and sym the
1161      containing one.  */
1162   if (context_proc->attr.contained)
1163     {
1164       gfc_symbol* parent_proc;
1165
1166       gcc_assert (context->parent);
1167       parent_proc = (context->parent->entries ? context->parent->entries->sym
1168                                               : context->parent->proc_name);
1169
1170       if (parent_proc == proc_sym)
1171         return true;
1172     }
1173
1174   return false;
1175 }
1176
1177
1178 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1179    its typespec and formal argument list.  */
1180
1181 static gfc_try
1182 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1183 {
1184   gfc_intrinsic_sym* isym;
1185   const char* symstd;
1186
1187   if (sym->formal)
1188     return SUCCESS;
1189
1190   /* We already know this one is an intrinsic, so we don't call
1191      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1192      gfc_find_subroutine directly to check whether it is a function or
1193      subroutine.  */
1194
1195   if ((isym = gfc_find_function (sym->name)))
1196     {
1197       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1198           && !sym->attr.implicit_type)
1199         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1200                       " ignored", sym->name, &sym->declared_at);
1201
1202       if (!sym->attr.function &&
1203           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1204         return FAILURE;
1205
1206       sym->ts = isym->ts;
1207     }
1208   else if ((isym = gfc_find_subroutine (sym->name)))
1209     {
1210       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1211         {
1212           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1213                       " specifier", sym->name, &sym->declared_at);
1214           return FAILURE;
1215         }
1216
1217       if (!sym->attr.subroutine &&
1218           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1219         return FAILURE;
1220     }
1221   else
1222     {
1223       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1224                  &sym->declared_at);
1225       return FAILURE;
1226     }
1227
1228   gfc_copy_formal_args_intr (sym, isym);
1229
1230   /* Check it is actually available in the standard settings.  */
1231   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1232       == FAILURE)
1233     {
1234       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1235                  " available in the current standard settings but %s.  Use"
1236                  " an appropriate -std=* option or enable -fall-intrinsics"
1237                  " in order to use it.",
1238                  sym->name, &sym->declared_at, symstd);
1239       return FAILURE;
1240     }
1241
1242   return SUCCESS;
1243 }
1244
1245
1246 /* Resolve a procedure expression, like passing it to a called procedure or as
1247    RHS for a procedure pointer assignment.  */
1248
1249 static gfc_try
1250 resolve_procedure_expression (gfc_expr* expr)
1251 {
1252   gfc_symbol* sym;
1253
1254   if (expr->expr_type != EXPR_VARIABLE)
1255     return SUCCESS;
1256   gcc_assert (expr->symtree);
1257
1258   sym = expr->symtree->n.sym;
1259
1260   if (sym->attr.intrinsic)
1261     resolve_intrinsic (sym, &expr->where);
1262
1263   if (sym->attr.flavor != FL_PROCEDURE
1264       || (sym->attr.function && sym->result == sym))
1265     return SUCCESS;
1266
1267   /* A non-RECURSIVE procedure that is used as procedure expression within its
1268      own body is in danger of being called recursively.  */
1269   if (is_illegal_recursion (sym, gfc_current_ns))
1270     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1271                  " itself recursively.  Declare it RECURSIVE or use"
1272                  " -frecursive", sym->name, &expr->where);
1273   
1274   return SUCCESS;
1275 }
1276
1277
1278 /* Resolve an actual argument list.  Most of the time, this is just
1279    resolving the expressions in the list.
1280    The exception is that we sometimes have to decide whether arguments
1281    that look like procedure arguments are really simple variable
1282    references.  */
1283
1284 static gfc_try
1285 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1286                         bool no_formal_args)
1287 {
1288   gfc_symbol *sym;
1289   gfc_symtree *parent_st;
1290   gfc_expr *e;
1291   int save_need_full_assumed_size;
1292   gfc_component *comp;
1293         
1294   for (; arg; arg = arg->next)
1295     {
1296       e = arg->expr;
1297       if (e == NULL)
1298         {
1299           /* Check the label is a valid branching target.  */
1300           if (arg->label)
1301             {
1302               if (arg->label->defined == ST_LABEL_UNKNOWN)
1303                 {
1304                   gfc_error ("Label %d referenced at %L is never defined",
1305                              arg->label->value, &arg->label->where);
1306                   return FAILURE;
1307                 }
1308             }
1309           continue;
1310         }
1311
1312       if (gfc_is_proc_ptr_comp (e, &comp))
1313         {
1314           e->ts = comp->ts;
1315           if (e->expr_type == EXPR_PPC)
1316             {
1317               if (comp->as != NULL)
1318                 e->rank = comp->as->rank;
1319               e->expr_type = EXPR_FUNCTION;
1320             }
1321           goto argument_list;
1322         }
1323
1324       if (e->expr_type == EXPR_VARIABLE
1325             && e->symtree->n.sym->attr.generic
1326             && no_formal_args
1327             && count_specific_procs (e) != 1)
1328         return FAILURE;
1329
1330       if (e->ts.type != BT_PROCEDURE)
1331         {
1332           save_need_full_assumed_size = need_full_assumed_size;
1333           if (e->expr_type != EXPR_VARIABLE)
1334             need_full_assumed_size = 0;
1335           if (gfc_resolve_expr (e) != SUCCESS)
1336             return FAILURE;
1337           need_full_assumed_size = save_need_full_assumed_size;
1338           goto argument_list;
1339         }
1340
1341       /* See if the expression node should really be a variable reference.  */
1342
1343       sym = e->symtree->n.sym;
1344
1345       if (sym->attr.flavor == FL_PROCEDURE
1346           || sym->attr.intrinsic
1347           || sym->attr.external)
1348         {
1349           int actual_ok;
1350
1351           /* If a procedure is not already determined to be something else
1352              check if it is intrinsic.  */
1353           if (!sym->attr.intrinsic
1354               && !(sym->attr.external || sym->attr.use_assoc
1355                    || sym->attr.if_source == IFSRC_IFBODY)
1356               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1357             sym->attr.intrinsic = 1;
1358
1359           if (sym->attr.proc == PROC_ST_FUNCTION)
1360             {
1361               gfc_error ("Statement function '%s' at %L is not allowed as an "
1362                          "actual argument", sym->name, &e->where);
1363             }
1364
1365           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1366                                                sym->attr.subroutine);
1367           if (sym->attr.intrinsic && actual_ok == 0)
1368             {
1369               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1370                          "actual argument", sym->name, &e->where);
1371             }
1372
1373           if (sym->attr.contained && !sym->attr.use_assoc
1374               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1375             {
1376               gfc_error ("Internal procedure '%s' is not allowed as an "
1377                          "actual argument at %L", sym->name, &e->where);
1378             }
1379
1380           if (sym->attr.elemental && !sym->attr.intrinsic)
1381             {
1382               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1383                          "allowed as an actual argument at %L", sym->name,
1384                          &e->where);
1385             }
1386
1387           /* Check if a generic interface has a specific procedure
1388             with the same name before emitting an error.  */
1389           if (sym->attr.generic && count_specific_procs (e) != 1)
1390             return FAILURE;
1391           
1392           /* Just in case a specific was found for the expression.  */
1393           sym = e->symtree->n.sym;
1394
1395           /* If the symbol is the function that names the current (or
1396              parent) scope, then we really have a variable reference.  */
1397
1398           if (sym->attr.function && sym->result == sym
1399               && (sym->ns->proc_name == sym
1400                   || (sym->ns->parent != NULL
1401                       && sym->ns->parent->proc_name == sym)))
1402             goto got_variable;
1403
1404           /* If all else fails, see if we have a specific intrinsic.  */
1405           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1406             {
1407               gfc_intrinsic_sym *isym;
1408
1409               isym = gfc_find_function (sym->name);
1410               if (isym == NULL || !isym->specific)
1411                 {
1412                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1413                              "for the reference '%s' at %L", sym->name,
1414                              &e->where);
1415                   return FAILURE;
1416                 }
1417               sym->ts = isym->ts;
1418               sym->attr.intrinsic = 1;
1419               sym->attr.function = 1;
1420             }
1421
1422           if (gfc_resolve_expr (e) == FAILURE)
1423             return FAILURE;
1424           goto argument_list;
1425         }
1426
1427       /* See if the name is a module procedure in a parent unit.  */
1428
1429       if (was_declared (sym) || sym->ns->parent == NULL)
1430         goto got_variable;
1431
1432       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1433         {
1434           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1435           return FAILURE;
1436         }
1437
1438       if (parent_st == NULL)
1439         goto got_variable;
1440
1441       sym = parent_st->n.sym;
1442       e->symtree = parent_st;           /* Point to the right thing.  */
1443
1444       if (sym->attr.flavor == FL_PROCEDURE
1445           || sym->attr.intrinsic
1446           || sym->attr.external)
1447         {
1448           if (gfc_resolve_expr (e) == FAILURE)
1449             return FAILURE;
1450           goto argument_list;
1451         }
1452
1453     got_variable:
1454       e->expr_type = EXPR_VARIABLE;
1455       e->ts = sym->ts;
1456       if (sym->as != NULL)
1457         {
1458           e->rank = sym->as->rank;
1459           e->ref = gfc_get_ref ();
1460           e->ref->type = REF_ARRAY;
1461           e->ref->u.ar.type = AR_FULL;
1462           e->ref->u.ar.as = sym->as;
1463         }
1464
1465       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1466          primary.c (match_actual_arg). If above code determines that it
1467          is a  variable instead, it needs to be resolved as it was not
1468          done at the beginning of this function.  */
1469       save_need_full_assumed_size = need_full_assumed_size;
1470       if (e->expr_type != EXPR_VARIABLE)
1471         need_full_assumed_size = 0;
1472       if (gfc_resolve_expr (e) != SUCCESS)
1473         return FAILURE;
1474       need_full_assumed_size = save_need_full_assumed_size;
1475
1476     argument_list:
1477       /* Check argument list functions %VAL, %LOC and %REF.  There is
1478          nothing to do for %REF.  */
1479       if (arg->name && arg->name[0] == '%')
1480         {
1481           if (strncmp ("%VAL", arg->name, 4) == 0)
1482             {
1483               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1484                 {
1485                   gfc_error ("By-value argument at %L is not of numeric "
1486                              "type", &e->where);
1487                   return FAILURE;
1488                 }
1489
1490               if (e->rank)
1491                 {
1492                   gfc_error ("By-value argument at %L cannot be an array or "
1493                              "an array section", &e->where);
1494                 return FAILURE;
1495                 }
1496
1497               /* Intrinsics are still PROC_UNKNOWN here.  However,
1498                  since same file external procedures are not resolvable
1499                  in gfortran, it is a good deal easier to leave them to
1500                  intrinsic.c.  */
1501               if (ptype != PROC_UNKNOWN
1502                   && ptype != PROC_DUMMY
1503                   && ptype != PROC_EXTERNAL
1504                   && ptype != PROC_MODULE)
1505                 {
1506                   gfc_error ("By-value argument at %L is not allowed "
1507                              "in this context", &e->where);
1508                   return FAILURE;
1509                 }
1510             }
1511
1512           /* Statement functions have already been excluded above.  */
1513           else if (strncmp ("%LOC", arg->name, 4) == 0
1514                    && e->ts.type == BT_PROCEDURE)
1515             {
1516               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1517                 {
1518                   gfc_error ("Passing internal procedure at %L by location "
1519                              "not allowed", &e->where);
1520                   return FAILURE;
1521                 }
1522             }
1523         }
1524     }
1525
1526   return SUCCESS;
1527 }
1528
1529
1530 /* Do the checks of the actual argument list that are specific to elemental
1531    procedures.  If called with c == NULL, we have a function, otherwise if
1532    expr == NULL, we have a subroutine.  */
1533
1534 static gfc_try
1535 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1536 {
1537   gfc_actual_arglist *arg0;
1538   gfc_actual_arglist *arg;
1539   gfc_symbol *esym = NULL;
1540   gfc_intrinsic_sym *isym = NULL;
1541   gfc_expr *e = NULL;
1542   gfc_intrinsic_arg *iformal = NULL;
1543   gfc_formal_arglist *eformal = NULL;
1544   bool formal_optional = false;
1545   bool set_by_optional = false;
1546   int i;
1547   int rank = 0;
1548
1549   /* Is this an elemental procedure?  */
1550   if (expr && expr->value.function.actual != NULL)
1551     {
1552       if (expr->value.function.esym != NULL
1553           && expr->value.function.esym->attr.elemental)
1554         {
1555           arg0 = expr->value.function.actual;
1556           esym = expr->value.function.esym;
1557         }
1558       else if (expr->value.function.isym != NULL
1559                && expr->value.function.isym->elemental)
1560         {
1561           arg0 = expr->value.function.actual;
1562           isym = expr->value.function.isym;
1563         }
1564       else
1565         return SUCCESS;
1566     }
1567   else if (c && c->ext.actual != NULL)
1568     {
1569       arg0 = c->ext.actual;
1570       
1571       if (c->resolved_sym)
1572         esym = c->resolved_sym;
1573       else
1574         esym = c->symtree->n.sym;
1575       gcc_assert (esym);
1576
1577       if (!esym->attr.elemental)
1578         return SUCCESS;
1579     }
1580   else
1581     return SUCCESS;
1582
1583   /* The rank of an elemental is the rank of its array argument(s).  */
1584   for (arg = arg0; arg; arg = arg->next)
1585     {
1586       if (arg->expr != NULL && arg->expr->rank > 0)
1587         {
1588           rank = arg->expr->rank;
1589           if (arg->expr->expr_type == EXPR_VARIABLE
1590               && arg->expr->symtree->n.sym->attr.optional)
1591             set_by_optional = true;
1592
1593           /* Function specific; set the result rank and shape.  */
1594           if (expr)
1595             {
1596               expr->rank = rank;
1597               if (!expr->shape && arg->expr->shape)
1598                 {
1599                   expr->shape = gfc_get_shape (rank);
1600                   for (i = 0; i < rank; i++)
1601                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1602                 }
1603             }
1604           break;
1605         }
1606     }
1607
1608   /* If it is an array, it shall not be supplied as an actual argument
1609      to an elemental procedure unless an array of the same rank is supplied
1610      as an actual argument corresponding to a nonoptional dummy argument of
1611      that elemental procedure(12.4.1.5).  */
1612   formal_optional = false;
1613   if (isym)
1614     iformal = isym->formal;
1615   else
1616     eformal = esym->formal;
1617
1618   for (arg = arg0; arg; arg = arg->next)
1619     {
1620       if (eformal)
1621         {
1622           if (eformal->sym && eformal->sym->attr.optional)
1623             formal_optional = true;
1624           eformal = eformal->next;
1625         }
1626       else if (isym && iformal)
1627         {
1628           if (iformal->optional)
1629             formal_optional = true;
1630           iformal = iformal->next;
1631         }
1632       else if (isym)
1633         formal_optional = true;
1634
1635       if (pedantic && arg->expr != NULL
1636           && arg->expr->expr_type == EXPR_VARIABLE
1637           && arg->expr->symtree->n.sym->attr.optional
1638           && formal_optional
1639           && arg->expr->rank
1640           && (set_by_optional || arg->expr->rank != rank)
1641           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1642         {
1643           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1644                        "MISSING, it cannot be the actual argument of an "
1645                        "ELEMENTAL procedure unless there is a non-optional "
1646                        "argument with the same rank (12.4.1.5)",
1647                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1648           return FAILURE;
1649         }
1650     }
1651
1652   for (arg = arg0; arg; arg = arg->next)
1653     {
1654       if (arg->expr == NULL || arg->expr->rank == 0)
1655         continue;
1656
1657       /* Being elemental, the last upper bound of an assumed size array
1658          argument must be present.  */
1659       if (resolve_assumed_size_actual (arg->expr))
1660         return FAILURE;
1661
1662       /* Elemental procedure's array actual arguments must conform.  */
1663       if (e != NULL)
1664         {
1665           if (gfc_check_conformance (arg->expr, e,
1666                                      "elemental procedure") == FAILURE)
1667             return FAILURE;
1668         }
1669       else
1670         e = arg->expr;
1671     }
1672
1673   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1674      is an array, the intent inout/out variable needs to be also an array.  */
1675   if (rank > 0 && esym && expr == NULL)
1676     for (eformal = esym->formal, arg = arg0; arg && eformal;
1677          arg = arg->next, eformal = eformal->next)
1678       if ((eformal->sym->attr.intent == INTENT_OUT
1679            || eformal->sym->attr.intent == INTENT_INOUT)
1680           && arg->expr && arg->expr->rank == 0)
1681         {
1682           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1683                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1684                      "actual argument is an array", &arg->expr->where,
1685                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1686                      : "INOUT", eformal->sym->name, esym->name);
1687           return FAILURE;
1688         }
1689   return SUCCESS;
1690 }
1691
1692
1693 /* Go through each actual argument in ACTUAL and see if it can be
1694    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1695    function being called, or NULL if not known.  */
1696
1697 static void
1698 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1699 {
1700   gfc_actual_arglist *ap;
1701   gfc_expr *expr;
1702
1703   for (ap = actual; ap; ap = ap->next)
1704     if (ap->expr
1705         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1706         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1707                                          NOT_ELEMENTAL))
1708       ap->expr->inline_noncopying_intrinsic = 1;
1709 }
1710
1711
1712 /* This function does the checking of references to global procedures
1713    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1714    77 and 95 standards.  It checks for a gsymbol for the name, making
1715    one if it does not already exist.  If it already exists, then the
1716    reference being resolved must correspond to the type of gsymbol.
1717    Otherwise, the new symbol is equipped with the attributes of the
1718    reference.  The corresponding code that is called in creating
1719    global entities is parse.c.
1720
1721    In addition, for all but -std=legacy, the gsymbols are used to
1722    check the interfaces of external procedures from the same file.
1723    The namespace of the gsymbol is resolved and then, once this is
1724    done the interface is checked.  */
1725
1726
1727 static bool
1728 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1729 {
1730   if (!gsym_ns->proc_name->attr.recursive)
1731     return true;
1732
1733   if (sym->ns == gsym_ns)
1734     return false;
1735
1736   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1737     return false;
1738
1739   return true;
1740 }
1741
1742 static bool
1743 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1744 {
1745   if (gsym_ns->entries)
1746     {
1747       gfc_entry_list *entry = gsym_ns->entries;
1748
1749       for (; entry; entry = entry->next)
1750         {
1751           if (strcmp (sym->name, entry->sym->name) == 0)
1752             {
1753               if (strcmp (gsym_ns->proc_name->name,
1754                           sym->ns->proc_name->name) == 0)
1755                 return false;
1756
1757               if (sym->ns->parent
1758                   && strcmp (gsym_ns->proc_name->name,
1759                              sym->ns->parent->proc_name->name) == 0)
1760                 return false;
1761             }
1762         }
1763     }
1764   return true;
1765 }
1766
1767 static void
1768 resolve_global_procedure (gfc_symbol *sym, locus *where,
1769                           gfc_actual_arglist **actual, int sub)
1770 {
1771   gfc_gsymbol * gsym;
1772   gfc_namespace *ns;
1773   enum gfc_symbol_type type;
1774
1775   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1776
1777   gsym = gfc_get_gsymbol (sym->name);
1778
1779   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1780     gfc_global_used (gsym, where);
1781
1782   if (gfc_option.flag_whole_file
1783         && sym->attr.if_source == IFSRC_UNKNOWN
1784         && gsym->type != GSYM_UNKNOWN
1785         && gsym->ns
1786         && gsym->ns->resolved != -1
1787         && gsym->ns->proc_name
1788         && not_in_recursive (sym, gsym->ns)
1789         && not_entry_self_reference (sym, gsym->ns))
1790     {
1791       /* Make sure that translation for the gsymbol occurs before
1792          the procedure currently being resolved.  */
1793       ns = gsym->ns->resolved ? NULL : gfc_global_ns_list;
1794       for (; ns && ns != gsym->ns; ns = ns->sibling)
1795         {
1796           if (ns->sibling == gsym->ns)
1797             {
1798               ns->sibling = gsym->ns->sibling;
1799               gsym->ns->sibling = gfc_global_ns_list;
1800               gfc_global_ns_list = gsym->ns;
1801               break;
1802             }
1803         }
1804
1805       if (!gsym->ns->resolved)
1806         {
1807           gfc_dt_list *old_dt_list;
1808
1809           /* Stash away derived types so that the backend_decls do not
1810              get mixed up.  */
1811           old_dt_list = gfc_derived_types;
1812           gfc_derived_types = NULL;
1813
1814           gfc_resolve (gsym->ns);
1815
1816           /* Store the new derived types with the global namespace.  */
1817           if (gfc_derived_types)
1818             gsym->ns->derived_types = gfc_derived_types;
1819
1820           /* Restore the derived types of this namespace.  */
1821           gfc_derived_types = old_dt_list;
1822         }
1823
1824       if (gsym->ns->proc_name->attr.function
1825             && gsym->ns->proc_name->as
1826             && gsym->ns->proc_name->as->rank
1827             && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1828         gfc_error ("The reference to function '%s' at %L either needs an "
1829                    "explicit INTERFACE or the rank is incorrect", sym->name,
1830                    where);
1831
1832       if (gfc_option.flag_whole_file == 1
1833             || ((gfc_option.warn_std & GFC_STD_LEGACY)
1834                   &&
1835                !(gfc_option.warn_std & GFC_STD_GNU)))
1836         gfc_errors_to_warnings (1);
1837
1838       gfc_procedure_use (gsym->ns->proc_name, actual, where);
1839
1840       gfc_errors_to_warnings (0);
1841     }
1842
1843   if (gsym->type == GSYM_UNKNOWN)
1844     {
1845       gsym->type = type;
1846       gsym->where = *where;
1847     }
1848
1849   gsym->used = 1;
1850 }
1851
1852
1853 /************* Function resolution *************/
1854
1855 /* Resolve a function call known to be generic.
1856    Section 14.1.2.4.1.  */
1857
1858 static match
1859 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1860 {
1861   gfc_symbol *s;
1862
1863   if (sym->attr.generic)
1864     {
1865       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1866       if (s != NULL)
1867         {
1868           expr->value.function.name = s->name;
1869           expr->value.function.esym = s;
1870
1871           if (s->ts.type != BT_UNKNOWN)
1872             expr->ts = s->ts;
1873           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1874             expr->ts = s->result->ts;
1875
1876           if (s->as != NULL)
1877             expr->rank = s->as->rank;
1878           else if (s->result != NULL && s->result->as != NULL)
1879             expr->rank = s->result->as->rank;
1880
1881           gfc_set_sym_referenced (expr->value.function.esym);
1882
1883           return MATCH_YES;
1884         }
1885
1886       /* TODO: Need to search for elemental references in generic
1887          interface.  */
1888     }
1889
1890   if (sym->attr.intrinsic)
1891     return gfc_intrinsic_func_interface (expr, 0);
1892
1893   return MATCH_NO;
1894 }
1895
1896
1897 static gfc_try
1898 resolve_generic_f (gfc_expr *expr)
1899 {
1900   gfc_symbol *sym;
1901   match m;
1902
1903   sym = expr->symtree->n.sym;
1904
1905   for (;;)
1906     {
1907       m = resolve_generic_f0 (expr, sym);
1908       if (m == MATCH_YES)
1909         return SUCCESS;
1910       else if (m == MATCH_ERROR)
1911         return FAILURE;
1912
1913 generic:
1914       if (sym->ns->parent == NULL)
1915         break;
1916       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1917
1918       if (sym == NULL)
1919         break;
1920       if (!generic_sym (sym))
1921         goto generic;
1922     }
1923
1924   /* Last ditch attempt.  See if the reference is to an intrinsic
1925      that possesses a matching interface.  14.1.2.4  */
1926   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
1927     {
1928       gfc_error ("There is no specific function for the generic '%s' at %L",
1929                  expr->symtree->n.sym->name, &expr->where);
1930       return FAILURE;
1931     }
1932
1933   m = gfc_intrinsic_func_interface (expr, 0);
1934   if (m == MATCH_YES)
1935     return SUCCESS;
1936   if (m == MATCH_NO)
1937     gfc_error ("Generic function '%s' at %L is not consistent with a "
1938                "specific intrinsic interface", expr->symtree->n.sym->name,
1939                &expr->where);
1940
1941   return FAILURE;
1942 }
1943
1944
1945 /* Resolve a function call known to be specific.  */
1946
1947 static match
1948 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
1949 {
1950   match m;
1951
1952   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1953     {
1954       if (sym->attr.dummy)
1955         {
1956           sym->attr.proc = PROC_DUMMY;
1957           goto found;
1958         }
1959
1960       sym->attr.proc = PROC_EXTERNAL;
1961       goto found;
1962     }
1963
1964   if (sym->attr.proc == PROC_MODULE
1965       || sym->attr.proc == PROC_ST_FUNCTION
1966       || sym->attr.proc == PROC_INTERNAL)
1967     goto found;
1968
1969   if (sym->attr.intrinsic)
1970     {
1971       m = gfc_intrinsic_func_interface (expr, 1);
1972       if (m == MATCH_YES)
1973         return MATCH_YES;
1974       if (m == MATCH_NO)
1975         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
1976                    "with an intrinsic", sym->name, &expr->where);
1977
1978       return MATCH_ERROR;
1979     }
1980
1981   return MATCH_NO;
1982
1983 found:
1984   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1985
1986   if (sym->result)
1987     expr->ts = sym->result->ts;
1988   else
1989     expr->ts = sym->ts;
1990   expr->value.function.name = sym->name;
1991   expr->value.function.esym = sym;
1992   if (sym->as != NULL)
1993     expr->rank = sym->as->rank;
1994
1995   return MATCH_YES;
1996 }
1997
1998
1999 static gfc_try
2000 resolve_specific_f (gfc_expr *expr)
2001 {
2002   gfc_symbol *sym;
2003   match m;
2004
2005   sym = expr->symtree->n.sym;
2006
2007   for (;;)
2008     {
2009       m = resolve_specific_f0 (sym, expr);
2010       if (m == MATCH_YES)
2011         return SUCCESS;
2012       if (m == MATCH_ERROR)
2013         return FAILURE;
2014
2015       if (sym->ns->parent == NULL)
2016         break;
2017
2018       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2019
2020       if (sym == NULL)
2021         break;
2022     }
2023
2024   gfc_error ("Unable to resolve the specific function '%s' at %L",
2025              expr->symtree->n.sym->name, &expr->where);
2026
2027   return SUCCESS;
2028 }
2029
2030
2031 /* Resolve a procedure call not known to be generic nor specific.  */
2032
2033 static gfc_try
2034 resolve_unknown_f (gfc_expr *expr)
2035 {
2036   gfc_symbol *sym;
2037   gfc_typespec *ts;
2038
2039   sym = expr->symtree->n.sym;
2040
2041   if (sym->attr.dummy)
2042     {
2043       sym->attr.proc = PROC_DUMMY;
2044       expr->value.function.name = sym->name;
2045       goto set_type;
2046     }
2047
2048   /* See if we have an intrinsic function reference.  */
2049
2050   if (gfc_is_intrinsic (sym, 0, expr->where))
2051     {
2052       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2053         return SUCCESS;
2054       return FAILURE;
2055     }
2056
2057   /* The reference is to an external name.  */
2058
2059   sym->attr.proc = PROC_EXTERNAL;
2060   expr->value.function.name = sym->name;
2061   expr->value.function.esym = expr->symtree->n.sym;
2062
2063   if (sym->as != NULL)
2064     expr->rank = sym->as->rank;
2065
2066   /* Type of the expression is either the type of the symbol or the
2067      default type of the symbol.  */
2068
2069 set_type:
2070   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2071
2072   if (sym->ts.type != BT_UNKNOWN)
2073     expr->ts = sym->ts;
2074   else
2075     {
2076       ts = gfc_get_default_type (sym->name, sym->ns);
2077
2078       if (ts->type == BT_UNKNOWN)
2079         {
2080           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2081                      sym->name, &expr->where);
2082           return FAILURE;
2083         }
2084       else
2085         expr->ts = *ts;
2086     }
2087
2088   return SUCCESS;
2089 }
2090
2091
2092 /* Return true, if the symbol is an external procedure.  */
2093 static bool
2094 is_external_proc (gfc_symbol *sym)
2095 {
2096   if (!sym->attr.dummy && !sym->attr.contained
2097         && !(sym->attr.intrinsic
2098               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2099         && sym->attr.proc != PROC_ST_FUNCTION
2100         && !sym->attr.use_assoc
2101         && sym->name)
2102     return true;
2103
2104   return false;
2105 }
2106
2107
2108 /* Figure out if a function reference is pure or not.  Also set the name
2109    of the function for a potential error message.  Return nonzero if the
2110    function is PURE, zero if not.  */
2111 static int
2112 pure_stmt_function (gfc_expr *, gfc_symbol *);
2113
2114 static int
2115 pure_function (gfc_expr *e, const char **name)
2116 {
2117   int pure;
2118
2119   *name = NULL;
2120
2121   if (e->symtree != NULL
2122         && e->symtree->n.sym != NULL
2123         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2124     return pure_stmt_function (e, e->symtree->n.sym);
2125
2126   if (e->value.function.esym)
2127     {
2128       pure = gfc_pure (e->value.function.esym);
2129       *name = e->value.function.esym->name;
2130     }
2131   else if (e->value.function.isym)
2132     {
2133       pure = e->value.function.isym->pure
2134              || e->value.function.isym->elemental;
2135       *name = e->value.function.isym->name;
2136     }
2137   else
2138     {
2139       /* Implicit functions are not pure.  */
2140       pure = 0;
2141       *name = e->value.function.name;
2142     }
2143
2144   return pure;
2145 }
2146
2147
2148 static bool
2149 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2150                  int *f ATTRIBUTE_UNUSED)
2151 {
2152   const char *name;
2153
2154   /* Don't bother recursing into other statement functions
2155      since they will be checked individually for purity.  */
2156   if (e->expr_type != EXPR_FUNCTION
2157         || !e->symtree
2158         || e->symtree->n.sym == sym
2159         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2160     return false;
2161
2162   return pure_function (e, &name) ? false : true;
2163 }
2164
2165
2166 static int
2167 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2168 {
2169   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2170 }
2171
2172
2173 static gfc_try
2174 is_scalar_expr_ptr (gfc_expr *expr)
2175 {
2176   gfc_try retval = SUCCESS;
2177   gfc_ref *ref;
2178   int start;
2179   int end;
2180
2181   /* See if we have a gfc_ref, which means we have a substring, array
2182      reference, or a component.  */
2183   if (expr->ref != NULL)
2184     {
2185       ref = expr->ref;
2186       while (ref->next != NULL)
2187         ref = ref->next;
2188
2189       switch (ref->type)
2190         {
2191         case REF_SUBSTRING:
2192           if (ref->u.ss.length != NULL 
2193               && ref->u.ss.length->length != NULL
2194               && ref->u.ss.start
2195               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2196               && ref->u.ss.end
2197               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2198             {
2199               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2200               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2201               if (end - start + 1 != 1)
2202                 retval = FAILURE;
2203             }
2204           else
2205             retval = FAILURE;
2206           break;
2207         case REF_ARRAY:
2208           if (ref->u.ar.type == AR_ELEMENT)
2209             retval = SUCCESS;
2210           else if (ref->u.ar.type == AR_FULL)
2211             {
2212               /* The user can give a full array if the array is of size 1.  */
2213               if (ref->u.ar.as != NULL
2214                   && ref->u.ar.as->rank == 1
2215                   && ref->u.ar.as->type == AS_EXPLICIT
2216                   && ref->u.ar.as->lower[0] != NULL
2217                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2218                   && ref->u.ar.as->upper[0] != NULL
2219                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2220                 {
2221                   /* If we have a character string, we need to check if
2222                      its length is one.  */
2223                   if (expr->ts.type == BT_CHARACTER)
2224                     {
2225                       if (expr->ts.u.cl == NULL
2226                           || expr->ts.u.cl->length == NULL
2227                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2228                           != 0)
2229                         retval = FAILURE;
2230                     }
2231                   else
2232                     {
2233                       /* We have constant lower and upper bounds.  If the
2234                          difference between is 1, it can be considered a
2235                          scalar.  */
2236                       start = (int) mpz_get_si
2237                                 (ref->u.ar.as->lower[0]->value.integer);
2238                       end = (int) mpz_get_si
2239                                 (ref->u.ar.as->upper[0]->value.integer);
2240                       if (end - start + 1 != 1)
2241                         retval = FAILURE;
2242                    }
2243                 }
2244               else
2245                 retval = FAILURE;
2246             }
2247           else
2248             retval = FAILURE;
2249           break;
2250         default:
2251           retval = SUCCESS;
2252           break;
2253         }
2254     }
2255   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2256     {
2257       /* Character string.  Make sure it's of length 1.  */
2258       if (expr->ts.u.cl == NULL
2259           || expr->ts.u.cl->length == NULL
2260           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2261         retval = FAILURE;
2262     }
2263   else if (expr->rank != 0)
2264     retval = FAILURE;
2265
2266   return retval;
2267 }
2268
2269
2270 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2271    and, in the case of c_associated, set the binding label based on
2272    the arguments.  */
2273
2274 static gfc_try
2275 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2276                           gfc_symbol **new_sym)
2277 {
2278   char name[GFC_MAX_SYMBOL_LEN + 1];
2279   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2280   int optional_arg = 0, is_pointer = 0;
2281   gfc_try retval = SUCCESS;
2282   gfc_symbol *args_sym;
2283   gfc_typespec *arg_ts;
2284
2285   if (args->expr->expr_type == EXPR_CONSTANT
2286       || args->expr->expr_type == EXPR_OP
2287       || args->expr->expr_type == EXPR_NULL)
2288     {
2289       gfc_error ("Argument to '%s' at %L is not a variable",
2290                  sym->name, &(args->expr->where));
2291       return FAILURE;
2292     }
2293
2294   args_sym = args->expr->symtree->n.sym;
2295
2296   /* The typespec for the actual arg should be that stored in the expr
2297      and not necessarily that of the expr symbol (args_sym), because
2298      the actual expression could be a part-ref of the expr symbol.  */
2299   arg_ts = &(args->expr->ts);
2300
2301   is_pointer = gfc_is_data_pointer (args->expr);
2302     
2303   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2304     {
2305       /* If the user gave two args then they are providing something for
2306          the optional arg (the second cptr).  Therefore, set the name and
2307          binding label to the c_associated for two cptrs.  Otherwise,
2308          set c_associated to expect one cptr.  */
2309       if (args->next)
2310         {
2311           /* two args.  */
2312           sprintf (name, "%s_2", sym->name);
2313           sprintf (binding_label, "%s_2", sym->binding_label);
2314           optional_arg = 1;
2315         }
2316       else
2317         {
2318           /* one arg.  */
2319           sprintf (name, "%s_1", sym->name);
2320           sprintf (binding_label, "%s_1", sym->binding_label);
2321           optional_arg = 0;
2322         }
2323
2324       /* Get a new symbol for the version of c_associated that
2325          will get called.  */
2326       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2327     }
2328   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2329            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2330     {
2331       sprintf (name, "%s", sym->name);
2332       sprintf (binding_label, "%s", sym->binding_label);
2333
2334       /* Error check the call.  */
2335       if (args->next != NULL)
2336         {
2337           gfc_error_now ("More actual than formal arguments in '%s' "
2338                          "call at %L", name, &(args->expr->where));
2339           retval = FAILURE;
2340         }
2341       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2342         {
2343           /* Make sure we have either the target or pointer attribute.  */
2344           if (!args_sym->attr.target && !is_pointer)
2345             {
2346               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2347                              "a TARGET or an associated pointer",
2348                              args_sym->name,
2349                              sym->name, &(args->expr->where));
2350               retval = FAILURE;
2351             }
2352
2353           /* See if we have interoperable type and type param.  */
2354           if (verify_c_interop (arg_ts) == SUCCESS
2355               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2356             {
2357               if (args_sym->attr.target == 1)
2358                 {
2359                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2360                      has the target attribute and is interoperable.  */
2361                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2362                      allocatable variable that has the TARGET attribute and
2363                      is not an array of zero size.  */
2364                   if (args_sym->attr.allocatable == 1)
2365                     {
2366                       if (args_sym->attr.dimension != 0 
2367                           && (args_sym->as && args_sym->as->rank == 0))
2368                         {
2369                           gfc_error_now ("Allocatable variable '%s' used as a "
2370                                          "parameter to '%s' at %L must not be "
2371                                          "an array of zero size",
2372                                          args_sym->name, sym->name,
2373                                          &(args->expr->where));
2374                           retval = FAILURE;
2375                         }
2376                     }
2377                   else
2378                     {
2379                       /* A non-allocatable target variable with C
2380                          interoperable type and type parameters must be
2381                          interoperable.  */
2382                       if (args_sym && args_sym->attr.dimension)
2383                         {
2384                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2385                             {
2386                               gfc_error ("Assumed-shape array '%s' at %L "
2387                                          "cannot be an argument to the "
2388                                          "procedure '%s' because "
2389                                          "it is not C interoperable",
2390                                          args_sym->name,
2391                                          &(args->expr->where), sym->name);
2392                               retval = FAILURE;
2393                             }
2394                           else if (args_sym->as->type == AS_DEFERRED)
2395                             {
2396                               gfc_error ("Deferred-shape array '%s' at %L "
2397                                          "cannot be an argument to the "
2398                                          "procedure '%s' because "
2399                                          "it is not C interoperable",
2400                                          args_sym->name,
2401                                          &(args->expr->where), sym->name);
2402                               retval = FAILURE;
2403                             }
2404                         }
2405                               
2406                       /* Make sure it's not a character string.  Arrays of
2407                          any type should be ok if the variable is of a C
2408                          interoperable type.  */
2409                       if (arg_ts->type == BT_CHARACTER)
2410                         if (arg_ts->u.cl != NULL
2411                             && (arg_ts->u.cl->length == NULL
2412                                 || arg_ts->u.cl->length->expr_type
2413                                    != EXPR_CONSTANT
2414                                 || mpz_cmp_si
2415                                     (arg_ts->u.cl->length->value.integer, 1)
2416                                    != 0)
2417                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2418                           {
2419                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2420                                            "at %L must have a length of 1",
2421                                            args_sym->name, sym->name,
2422                                            &(args->expr->where));
2423                             retval = FAILURE;
2424                           }
2425                     }
2426                 }
2427               else if (is_pointer
2428                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2429                 {
2430                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2431                      scalar pointer.  */
2432                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2433                                  "associated scalar POINTER", args_sym->name,
2434                                  sym->name, &(args->expr->where));
2435                   retval = FAILURE;
2436                 }
2437             }
2438           else
2439             {
2440               /* The parameter is not required to be C interoperable.  If it
2441                  is not C interoperable, it must be a nonpolymorphic scalar
2442                  with no length type parameters.  It still must have either
2443                  the pointer or target attribute, and it can be
2444                  allocatable (but must be allocated when c_loc is called).  */
2445               if (args->expr->rank != 0 
2446                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2447                 {
2448                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2449                                  "scalar", args_sym->name, sym->name,
2450                                  &(args->expr->where));
2451                   retval = FAILURE;
2452                 }
2453               else if (arg_ts->type == BT_CHARACTER 
2454                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2455                 {
2456                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2457                                  "%L must have a length of 1",
2458                                  args_sym->name, sym->name,
2459                                  &(args->expr->where));
2460                   retval = FAILURE;
2461                 }
2462             }
2463         }
2464       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2465         {
2466           if (args_sym->attr.flavor != FL_PROCEDURE)
2467             {
2468               /* TODO: Update this error message to allow for procedure
2469                  pointers once they are implemented.  */
2470               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2471                              "procedure",
2472                              args_sym->name, sym->name,
2473                              &(args->expr->where));
2474               retval = FAILURE;
2475             }
2476           else if (args_sym->attr.is_bind_c != 1)
2477             {
2478               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2479                              "BIND(C)",
2480                              args_sym->name, sym->name,
2481                              &(args->expr->where));
2482               retval = FAILURE;
2483             }
2484         }
2485       
2486       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2487       *new_sym = sym;
2488     }
2489   else
2490     {
2491       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2492                           "iso_c_binding function: '%s'!\n", sym->name);
2493     }
2494
2495   return retval;
2496 }
2497
2498
2499 /* Resolve a function call, which means resolving the arguments, then figuring
2500    out which entity the name refers to.  */
2501 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2502    to INTENT(OUT) or INTENT(INOUT).  */
2503
2504 static gfc_try
2505 resolve_function (gfc_expr *expr)
2506 {
2507   gfc_actual_arglist *arg;
2508   gfc_symbol *sym;
2509   const char *name;
2510   gfc_try t;
2511   int temp;
2512   procedure_type p = PROC_INTRINSIC;
2513   bool no_formal_args;
2514
2515   sym = NULL;
2516   if (expr->symtree)
2517     sym = expr->symtree->n.sym;
2518
2519   if (sym && sym->attr.intrinsic
2520       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2521     return FAILURE;
2522
2523   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2524     {
2525       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2526       return FAILURE;
2527     }
2528
2529   if (sym && sym->attr.abstract)
2530     {
2531       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2532                  sym->name, &expr->where);
2533       return FAILURE;
2534     }
2535
2536   /* Switch off assumed size checking and do this again for certain kinds
2537      of procedure, once the procedure itself is resolved.  */
2538   need_full_assumed_size++;
2539
2540   if (expr->symtree && expr->symtree->n.sym)
2541     p = expr->symtree->n.sym->attr.proc;
2542
2543   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2544   if (resolve_actual_arglist (expr->value.function.actual,
2545                               p, no_formal_args) == FAILURE)
2546       return FAILURE;
2547
2548   /* Need to setup the call to the correct c_associated, depending on
2549      the number of cptrs to user gives to compare.  */
2550   if (sym && sym->attr.is_iso_c == 1)
2551     {
2552       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2553           == FAILURE)
2554         return FAILURE;
2555       
2556       /* Get the symtree for the new symbol (resolved func).
2557          the old one will be freed later, when it's no longer used.  */
2558       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2559     }
2560   
2561   /* Resume assumed_size checking.  */
2562   need_full_assumed_size--;
2563
2564   /* If the procedure is external, check for usage.  */
2565   if (sym && is_external_proc (sym))
2566     resolve_global_procedure (sym, &expr->where,
2567                               &expr->value.function.actual, 0);
2568
2569   if (sym && sym->ts.type == BT_CHARACTER
2570       && sym->ts.u.cl
2571       && sym->ts.u.cl->length == NULL
2572       && !sym->attr.dummy
2573       && expr->value.function.esym == NULL
2574       && !sym->attr.contained)
2575     {
2576       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2577       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2578                  "be used at %L since it is not a dummy argument",
2579                  sym->name, &expr->where);
2580       return FAILURE;
2581     }
2582
2583   /* See if function is already resolved.  */
2584
2585   if (expr->value.function.name != NULL)
2586     {
2587       if (expr->ts.type == BT_UNKNOWN)
2588         expr->ts = sym->ts;
2589       t = SUCCESS;
2590     }
2591   else
2592     {
2593       /* Apply the rules of section 14.1.2.  */
2594
2595       switch (procedure_kind (sym))
2596         {
2597         case PTYPE_GENERIC:
2598           t = resolve_generic_f (expr);
2599           break;
2600
2601         case PTYPE_SPECIFIC:
2602           t = resolve_specific_f (expr);
2603           break;
2604
2605         case PTYPE_UNKNOWN:
2606           t = resolve_unknown_f (expr);
2607           break;
2608
2609         default:
2610           gfc_internal_error ("resolve_function(): bad function type");
2611         }
2612     }
2613
2614   /* If the expression is still a function (it might have simplified),
2615      then we check to see if we are calling an elemental function.  */
2616
2617   if (expr->expr_type != EXPR_FUNCTION)
2618     return t;
2619
2620   temp = need_full_assumed_size;
2621   need_full_assumed_size = 0;
2622
2623   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2624     return FAILURE;
2625
2626   if (omp_workshare_flag
2627       && expr->value.function.esym
2628       && ! gfc_elemental (expr->value.function.esym))
2629     {
2630       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2631                  "in WORKSHARE construct", expr->value.function.esym->name,
2632                  &expr->where);
2633       t = FAILURE;
2634     }
2635
2636 #define GENERIC_ID expr->value.function.isym->id
2637   else if (expr->value.function.actual != NULL
2638            && expr->value.function.isym != NULL
2639            && GENERIC_ID != GFC_ISYM_LBOUND
2640            && GENERIC_ID != GFC_ISYM_LEN
2641            && GENERIC_ID != GFC_ISYM_LOC
2642            && GENERIC_ID != GFC_ISYM_PRESENT)
2643     {
2644       /* Array intrinsics must also have the last upper bound of an
2645          assumed size array argument.  UBOUND and SIZE have to be
2646          excluded from the check if the second argument is anything
2647          than a constant.  */
2648
2649       for (arg = expr->value.function.actual; arg; arg = arg->next)
2650         {
2651           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2652               && arg->next != NULL && arg->next->expr)
2653             {
2654               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2655                 break;
2656
2657               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2658                 break;
2659
2660               if ((int)mpz_get_si (arg->next->expr->value.integer)
2661                         < arg->expr->rank)
2662                 break;
2663             }
2664
2665           if (arg->expr != NULL
2666               && arg->expr->rank > 0
2667               && resolve_assumed_size_actual (arg->expr))
2668             return FAILURE;
2669         }
2670     }
2671 #undef GENERIC_ID
2672
2673   need_full_assumed_size = temp;
2674   name = NULL;
2675
2676   if (!pure_function (expr, &name) && name)
2677     {
2678       if (forall_flag)
2679         {
2680           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2681                      "FORALL %s", name, &expr->where,
2682                      forall_flag == 2 ? "mask" : "block");
2683           t = FAILURE;
2684         }
2685       else if (gfc_pure (NULL))
2686         {
2687           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2688                      "procedure within a PURE procedure", name, &expr->where);
2689           t = FAILURE;
2690         }
2691     }
2692
2693   /* Functions without the RECURSIVE attribution are not allowed to
2694    * call themselves.  */
2695   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2696     {
2697       gfc_symbol *esym;
2698       esym = expr->value.function.esym;
2699
2700       if (is_illegal_recursion (esym, gfc_current_ns))
2701       {
2702         if (esym->attr.entry && esym->ns->entries)
2703           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2704                      " function '%s' is not RECURSIVE",
2705                      esym->name, &expr->where, esym->ns->entries->sym->name);
2706         else
2707           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2708                      " is not RECURSIVE", esym->name, &expr->where);
2709
2710         t = FAILURE;
2711       }
2712     }
2713
2714   /* Character lengths of use associated functions may contains references to
2715      symbols not referenced from the current program unit otherwise.  Make sure
2716      those symbols are marked as referenced.  */
2717
2718   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2719       && expr->value.function.esym->attr.use_assoc)
2720     {
2721       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2722     }
2723
2724   if (t == SUCCESS
2725         && !((expr->value.function.esym
2726                 && expr->value.function.esym->attr.elemental)
2727                         ||
2728              (expr->value.function.isym
2729                 && expr->value.function.isym->elemental)))
2730     find_noncopying_intrinsics (expr->value.function.esym,
2731                                 expr->value.function.actual);
2732
2733   /* Make sure that the expression has a typespec that works.  */
2734   if (expr->ts.type == BT_UNKNOWN)
2735     {
2736       if (expr->symtree->n.sym->result
2737             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2738             && !expr->symtree->n.sym->result->attr.proc_pointer)
2739         expr->ts = expr->symtree->n.sym->result->ts;
2740     }
2741
2742   return t;
2743 }
2744
2745
2746 /************* Subroutine resolution *************/
2747
2748 static void
2749 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2750 {
2751   if (gfc_pure (sym))
2752     return;
2753
2754   if (forall_flag)
2755     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2756                sym->name, &c->loc);
2757   else if (gfc_pure (NULL))
2758     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2759                &c->loc);
2760 }
2761
2762
2763 static match
2764 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2765 {
2766   gfc_symbol *s;
2767
2768   if (sym->attr.generic)
2769     {
2770       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2771       if (s != NULL)
2772         {
2773           c->resolved_sym = s;
2774           pure_subroutine (c, s);
2775           return MATCH_YES;
2776         }
2777
2778       /* TODO: Need to search for elemental references in generic interface.  */
2779     }
2780
2781   if (sym->attr.intrinsic)
2782     return gfc_intrinsic_sub_interface (c, 0);
2783
2784   return MATCH_NO;
2785 }
2786
2787
2788 static gfc_try
2789 resolve_generic_s (gfc_code *c)
2790 {
2791   gfc_symbol *sym;
2792   match m;
2793
2794   sym = c->symtree->n.sym;
2795
2796   for (;;)
2797     {
2798       m = resolve_generic_s0 (c, sym);
2799       if (m == MATCH_YES)
2800         return SUCCESS;
2801       else if (m == MATCH_ERROR)
2802         return FAILURE;
2803
2804 generic:
2805       if (sym->ns->parent == NULL)
2806         break;
2807       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2808
2809       if (sym == NULL)
2810         break;
2811       if (!generic_sym (sym))
2812         goto generic;
2813     }
2814
2815   /* Last ditch attempt.  See if the reference is to an intrinsic
2816      that possesses a matching interface.  14.1.2.4  */
2817   sym = c->symtree->n.sym;
2818
2819   if (!gfc_is_intrinsic (sym, 1, c->loc))
2820     {
2821       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2822                  sym->name, &c->loc);
2823       return FAILURE;
2824     }
2825
2826   m = gfc_intrinsic_sub_interface (c, 0);
2827   if (m == MATCH_YES)
2828     return SUCCESS;
2829   if (m == MATCH_NO)
2830     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2831                "intrinsic subroutine interface", sym->name, &c->loc);
2832
2833   return FAILURE;
2834 }
2835
2836
2837 /* Set the name and binding label of the subroutine symbol in the call
2838    expression represented by 'c' to include the type and kind of the
2839    second parameter.  This function is for resolving the appropriate
2840    version of c_f_pointer() and c_f_procpointer().  For example, a
2841    call to c_f_pointer() for a default integer pointer could have a
2842    name of c_f_pointer_i4.  If no second arg exists, which is an error
2843    for these two functions, it defaults to the generic symbol's name
2844    and binding label.  */
2845
2846 static void
2847 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2848                     char *name, char *binding_label)
2849 {
2850   gfc_expr *arg = NULL;
2851   char type;
2852   int kind;
2853
2854   /* The second arg of c_f_pointer and c_f_procpointer determines
2855      the type and kind for the procedure name.  */
2856   arg = c->ext.actual->next->expr;
2857
2858   if (arg != NULL)
2859     {
2860       /* Set up the name to have the given symbol's name,
2861          plus the type and kind.  */
2862       /* a derived type is marked with the type letter 'u' */
2863       if (arg->ts.type == BT_DERIVED)
2864         {
2865           type = 'd';
2866           kind = 0; /* set the kind as 0 for now */
2867         }
2868       else
2869         {
2870           type = gfc_type_letter (arg->ts.type);
2871           kind = arg->ts.kind;
2872         }
2873
2874       if (arg->ts.type == BT_CHARACTER)
2875         /* Kind info for character strings not needed.  */
2876         kind = 0;
2877
2878       sprintf (name, "%s_%c%d", sym->name, type, kind);
2879       /* Set up the binding label as the given symbol's label plus
2880          the type and kind.  */
2881       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2882     }
2883   else
2884     {
2885       /* If the second arg is missing, set the name and label as
2886          was, cause it should at least be found, and the missing
2887          arg error will be caught by compare_parameters().  */
2888       sprintf (name, "%s", sym->name);
2889       sprintf (binding_label, "%s", sym->binding_label);
2890     }
2891    
2892   return;
2893 }
2894
2895
2896 /* Resolve a generic version of the iso_c_binding procedure given
2897    (sym) to the specific one based on the type and kind of the
2898    argument(s).  Currently, this function resolves c_f_pointer() and
2899    c_f_procpointer based on the type and kind of the second argument
2900    (FPTR).  Other iso_c_binding procedures aren't specially handled.
2901    Upon successfully exiting, c->resolved_sym will hold the resolved
2902    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
2903    otherwise.  */
2904
2905 match
2906 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2907 {
2908   gfc_symbol *new_sym;
2909   /* this is fine, since we know the names won't use the max */
2910   char name[GFC_MAX_SYMBOL_LEN + 1];
2911   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2912   /* default to success; will override if find error */
2913   match m = MATCH_YES;
2914
2915   /* Make sure the actual arguments are in the necessary order (based on the 
2916      formal args) before resolving.  */
2917   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2918
2919   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2920       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2921     {
2922       set_name_and_label (c, sym, name, binding_label);
2923       
2924       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2925         {
2926           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2927             {
2928               /* Make sure we got a third arg if the second arg has non-zero
2929                  rank.  We must also check that the type and rank are
2930                  correct since we short-circuit this check in
2931                  gfc_procedure_use() (called above to sort actual args).  */
2932               if (c->ext.actual->next->expr->rank != 0)
2933                 {
2934                   if(c->ext.actual->next->next == NULL 
2935                      || c->ext.actual->next->next->expr == NULL)
2936                     {
2937                       m = MATCH_ERROR;
2938                       gfc_error ("Missing SHAPE parameter for call to %s "
2939                                  "at %L", sym->name, &(c->loc));
2940                     }
2941                   else if (c->ext.actual->next->next->expr->ts.type
2942                            != BT_INTEGER
2943                            || c->ext.actual->next->next->expr->rank != 1)
2944                     {
2945                       m = MATCH_ERROR;
2946                       gfc_error ("SHAPE parameter for call to %s at %L must "
2947                                  "be a rank 1 INTEGER array", sym->name,
2948                                  &(c->loc));
2949                     }
2950                 }
2951             }
2952         }
2953       
2954       if (m != MATCH_ERROR)
2955         {
2956           /* the 1 means to add the optional arg to formal list */
2957           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2958          
2959           /* for error reporting, say it's declared where the original was */
2960           new_sym->declared_at = sym->declared_at;
2961         }
2962     }
2963   else
2964     {
2965       /* no differences for c_loc or c_funloc */
2966       new_sym = sym;
2967     }
2968
2969   /* set the resolved symbol */
2970   if (m != MATCH_ERROR)
2971     c->resolved_sym = new_sym;
2972   else
2973     c->resolved_sym = sym;
2974   
2975   return m;
2976 }
2977
2978
2979 /* Resolve a subroutine call known to be specific.  */
2980
2981 static match
2982 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
2983 {
2984   match m;
2985
2986   if(sym->attr.is_iso_c)
2987     {
2988       m = gfc_iso_c_sub_interface (c,sym);
2989       return m;
2990     }
2991   
2992   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2993     {
2994       if (sym->attr.dummy)
2995         {
2996           sym->attr.proc = PROC_DUMMY;
2997           goto found;
2998         }
2999
3000       sym->attr.proc = PROC_EXTERNAL;
3001       goto found;
3002     }
3003
3004   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3005     goto found;
3006
3007   if (sym->attr.intrinsic)
3008     {
3009       m = gfc_intrinsic_sub_interface (c, 1);
3010       if (m == MATCH_YES)
3011         return MATCH_YES;
3012       if (m == MATCH_NO)
3013         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3014                    "with an intrinsic", sym->name, &c->loc);
3015
3016       return MATCH_ERROR;
3017     }
3018
3019   return MATCH_NO;
3020
3021 found:
3022   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3023
3024   c->resolved_sym = sym;
3025   pure_subroutine (c, sym);
3026
3027   return MATCH_YES;
3028 }
3029
3030
3031 static gfc_try
3032 resolve_specific_s (gfc_code *c)
3033 {
3034   gfc_symbol *sym;
3035   match m;
3036
3037   sym = c->symtree->n.sym;
3038
3039   for (;;)
3040     {
3041       m = resolve_specific_s0 (c, sym);
3042       if (m == MATCH_YES)
3043         return SUCCESS;
3044       if (m == MATCH_ERROR)
3045         return FAILURE;
3046
3047       if (sym->ns->parent == NULL)
3048         break;
3049
3050       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3051
3052       if (sym == NULL)
3053         break;
3054     }
3055
3056   sym = c->symtree->n.sym;
3057   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3058              sym->name, &c->loc);
3059
3060   return FAILURE;
3061 }
3062
3063
3064 /* Resolve a subroutine call not known to be generic nor specific.  */
3065
3066 static gfc_try
3067 resolve_unknown_s (gfc_code *c)
3068 {
3069   gfc_symbol *sym;
3070
3071   sym = c->symtree->n.sym;
3072
3073   if (sym->attr.dummy)
3074     {
3075       sym->attr.proc = PROC_DUMMY;
3076       goto found;
3077     }
3078
3079   /* See if we have an intrinsic function reference.  */
3080
3081   if (gfc_is_intrinsic (sym, 1, c->loc))
3082     {
3083       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3084         return SUCCESS;
3085       return FAILURE;
3086     }
3087
3088   /* The reference is to an external name.  */
3089
3090 found:
3091   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3092
3093   c->resolved_sym = sym;
3094
3095   pure_subroutine (c, sym);
3096
3097   return SUCCESS;
3098 }
3099
3100
3101 /* Resolve a subroutine call.  Although it was tempting to use the same code
3102    for functions, subroutines and functions are stored differently and this
3103    makes things awkward.  */
3104
3105 static gfc_try
3106 resolve_call (gfc_code *c)
3107 {
3108   gfc_try t;
3109   procedure_type ptype = PROC_INTRINSIC;
3110   gfc_symbol *csym, *sym;
3111   bool no_formal_args;
3112
3113   csym = c->symtree ? c->symtree->n.sym : NULL;
3114
3115   if (csym && csym->ts.type != BT_UNKNOWN)
3116     {
3117       gfc_error ("'%s' at %L has a type, which is not consistent with "
3118                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3119       return FAILURE;
3120     }
3121
3122   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3123     {
3124       gfc_symtree *st;
3125       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3126       sym = st ? st->n.sym : NULL;
3127       if (sym && csym != sym
3128               && sym->ns == gfc_current_ns
3129               && sym->attr.flavor == FL_PROCEDURE
3130               && sym->attr.contained)
3131         {
3132           sym->refs++;
3133           if (csym->attr.generic)
3134             c->symtree->n.sym = sym;
3135           else
3136             c->symtree = st;
3137           csym = c->symtree->n.sym;
3138         }
3139     }
3140
3141   /* Subroutines without the RECURSIVE attribution are not allowed to
3142    * call themselves.  */
3143   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3144     {
3145       if (csym->attr.entry && csym->ns->entries)
3146         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3147                    " subroutine '%s' is not RECURSIVE",
3148                    csym->name, &c->loc, csym->ns->entries->sym->name);
3149       else
3150         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3151                    " is not RECURSIVE", csym->name, &c->loc);
3152
3153       t = FAILURE;
3154     }
3155
3156   /* Switch off assumed size checking and do this again for certain kinds
3157      of procedure, once the procedure itself is resolved.  */
3158   need_full_assumed_size++;
3159
3160   if (csym)
3161     ptype = csym->attr.proc;
3162
3163   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3164   if (resolve_actual_arglist (c->ext.actual, ptype,
3165                               no_formal_args) == FAILURE)
3166     return FAILURE;
3167
3168   /* Resume assumed_size checking.  */
3169   need_full_assumed_size--;
3170
3171   /* If external, check for usage.  */
3172   if (csym && is_external_proc (csym))
3173     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3174
3175   t = SUCCESS;
3176   if (c->resolved_sym == NULL)
3177     {
3178       c->resolved_isym = NULL;
3179       switch (procedure_kind (csym))
3180         {
3181         case PTYPE_GENERIC:
3182           t = resolve_generic_s (c);
3183           break;
3184
3185         case PTYPE_SPECIFIC:
3186           t = resolve_specific_s (c);
3187           break;
3188
3189         case PTYPE_UNKNOWN:
3190           t = resolve_unknown_s (c);
3191           break;
3192
3193         default:
3194           gfc_internal_error ("resolve_subroutine(): bad function type");
3195         }
3196     }
3197
3198   /* Some checks of elemental subroutine actual arguments.  */
3199   if (resolve_elemental_actual (NULL, c) == FAILURE)
3200     return FAILURE;
3201
3202   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3203     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3204   return t;
3205 }
3206
3207
3208 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3209    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3210    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3211    if their shapes do not match.  If either op1->shape or op2->shape is
3212    NULL, return SUCCESS.  */
3213
3214 static gfc_try
3215 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3216 {
3217   gfc_try t;
3218   int i;
3219
3220   t = SUCCESS;
3221
3222   if (op1->shape != NULL && op2->shape != NULL)
3223     {
3224       for (i = 0; i < op1->rank; i++)
3225         {
3226           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3227            {
3228              gfc_error ("Shapes for operands at %L and %L are not conformable",
3229                          &op1->where, &op2->where);
3230              t = FAILURE;
3231              break;
3232            }
3233         }
3234     }
3235
3236   return t;
3237 }
3238
3239
3240 /* Resolve an operator expression node.  This can involve replacing the
3241    operation with a user defined function call.  */
3242
3243 static gfc_try
3244 resolve_operator (gfc_expr *e)
3245 {
3246   gfc_expr *op1, *op2;
3247   char msg[200];
3248   bool dual_locus_error;
3249   gfc_try t;
3250
3251   /* Resolve all subnodes-- give them types.  */
3252
3253   switch (e->value.op.op)
3254     {
3255     default:
3256       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3257         return FAILURE;
3258
3259     /* Fall through...  */
3260
3261     case INTRINSIC_NOT:
3262     case INTRINSIC_UPLUS:
3263     case INTRINSIC_UMINUS:
3264     case INTRINSIC_PARENTHESES:
3265       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3266         return FAILURE;
3267       break;
3268     }
3269
3270   /* Typecheck the new node.  */
3271
3272   op1 = e->value.op.op1;
3273   op2 = e->value.op.op2;
3274   dual_locus_error = false;
3275
3276   if ((op1 && op1->expr_type == EXPR_NULL)
3277       || (op2 && op2->expr_type == EXPR_NULL))
3278     {
3279       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3280       goto bad_op;
3281     }
3282
3283   switch (e->value.op.op)
3284     {
3285     case INTRINSIC_UPLUS:
3286     case INTRINSIC_UMINUS:
3287       if (op1->ts.type == BT_INTEGER
3288           || op1->ts.type == BT_REAL
3289           || op1->ts.type == BT_COMPLEX)
3290         {
3291           e->ts = op1->ts;
3292           break;
3293         }
3294
3295       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3296                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3297       goto bad_op;
3298
3299     case INTRINSIC_PLUS:
3300     case INTRINSIC_MINUS:
3301     case INTRINSIC_TIMES:
3302     case INTRINSIC_DIVIDE:
3303     case INTRINSIC_POWER:
3304       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3305         {
3306           gfc_type_convert_binary (e);
3307           break;
3308         }
3309
3310       sprintf (msg,
3311                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3312                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3313                gfc_typename (&op2->ts));
3314       goto bad_op;
3315
3316     case INTRINSIC_CONCAT:
3317       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3318           && op1->ts.kind == op2->ts.kind)
3319         {
3320           e->ts.type = BT_CHARACTER;
3321           e->ts.kind = op1->ts.kind;
3322           break;
3323         }
3324
3325       sprintf (msg,
3326                _("Operands of string concatenation operator at %%L are %s/%s"),
3327                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3328       goto bad_op;
3329
3330     case INTRINSIC_AND:
3331     case INTRINSIC_OR:
3332     case INTRINSIC_EQV:
3333     case INTRINSIC_NEQV:
3334       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3335         {
3336           e->ts.type = BT_LOGICAL;
3337           e->ts.kind = gfc_kind_max (op1, op2);
3338           if (op1->ts.kind < e->ts.kind)
3339             gfc_convert_type (op1, &e->ts, 2);
3340           else if (op2->ts.kind < e->ts.kind)
3341             gfc_convert_type (op2, &e->ts, 2);
3342           break;
3343         }
3344
3345       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3346                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3347                gfc_typename (&op2->ts));
3348
3349       goto bad_op;
3350
3351     case INTRINSIC_NOT:
3352       if (op1->ts.type == BT_LOGICAL)
3353         {
3354           e->ts.type = BT_LOGICAL;
3355           e->ts.kind = op1->ts.kind;
3356           break;
3357         }
3358
3359       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3360                gfc_typename (&op1->ts));
3361       goto bad_op;
3362
3363     case INTRINSIC_GT:
3364     case INTRINSIC_GT_OS:
3365     case INTRINSIC_GE:
3366     case INTRINSIC_GE_OS:
3367     case INTRINSIC_LT:
3368     case INTRINSIC_LT_OS:
3369     case INTRINSIC_LE:
3370     case INTRINSIC_LE_OS:
3371       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3372         {
3373           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3374           goto bad_op;
3375         }
3376
3377       /* Fall through...  */
3378
3379     case INTRINSIC_EQ:
3380     case INTRINSIC_EQ_OS:
3381     case INTRINSIC_NE:
3382     case INTRINSIC_NE_OS:
3383       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3384           && op1->ts.kind == op2->ts.kind)
3385         {
3386           e->ts.type = BT_LOGICAL;
3387           e->ts.kind = gfc_default_logical_kind;
3388           break;
3389         }
3390
3391       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3392         {
3393           gfc_type_convert_binary (e);
3394
3395           e->ts.type = BT_LOGICAL;
3396           e->ts.kind = gfc_default_logical_kind;
3397           break;
3398         }
3399
3400       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3401         sprintf (msg,
3402                  _("Logicals at %%L must be compared with %s instead of %s"),
3403                  (e->value.op.op == INTRINSIC_EQ 
3404                   || e->value.op.op == INTRINSIC_EQ_OS)
3405                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3406       else
3407         sprintf (msg,
3408                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3409                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3410                  gfc_typename (&op2->ts));
3411
3412       goto bad_op;
3413
3414     case INTRINSIC_USER:
3415       if (e->value.op.uop->op == NULL)
3416         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3417       else if (op2 == NULL)
3418         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3419                  e->value.op.uop->name, gfc_typename (&op1->ts));
3420       else
3421         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3422                  e->value.op.uop->name, gfc_typename (&op1->ts),
3423                  gfc_typename (&op2->ts));
3424
3425       goto bad_op;
3426
3427     case INTRINSIC_PARENTHESES:
3428       e->ts = op1->ts;
3429       if (e->ts.type == BT_CHARACTER)
3430         e->ts.u.cl = op1->ts.u.cl;
3431       break;
3432
3433     default:
3434       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3435     }
3436
3437   /* Deal with arrayness of an operand through an operator.  */
3438
3439   t = SUCCESS;
3440
3441   switch (e->value.op.op)
3442     {
3443     case INTRINSIC_PLUS:
3444     case INTRINSIC_MINUS:
3445     case INTRINSIC_TIMES:
3446     case INTRINSIC_DIVIDE:
3447     case INTRINSIC_POWER:
3448     case INTRINSIC_CONCAT:
3449     case INTRINSIC_AND:
3450     case INTRINSIC_OR:
3451     case INTRINSIC_EQV:
3452     case INTRINSIC_NEQV:
3453     case INTRINSIC_EQ:
3454     case INTRINSIC_EQ_OS:
3455     case INTRINSIC_NE:
3456     case INTRINSIC_NE_OS:
3457     case INTRINSIC_GT:
3458     case INTRINSIC_GT_OS:
3459     case INTRINSIC_GE:
3460     case INTRINSIC_GE_OS:
3461     case INTRINSIC_LT:
3462     case INTRINSIC_LT_OS:
3463     case INTRINSIC_LE:
3464     case INTRINSIC_LE_OS:
3465
3466       if (op1->rank == 0 && op2->rank == 0)
3467         e->rank = 0;
3468
3469       if (op1->rank == 0 && op2->rank != 0)
3470         {
3471           e->rank = op2->rank;
3472
3473           if (e->shape == NULL)
3474             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3475         }
3476
3477       if (op1->rank != 0 && op2->rank == 0)
3478         {
3479           e->rank = op1->rank;
3480
3481           if (e->shape == NULL)
3482             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3483         }
3484
3485       if (op1->rank != 0 && op2->rank != 0)
3486         {
3487           if (op1->rank == op2->rank)
3488             {
3489               e->rank = op1->rank;
3490               if (e->shape == NULL)
3491                 {
3492                   t = compare_shapes(op1, op2);
3493                   if (t == FAILURE)
3494                     e->shape = NULL;
3495                   else
3496                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3497                 }
3498             }
3499           else
3500             {
3501               /* Allow higher level expressions to work.  */
3502               e->rank = 0;
3503
3504               /* Try user-defined operators, and otherwise throw an error.  */
3505               dual_locus_error = true;
3506               sprintf (msg,
3507                        _("Inconsistent ranks for operator at %%L and %%L"));
3508               goto bad_op;
3509             }
3510         }
3511
3512       break;
3513
3514     case INTRINSIC_PARENTHESES:
3515     case INTRINSIC_NOT:
3516     case INTRINSIC_UPLUS:
3517     case INTRINSIC_UMINUS:
3518       /* Simply copy arrayness attribute */
3519       e->rank = op1->rank;
3520
3521       if (e->shape == NULL)
3522         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3523
3524       break;
3525
3526     default:
3527       break;
3528     }
3529
3530   /* Attempt to simplify the expression.  */
3531   if (t == SUCCESS)
3532     {
3533       t = gfc_simplify_expr (e, 0);
3534       /* Some calls do not succeed in simplification and return FAILURE
3535          even though there is no error; e.g. variable references to
3536          PARAMETER arrays.  */
3537       if (!gfc_is_constant_expr (e))
3538         t = SUCCESS;
3539     }
3540   return t;
3541
3542 bad_op:
3543
3544   {
3545     bool real_error;
3546     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3547       return SUCCESS;
3548
3549     if (real_error)
3550       return FAILURE;
3551   }
3552
3553   if (dual_locus_error)
3554     gfc_error (msg, &op1->where, &op2->where);
3555   else
3556     gfc_error (msg, &e->where);
3557
3558   return FAILURE;
3559 }
3560
3561
3562 /************** Array resolution subroutines **************/
3563
3564 typedef enum
3565 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3566 comparison;
3567
3568 /* Compare two integer expressions.  */
3569
3570 static comparison
3571 compare_bound (gfc_expr *a, gfc_expr *b)
3572 {
3573   int i;
3574
3575   if (a == NULL || a->expr_type != EXPR_CONSTANT
3576       || b == NULL || b->expr_type != EXPR_CONSTANT)
3577     return CMP_UNKNOWN;
3578
3579   /* If either of the types isn't INTEGER, we must have
3580      raised an error earlier.  */
3581
3582   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3583     return CMP_UNKNOWN;
3584
3585   i = mpz_cmp (a->value.integer, b->value.integer);
3586
3587   if (i < 0)
3588     return CMP_LT;
3589   if (i > 0)
3590     return CMP_GT;
3591   return CMP_EQ;
3592 }
3593
3594
3595 /* Compare an integer expression with an integer.  */
3596
3597 static comparison
3598 compare_bound_int (gfc_expr *a, int b)
3599 {
3600   int i;
3601
3602   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3603     return CMP_UNKNOWN;
3604
3605   if (a->ts.type != BT_INTEGER)
3606     gfc_internal_error ("compare_bound_int(): Bad expression");
3607
3608   i = mpz_cmp_si (a->value.integer, b);
3609
3610   if (i < 0)
3611     return CMP_LT;
3612   if (i > 0)
3613     return CMP_GT;
3614   return CMP_EQ;
3615 }
3616
3617
3618 /* Compare an integer expression with a mpz_t.  */
3619
3620 static comparison
3621 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3622 {
3623   int i;
3624
3625   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3626     return CMP_UNKNOWN;
3627
3628   if (a->ts.type != BT_INTEGER)
3629     gfc_internal_error ("compare_bound_int(): Bad expression");
3630
3631   i = mpz_cmp (a->value.integer, b);
3632
3633   if (i < 0)
3634     return CMP_LT;
3635   if (i > 0)
3636     return CMP_GT;
3637   return CMP_EQ;
3638 }
3639
3640
3641 /* Compute the last value of a sequence given by a triplet.  
3642    Return 0 if it wasn't able to compute the last value, or if the
3643    sequence if empty, and 1 otherwise.  */
3644
3645 static int
3646 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3647                                 gfc_expr *stride, mpz_t last)
3648 {
3649   mpz_t rem;
3650
3651   if (start == NULL || start->expr_type != EXPR_CONSTANT
3652       || end == NULL || end->expr_type != EXPR_CONSTANT
3653       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3654     return 0;
3655
3656   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3657       || (stride != NULL && stride->ts.type != BT_INTEGER))
3658     return 0;
3659
3660   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3661     {
3662       if (compare_bound (start, end) == CMP_GT)
3663         return 0;
3664       mpz_set (last, end->value.integer);
3665       return 1;
3666     }
3667
3668   if (compare_bound_int (stride, 0) == CMP_GT)
3669     {
3670       /* Stride is positive */
3671       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3672         return 0;
3673     }
3674   else
3675     {
3676       /* Stride is negative */
3677       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3678         return 0;
3679     }
3680
3681   mpz_init (rem);
3682   mpz_sub (rem, end->value.integer, start->value.integer);
3683   mpz_tdiv_r (rem, rem, stride->value.integer);
3684   mpz_sub (last, end->value.integer, rem);
3685   mpz_clear (rem);
3686
3687   return 1;
3688 }
3689
3690
3691 /* Compare a single dimension of an array reference to the array
3692    specification.  */
3693
3694 static gfc_try
3695 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3696 {
3697   mpz_t last_value;
3698
3699 /* Given start, end and stride values, calculate the minimum and
3700    maximum referenced indexes.  */
3701
3702   switch (ar->dimen_type[i])
3703     {
3704     case DIMEN_VECTOR:
3705       break;
3706
3707     case DIMEN_ELEMENT:
3708       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3709         {
3710           gfc_warning ("Array reference at %L is out of bounds "
3711                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3712                        mpz_get_si (ar->start[i]->value.integer),
3713                        mpz_get_si (as->lower[i]->value.integer), i+1);
3714           return SUCCESS;
3715         }
3716       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3717         {
3718           gfc_warning ("Array reference at %L is out of bounds "
3719                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3720                        mpz_get_si (ar->start[i]->value.integer),
3721                        mpz_get_si (as->upper[i]->value.integer), i+1);
3722           return SUCCESS;
3723         }
3724
3725       break;
3726
3727     case DIMEN_RANGE:
3728       {
3729 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3730 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3731
3732         comparison comp_start_end = compare_bound (AR_START, AR_END);
3733
3734         /* Check for zero stride, which is not allowed.  */
3735         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3736           {
3737             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3738             return FAILURE;
3739           }
3740
3741         /* if start == len || (stride > 0 && start < len)
3742                            || (stride < 0 && start > len),
3743            then the array section contains at least one element.  In this
3744            case, there is an out-of-bounds access if
3745            (start < lower || start > upper).  */
3746         if (compare_bound (AR_START, AR_END) == CMP_EQ
3747             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3748                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3749             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3750                 && comp_start_end == CMP_GT))
3751           {
3752             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3753               {
3754                 gfc_warning ("Lower array reference at %L is out of bounds "
3755                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3756                        mpz_get_si (AR_START->value.integer),
3757                        mpz_get_si (as->lower[i]->value.integer), i+1);
3758                 return SUCCESS;
3759               }
3760             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3761               {
3762                 gfc_warning ("Lower array reference at %L is out of bounds "
3763                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3764                        mpz_get_si (AR_START->value.integer),
3765                        mpz_get_si (as->upper[i]->value.integer), i+1);
3766                 return SUCCESS;
3767               }
3768           }
3769
3770         /* If we can compute the highest index of the array section,
3771            then it also has to be between lower and upper.  */
3772         mpz_init (last_value);
3773         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3774                                             last_value))
3775           {
3776             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3777               {
3778                 gfc_warning ("Upper array reference at %L is out of bounds "
3779                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3780                        mpz_get_si (last_value),
3781                        mpz_get_si (as->lower[i]->value.integer), i+1);
3782                 mpz_clear (last_value);
3783                 return SUCCESS;
3784               }
3785             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3786               {
3787                 gfc_warning ("Upper array reference at %L is out of bounds "
3788                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3789                        mpz_get_si (last_value),
3790                        mpz_get_si (as->upper[i]->value.integer), i+1);
3791                 mpz_clear (last_value);
3792                 return SUCCESS;
3793               }
3794           }
3795         mpz_clear (last_value);
3796
3797 #undef AR_START
3798 #undef AR_END
3799       }
3800       break;
3801
3802     default:
3803       gfc_internal_error ("check_dimension(): Bad array reference");
3804     }
3805
3806   return SUCCESS;
3807 }
3808
3809
3810 /* Compare an array reference with an array specification.  */
3811
3812 static gfc_try
3813 compare_spec_to_ref (gfc_array_ref *ar)
3814 {
3815   gfc_array_spec *as;
3816   int i;
3817
3818   as = ar->as;
3819   i = as->rank - 1;
3820   /* TODO: Full array sections are only allowed as actual parameters.  */
3821   if (as->type == AS_ASSUMED_SIZE
3822       && (/*ar->type == AR_FULL
3823           ||*/ (ar->type == AR_SECTION
3824               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3825     {
3826       gfc_error ("Rightmost upper bound of assumed size array section "
3827                  "not specified at %L", &ar->where);
3828       return FAILURE;
3829     }
3830
3831   if (ar->type == AR_FULL)
3832     return SUCCESS;
3833
3834   if (as->rank != ar->dimen)
3835     {
3836       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3837                  &ar->where, ar->dimen, as->rank);
3838       return FAILURE;
3839     }
3840
3841   for (i = 0; i < as->rank; i++)
3842     if (check_dimension (i, ar, as) == FAILURE)
3843       return FAILURE;
3844
3845   return SUCCESS;
3846 }
3847
3848
3849 /* Resolve one part of an array index.  */
3850
3851 gfc_try
3852 gfc_resolve_index (gfc_expr *index, int check_scalar)
3853 {
3854   gfc_typespec ts;
3855
3856   if (index == NULL)
3857     return SUCCESS;
3858
3859   if (gfc_resolve_expr (index) == FAILURE)
3860     return FAILURE;
3861
3862   if (check_scalar && index->rank != 0)
3863     {
3864       gfc_error ("Array index at %L must be scalar", &index->where);
3865       return FAILURE;
3866     }
3867
3868   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3869     {
3870       gfc_error ("Array index at %L must be of INTEGER type, found %s",
3871                  &index->where, gfc_basic_typename (index->ts.type));
3872       return FAILURE;
3873     }
3874
3875   if (index->ts.type == BT_REAL)
3876     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
3877                         &index->where) == FAILURE)
3878       return FAILURE;
3879
3880   if (index->ts.kind != gfc_index_integer_kind
3881       || index->ts.type != BT_INTEGER)
3882     {
3883       gfc_clear_ts (&ts);
3884       ts.type = BT_INTEGER;
3885       ts.kind = gfc_index_integer_kind;
3886
3887       gfc_convert_type_warn (index, &ts, 2, 0);
3888     }
3889
3890   return SUCCESS;
3891 }
3892
3893 /* Resolve a dim argument to an intrinsic function.  */
3894
3895 gfc_try
3896 gfc_resolve_dim_arg (gfc_expr *dim)
3897 {
3898   if (dim == NULL)
3899     return SUCCESS;
3900
3901   if (gfc_resolve_expr (dim) == FAILURE)
3902     return FAILURE;
3903
3904   if (dim->rank != 0)
3905     {
3906       gfc_error ("Argument dim at %L must be scalar", &dim->where);
3907       return FAILURE;
3908
3909     }
3910
3911   if (dim->ts.type != BT_INTEGER)
3912     {
3913       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
3914       return FAILURE;
3915     }
3916
3917   if (dim->ts.kind != gfc_index_integer_kind)
3918     {
3919       gfc_typespec ts;
3920
3921       ts.type = BT_INTEGER;
3922       ts.kind = gfc_index_integer_kind;
3923
3924       gfc_convert_type_warn (dim, &ts, 2, 0);
3925     }
3926
3927   return SUCCESS;
3928 }
3929
3930 /* Given an expression that contains array references, update those array
3931    references to point to the right array specifications.  While this is
3932    filled in during matching, this information is difficult to save and load
3933    in a module, so we take care of it here.
3934
3935    The idea here is that the original array reference comes from the
3936    base symbol.  We traverse the list of reference structures, setting
3937    the stored reference to references.  Component references can
3938    provide an additional array specification.  */
3939
3940 static void
3941 find_array_spec (gfc_expr *e)
3942 {
3943   gfc_array_spec *as;
3944   gfc_component *c;
3945   gfc_symbol *derived;
3946   gfc_ref *ref;
3947
3948   if (e->symtree->n.sym->ts.type == BT_CLASS)
3949     as = e->symtree->n.sym->ts.u.derived->components->as;
3950   else
3951     as = e->symtree->n.sym->as;
3952   derived = NULL;
3953
3954   for (ref = e->ref; ref; ref = ref->next)
3955     switch (ref->type)
3956       {
3957       case REF_ARRAY:
3958         if (as == NULL)
3959           gfc_internal_error ("find_array_spec(): Missing spec");
3960
3961         ref->u.ar.as = as;
3962         as = NULL;
3963         break;
3964
3965       case REF_COMPONENT:
3966         if (derived == NULL)
3967           derived = e->symtree->n.sym->ts.u.derived;
3968
3969         c = derived->components;
3970
3971         for (; c; c = c->next)
3972           if (c == ref->u.c.component)
3973             {
3974               /* Track the sequence of component references.  */
3975               if (c->ts.type == BT_DERIVED)
3976                 derived = c->ts.u.derived;
3977               break;
3978             }
3979
3980         if (c == NULL)
3981           gfc_internal_error ("find_array_spec(): Component not found");
3982
3983         if (c->attr.dimension)
3984           {
3985             if (as != NULL)
3986               gfc_internal_error ("find_array_spec(): unused as(1)");
3987             as = c->as;
3988           }
3989
3990         break;
3991
3992       case REF_SUBSTRING:
3993         break;
3994       }
3995
3996   if (as != NULL)
3997     gfc_internal_error ("find_array_spec(): unused as(2)");
3998 }
3999
4000
4001 /* Resolve an array reference.  */
4002
4003 static gfc_try
4004 resolve_array_ref (gfc_array_ref *ar)
4005 {
4006   int i, check_scalar;
4007   gfc_expr *e;
4008
4009   for (i = 0; i < ar->dimen; i++)
4010     {
4011       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4012
4013       if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
4014         return FAILURE;
4015       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4016         return FAILURE;
4017       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4018         return FAILURE;
4019
4020       e = ar->start[i];
4021
4022       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4023         switch (e->rank)
4024           {
4025           case 0:
4026             ar->dimen_type[i] = DIMEN_ELEMENT;
4027             break;
4028
4029           case 1:
4030             ar->dimen_type[i] = DIMEN_VECTOR;
4031             if (e->expr_type == EXPR_VARIABLE
4032                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4033               ar->start[i] = gfc_get_parentheses (e);
4034             break;
4035
4036           default:
4037             gfc_error ("Array index at %L is an array of rank %d",
4038                        &ar->c_where[i], e->rank);
4039             return FAILURE;
4040           }
4041     }
4042
4043   /* If the reference type is unknown, figure out what kind it is.  */
4044
4045   if (ar->type == AR_UNKNOWN)
4046     {
4047       ar->type = AR_ELEMENT;
4048       for (i = 0; i < ar->dimen; i++)
4049         if (ar->dimen_type[i] == DIMEN_RANGE
4050             || ar->dimen_type[i] == DIMEN_VECTOR)
4051           {
4052             ar->type = AR_SECTION;
4053             break;
4054           }
4055     }
4056
4057   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4058     return FAILURE;
4059
4060   return SUCCESS;
4061 }
4062
4063
4064 static gfc_try
4065 resolve_substring (gfc_ref *ref)
4066 {
4067   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4068
4069   if (ref->u.ss.start != NULL)
4070     {
4071       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4072         return FAILURE;
4073
4074       if (ref->u.ss.start->ts.type != BT_INTEGER)
4075         {
4076           gfc_error ("Substring start index at %L must be of type INTEGER",
4077                      &ref->u.ss.start->where);
4078           return FAILURE;
4079         }
4080
4081       if (ref->u.ss.start->rank != 0)
4082         {
4083           gfc_error ("Substring start index at %L must be scalar",
4084                      &ref->u.ss.start->where);
4085           return FAILURE;
4086         }
4087
4088       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4089           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4090               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4091         {
4092           gfc_error ("Substring start index at %L is less than one",
4093                      &ref->u.ss.start->where);
4094           return FAILURE;
4095         }
4096     }
4097
4098   if (ref->u.ss.end != NULL)
4099     {
4100       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4101         return FAILURE;
4102
4103       if (ref->u.ss.end->ts.type != BT_INTEGER)
4104         {
4105           gfc_error ("Substring end index at %L must be of type INTEGER",
4106                      &ref->u.ss.end->where);
4107           return FAILURE;
4108         }
4109
4110       if (ref->u.ss.end->rank != 0)
4111         {
4112           gfc_error ("Substring end index at %L must be scalar",
4113                      &ref->u.ss.end->where);
4114           return FAILURE;
4115         }
4116
4117       if (ref->u.ss.length != NULL
4118           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4119           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4120               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4121         {
4122           gfc_error ("Substring end index at %L exceeds the string length",
4123                      &ref->u.ss.start->where);
4124           return FAILURE;
4125         }
4126
4127       if (compare_bound_mpz_t (ref->u.ss.end,
4128                                gfc_integer_kinds[k].huge) == CMP_GT
4129           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4130               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4131         {
4132           gfc_error ("Substring end index at %L is too large",
4133                      &ref->u.ss.end->where);
4134           return FAILURE;
4135         }
4136     }
4137
4138   return SUCCESS;
4139 }
4140
4141
4142 /* This function supplies missing substring charlens.  */
4143
4144 void
4145 gfc_resolve_substring_charlen (gfc_expr *e)
4146 {
4147   gfc_ref *char_ref;
4148   gfc_expr *start, *end;
4149
4150   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4151     if (char_ref->type == REF_SUBSTRING)
4152       break;
4153
4154   if (!char_ref)
4155     return;
4156
4157   gcc_assert (char_ref->next == NULL);
4158
4159   if (e->ts.u.cl)
4160     {
4161       if (e->ts.u.cl->length)
4162         gfc_free_expr (e->ts.u.cl->length);
4163       else if (e->expr_type == EXPR_VARIABLE
4164                  && e->symtree->n.sym->attr.dummy)
4165         return;
4166     }
4167
4168   e->ts.type = BT_CHARACTER;
4169   e->ts.kind = gfc_default_character_kind;
4170
4171   if (!e->ts.u.cl)
4172     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4173
4174   if (char_ref->u.ss.start)
4175     start = gfc_copy_expr (char_ref->u.ss.start);
4176   else
4177     start = gfc_int_expr (1);
4178
4179   if (char_ref->u.ss.end)
4180     end = gfc_copy_expr (char_ref->u.ss.end);
4181   else if (e->expr_type == EXPR_VARIABLE)
4182     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4183   else
4184     end = NULL;
4185
4186   if (!start || !end)
4187     return;
4188
4189   /* Length = (end - start +1).  */
4190   e->ts.u.cl->length = gfc_subtract (end, start);
4191   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length, gfc_int_expr (1));
4192
4193   e->ts.u.cl->length->ts.type = BT_INTEGER;
4194   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4195
4196   /* Make sure that the length is simplified.  */
4197   gfc_simplify_expr (e->ts.u.cl->length, 1);
4198   gfc_resolve_expr (e->ts.u.cl->length);
4199 }
4200
4201
4202 /* Resolve subtype references.  */
4203
4204 static gfc_try
4205 resolve_ref (gfc_expr *expr)
4206 {
4207   int current_part_dimension, n_components, seen_part_dimension;
4208   gfc_ref *ref;
4209
4210   for (ref = expr->ref; ref; ref = ref->next)
4211     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4212       {
4213         find_array_spec (expr);
4214         break;
4215       }
4216
4217   for (ref = expr->ref; ref; ref = ref->next)
4218     switch (ref->type)
4219       {
4220       case REF_ARRAY:
4221         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4222           return FAILURE;
4223         break;
4224
4225       case REF_COMPONENT:
4226         break;
4227
4228       case REF_SUBSTRING:
4229         resolve_substring (ref);
4230         break;
4231       }
4232
4233   /* Check constraints on part references.  */
4234
4235   current_part_dimension = 0;
4236   seen_part_dimension = 0;
4237   n_components = 0;
4238
4239   for (ref = expr->ref; ref; ref = ref->next)
4240     {
4241       switch (ref->type)
4242         {
4243         case REF_ARRAY:
4244           switch (ref->u.ar.type)
4245             {
4246             case AR_FULL:
4247             case AR_SECTION:
4248               current_part_dimension = 1;
4249               break;
4250
4251             case AR_ELEMENT:
4252               current_part_dimension = 0;
4253               break;
4254
4255             case AR_UNKNOWN:
4256               gfc_internal_error ("resolve_ref(): Bad array reference");
4257             }
4258
4259           break;
4260
4261         case REF_COMPONENT:
4262           if (current_part_dimension || seen_part_dimension)
4263             {
4264               if (ref->u.c.component->attr.pointer)
4265                 {
4266                   gfc_error ("Component to the right of a part reference "
4267                              "with nonzero rank must not have the POINTER "
4268                              "attribute at %L", &expr->where);
4269                   return FAILURE;
4270                 }
4271               else if (ref->u.c.component->attr.allocatable)
4272                 {
4273                   gfc_error ("Component to the right of a part reference "
4274                              "with nonzero rank must not have the ALLOCATABLE "
4275                              "attribute at %L", &expr->where);
4276                   return FAILURE;
4277                 }
4278             }
4279
4280           n_components++;
4281           break;
4282
4283         case REF_SUBSTRING:
4284           break;
4285         }
4286
4287       if (((ref->type == REF_COMPONENT && n_components > 1)
4288            || ref->next == NULL)
4289           && current_part_dimension
4290           && seen_part_dimension)
4291         {
4292           gfc_error ("Two or more part references with nonzero rank must "
4293                      "not be specified at %L", &expr->where);
4294           return FAILURE;
4295         }
4296
4297       if (ref->type == REF_COMPONENT)
4298         {
4299           if (current_part_dimension)
4300             seen_part_dimension = 1;
4301
4302           /* reset to make sure */
4303           current_part_dimension = 0;
4304         }
4305     }
4306
4307   return SUCCESS;
4308 }
4309
4310
4311 /* Given an expression, determine its shape.  This is easier than it sounds.
4312    Leaves the shape array NULL if it is not possible to determine the shape.  */
4313
4314 static void
4315 expression_shape (gfc_expr *e)
4316 {
4317   mpz_t array[GFC_MAX_DIMENSIONS];
4318   int i;
4319
4320   if (e->rank == 0 || e->shape != NULL)
4321     return;
4322
4323   for (i = 0; i < e->rank; i++)
4324     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4325       goto fail;
4326
4327   e->shape = gfc_get_shape (e->rank);
4328
4329   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4330
4331   return;
4332
4333 fail:
4334   for (i--; i >= 0; i--)
4335     mpz_clear (array[i]);
4336 }
4337
4338
4339 /* Given a variable expression node, compute the rank of the expression by
4340    examining the base symbol and any reference structures it may have.  */
4341
4342 static void
4343 expression_rank (gfc_expr *e)
4344 {
4345   gfc_ref *ref;
4346   int i, rank;
4347
4348   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4349      could lead to serious confusion...  */
4350   gcc_assert (e->expr_type != EXPR_COMPCALL);
4351
4352   if (e->ref == NULL)
4353     {
4354       if (e->expr_type == EXPR_ARRAY)
4355         goto done;
4356       /* Constructors can have a rank different from one via RESHAPE().  */
4357
4358       if (e->symtree == NULL)
4359         {
4360           e->rank = 0;
4361           goto done;
4362         }
4363
4364       e->rank = (e->symtree->n.sym->as == NULL)
4365                 ? 0 : e->symtree->n.sym->as->rank;
4366       goto done;
4367     }
4368
4369   rank = 0;
4370
4371   for (ref = e->ref; ref; ref = ref->next)
4372     {
4373       if (ref->type != REF_ARRAY)
4374         continue;
4375
4376       if (ref->u.ar.type == AR_FULL)
4377         {
4378           rank = ref->u.ar.as->rank;
4379           break;
4380         }
4381
4382       if (ref->u.ar.type == AR_SECTION)
4383         {
4384           /* Figure out the rank of the section.  */
4385           if (rank != 0)
4386             gfc_internal_error ("expression_rank(): Two array specs");
4387
4388           for (i = 0; i < ref->u.ar.dimen; i++)
4389             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4390                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4391               rank++;
4392
4393           break;
4394         }
4395     }
4396
4397   e->rank = rank;
4398
4399 done:
4400   expression_shape (e);
4401 }
4402
4403
4404 /* Resolve a variable expression.  */
4405
4406 static gfc_try
4407 resolve_variable (gfc_expr *e)
4408 {
4409   gfc_symbol *sym;
4410   gfc_try t;
4411
4412   t = SUCCESS;
4413
4414   if (e->symtree == NULL)
4415     return FAILURE;
4416
4417   if (e->ref && resolve_ref (e) == FAILURE)
4418     return FAILURE;
4419
4420   sym = e->symtree->n.sym;
4421   if (sym->attr.flavor == FL_PROCEDURE
4422       && (!sym->attr.function
4423           || (sym->attr.function && sym->result
4424               && sym->result->attr.proc_pointer
4425               && !sym->result->attr.function)))
4426     {
4427       e->ts.type = BT_PROCEDURE;
4428       goto resolve_procedure;
4429     }
4430
4431   if (sym->ts.type != BT_UNKNOWN)
4432     gfc_variable_attr (e, &e->ts);
4433   else
4434     {
4435       /* Must be a simple variable reference.  */
4436       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4437         return FAILURE;
4438       e->ts = sym->ts;
4439     }
4440
4441   if (check_assumed_size_reference (sym, e))
4442     return FAILURE;
4443
4444   /* Deal with forward references to entries during resolve_code, to
4445      satisfy, at least partially, 12.5.2.5.  */
4446   if (gfc_current_ns->entries
4447       && current_entry_id == sym->entry_id
4448       && cs_base
4449       && cs_base->current
4450       && cs_base->current->op != EXEC_ENTRY)
4451     {
4452       gfc_entry_list *entry;
4453       gfc_formal_arglist *formal;
4454       int n;
4455       bool seen;
4456
4457       /* If the symbol is a dummy...  */
4458       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4459         {
4460           entry = gfc_current_ns->entries;
4461           seen = false;
4462
4463           /* ...test if the symbol is a parameter of previous entries.  */
4464           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4465             for (formal = entry->sym->formal; formal; formal = formal->next)
4466               {
4467                 if (formal->sym && sym->name == formal->sym->name)
4468                   seen = true;
4469               }
4470
4471           /*  If it has not been seen as a dummy, this is an error.  */
4472           if (!seen)
4473             {
4474               if (specification_expr)
4475                 gfc_error ("Variable '%s', used in a specification expression"
4476                            ", is referenced at %L before the ENTRY statement "
4477                            "in which it is a parameter",
4478                            sym->name, &cs_base->current->loc);
4479               else
4480                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4481                            "statement in which it is a parameter",
4482                            sym->name, &cs_base->current->loc);
4483               t = FAILURE;
4484             }
4485         }
4486
4487       /* Now do the same check on the specification expressions.  */
4488       specification_expr = 1;
4489       if (sym->ts.type == BT_CHARACTER
4490           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4491         t = FAILURE;
4492
4493       if (sym->as)
4494         for (n = 0; n < sym->as->rank; n++)
4495           {
4496              specification_expr = 1;
4497              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4498                t = FAILURE;
4499              specification_expr = 1;
4500              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4501                t = FAILURE;
4502           }
4503       specification_expr = 0;
4504
4505       if (t == SUCCESS)
4506         /* Update the symbol's entry level.  */
4507         sym->entry_id = current_entry_id + 1;
4508     }
4509
4510 resolve_procedure:
4511   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4512     t = FAILURE;
4513
4514   return t;
4515 }
4516
4517
4518 /* Checks to see that the correct symbol has been host associated.
4519    The only situation where this arises is that in which a twice
4520    contained function is parsed after the host association is made.
4521    Therefore, on detecting this, change the symbol in the expression
4522    and convert the array reference into an actual arglist if the old
4523    symbol is a variable.  */
4524 static bool
4525 check_host_association (gfc_expr *e)
4526 {
4527   gfc_symbol *sym, *old_sym;
4528   gfc_symtree *st;
4529   int n;
4530   gfc_ref *ref;
4531   gfc_actual_arglist *arg, *tail = NULL;
4532   bool retval = e->expr_type == EXPR_FUNCTION;
4533
4534   /*  If the expression is the result of substitution in
4535       interface.c(gfc_extend_expr) because there is no way in
4536       which the host association can be wrong.  */
4537   if (e->symtree == NULL
4538         || e->symtree->n.sym == NULL
4539         || e->user_operator)
4540     return retval;
4541
4542   old_sym = e->symtree->n.sym;
4543
4544   if (gfc_current_ns->parent
4545         && old_sym->ns != gfc_current_ns)
4546     {
4547       /* Use the 'USE' name so that renamed module symbols are
4548          correctly handled.  */
4549       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4550
4551       if (sym && old_sym != sym
4552               && sym->ts.type == old_sym->ts.type
4553               && sym->attr.flavor == FL_PROCEDURE
4554               && sym->attr.contained)
4555         {
4556           /* Clear the shape, since it might not be valid.  */
4557           if (e->shape != NULL)
4558             {
4559               for (n = 0; n < e->rank; n++)
4560                 mpz_clear (e->shape[n]);
4561
4562               gfc_free (e->shape);
4563             }
4564
4565           /* Give the expression the right symtree!  */
4566           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4567           gcc_assert (st != NULL);
4568
4569           if (old_sym->attr.flavor == FL_PROCEDURE
4570                 || e->expr_type == EXPR_FUNCTION)
4571             {
4572               /* Original was function so point to the new symbol, since
4573                  the actual argument list is already attached to the
4574                  expression. */
4575               e->value.function.esym = NULL;
4576               e->symtree = st;
4577             }
4578           else
4579             {
4580               /* Original was variable so convert array references into
4581                  an actual arglist. This does not need any checking now
4582                  since gfc_resolve_function will take care of it.  */
4583               e->value.function.actual = NULL;
4584               e->expr_type = EXPR_FUNCTION;
4585               e->symtree = st;
4586
4587               /* Ambiguity will not arise if the array reference is not
4588                  the last reference.  */
4589               for (ref = e->ref; ref; ref = ref->next)
4590                 if (ref->type == REF_ARRAY && ref->next == NULL)
4591                   break;
4592
4593               gcc_assert (ref->type == REF_ARRAY);
4594
4595               /* Grab the start expressions from the array ref and
4596                  copy them into actual arguments.  */
4597               for (n = 0; n < ref->u.ar.dimen; n++)
4598                 {
4599                   arg = gfc_get_actual_arglist ();
4600                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4601                   if (e->value.function.actual == NULL)
4602                     tail = e->value.function.actual = arg;
4603                   else
4604                     {
4605                       tail->next = arg;
4606                       tail = arg;
4607                     }
4608                 }
4609
4610               /* Dump the reference list and set the rank.  */
4611               gfc_free_ref_list (e->ref);
4612               e->ref = NULL;
4613               e->rank = sym->as ? sym->as->rank : 0;
4614             }
4615
4616           gfc_resolve_expr (e);
4617           sym->refs++;
4618         }
4619     }
4620   /* This might have changed!  */
4621   return e->expr_type == EXPR_FUNCTION;
4622 }
4623
4624
4625 static void
4626 gfc_resolve_character_operator (gfc_expr *e)
4627 {
4628   gfc_expr *op1 = e->value.op.op1;
4629   gfc_expr *op2 = e->value.op.op2;
4630   gfc_expr *e1 = NULL;
4631   gfc_expr *e2 = NULL;
4632
4633   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4634
4635   if (op1->ts.u.cl && op1->ts.u.cl->length)
4636     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4637   else if (op1->expr_type == EXPR_CONSTANT)
4638     e1 = gfc_int_expr (op1->value.character.length);
4639
4640   if (op2->ts.u.cl && op2->ts.u.cl->length)
4641     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4642   else if (op2->expr_type == EXPR_CONSTANT)
4643     e2 = gfc_int_expr (op2->value.character.length);
4644
4645   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4646
4647   if (!e1 || !e2)
4648     return;
4649
4650   e->ts.u.cl->length = gfc_add (e1, e2);
4651   e->ts.u.cl->length->ts.type = BT_INTEGER;
4652   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4653   gfc_simplify_expr (e->ts.u.cl->length, 0);
4654   gfc_resolve_expr (e->ts.u.cl->length);
4655
4656   return;
4657 }
4658
4659
4660 /*  Ensure that an character expression has a charlen and, if possible, a
4661     length expression.  */
4662
4663 static void
4664 fixup_charlen (gfc_expr *e)
4665 {
4666   /* The cases fall through so that changes in expression type and the need
4667      for multiple fixes are picked up.  In all circumstances, a charlen should
4668      be available for the middle end to hang a backend_decl on.  */
4669   switch (e->expr_type)
4670     {
4671     case EXPR_OP:
4672       gfc_resolve_character_operator (e);
4673
4674     case EXPR_ARRAY:
4675       if (e->expr_type == EXPR_ARRAY)
4676         gfc_resolve_character_array_constructor (e);
4677
4678     case EXPR_SUBSTRING:
4679       if (!e->ts.u.cl && e->ref)
4680         gfc_resolve_substring_charlen (e);
4681
4682     default:
4683       if (!e->ts.u.cl)
4684         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4685
4686       break;
4687     }
4688 }
4689
4690
4691 /* Update an actual argument to include the passed-object for type-bound
4692    procedures at the right position.  */
4693
4694 static gfc_actual_arglist*
4695 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
4696                      const char *name)
4697 {
4698   gcc_assert (argpos > 0);
4699
4700   if (argpos == 1)
4701     {
4702       gfc_actual_arglist* result;
4703
4704       result = gfc_get_actual_arglist ();
4705       result->expr = po;
4706       result->next = lst;
4707       if (name)
4708         result->name = name;
4709
4710       return result;
4711     }
4712
4713   if (lst)
4714     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
4715   else
4716     lst = update_arglist_pass (NULL, po, argpos - 1, name);
4717   return lst;
4718 }
4719
4720
4721 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
4722
4723 static gfc_expr*
4724 extract_compcall_passed_object (gfc_expr* e)
4725 {
4726   gfc_expr* po;
4727
4728   gcc_assert (e->expr_type == EXPR_COMPCALL);
4729
4730   if (e->value.compcall.base_object)
4731     po = gfc_copy_expr (e->value.compcall.base_object);
4732   else
4733     {
4734       po = gfc_get_expr ();
4735       po->expr_type = EXPR_VARIABLE;
4736       po->symtree = e->symtree;
4737       po->ref = gfc_copy_ref (e->ref);
4738     }
4739
4740   if (gfc_resolve_expr (po) == FAILURE)
4741     return NULL;
4742
4743   return po;
4744 }
4745
4746
4747 /* Update the arglist of an EXPR_COMPCALL expression to include the
4748    passed-object.  */
4749
4750 static gfc_try
4751 update_compcall_arglist (gfc_expr* e)
4752 {
4753   gfc_expr* po;
4754   gfc_typebound_proc* tbp;
4755
4756   tbp = e->value.compcall.tbp;
4757
4758   if (tbp->error)
4759     return FAILURE;
4760
4761   po = extract_compcall_passed_object (e);
4762   if (!po)
4763     return FAILURE;
4764
4765   if (po->rank > 0)
4766     {
4767       gfc_error ("Passed-object at %L must be scalar", &e->where);
4768       return FAILURE;
4769     }
4770
4771   if (tbp->nopass || e->value.compcall.ignore_pass)
4772     {
4773       gfc_free_expr (po);
4774       return SUCCESS;
4775     }
4776
4777   gcc_assert (tbp->pass_arg_num > 0);
4778   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
4779                                                   tbp->pass_arg_num,
4780                                                   tbp->pass_arg);
4781
4782   return SUCCESS;
4783 }
4784
4785
4786 /* Extract the passed object from a PPC call (a copy of it).  */
4787
4788 static gfc_expr*
4789 extract_ppc_passed_object (gfc_expr *e)
4790 {
4791   gfc_expr *po;
4792   gfc_ref **ref;
4793
4794   po = gfc_get_expr ();
4795   po->expr_type = EXPR_VARIABLE;
4796   po->symtree = e->symtree;
4797   po->ref = gfc_copy_ref (e->ref);
4798
4799   /* Remove PPC reference.  */
4800   ref = &po->ref;
4801   while ((*ref)->next)
4802     (*ref) = (*ref)->next;
4803   gfc_free_ref_list (*ref);
4804   *ref = NULL;
4805
4806   if (gfc_resolve_expr (po) == FAILURE)
4807     return NULL;
4808
4809   return po;
4810 }
4811
4812
4813 /* Update the actual arglist of a procedure pointer component to include the
4814    passed-object.  */
4815
4816 static gfc_try
4817 update_ppc_arglist (gfc_expr* e)
4818 {
4819   gfc_expr* po;
4820   gfc_component *ppc;
4821   gfc_typebound_proc* tb;
4822
4823   if (!gfc_is_proc_ptr_comp (e, &ppc))
4824     return FAILURE;
4825
4826   tb = ppc->tb;
4827
4828   if (tb->error)
4829     return FAILURE;
4830   else if (tb->nopass)
4831     return SUCCESS;
4832
4833   po = extract_ppc_passed_object (e);
4834   if (!po)
4835     return FAILURE;
4836
4837   if (po->rank > 0)
4838     {
4839       gfc_error ("Passed-object at %L must be scalar", &e->where);
4840       return FAILURE;
4841     }
4842
4843   gcc_assert (tb->pass_arg_num > 0);
4844   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
4845                                                   tb->pass_arg_num,
4846                                                   tb->pass_arg);
4847
4848   return SUCCESS;
4849 }
4850
4851
4852 /* Check that the object a TBP is called on is valid, i.e. it must not be
4853    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
4854
4855 static gfc_try
4856 check_typebound_baseobject (gfc_expr* e)
4857 {
4858   gfc_expr* base;
4859
4860   base = extract_compcall_passed_object (e);
4861   if (!base)
4862     return FAILURE;
4863
4864   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
4865
4866   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
4867     {
4868       gfc_error ("Base object for type-bound procedure call at %L is of"
4869                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
4870       return FAILURE;
4871     }
4872
4873   return SUCCESS;
4874 }
4875
4876
4877 /* Resolve a call to a type-bound procedure, either function or subroutine,
4878    statically from the data in an EXPR_COMPCALL expression.  The adapted
4879    arglist and the target-procedure symtree are returned.  */
4880
4881 static gfc_try
4882 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
4883                           gfc_actual_arglist** actual)
4884 {
4885   gcc_assert (e->expr_type == EXPR_COMPCALL);
4886   gcc_assert (!e->value.compcall.tbp->is_generic);
4887
4888   /* Update the actual arglist for PASS.  */
4889   if (update_compcall_arglist (e) == FAILURE)
4890     return FAILURE;
4891
4892   *actual = e->value.compcall.actual;
4893   *target = e->value.compcall.tbp->u.specific;
4894
4895   gfc_free_ref_list (e->ref);
4896   e->ref = NULL;
4897   e->value.compcall.actual = NULL;
4898
4899   return SUCCESS;
4900 }
4901
4902
4903 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
4904    which of the specific bindings (if any) matches the arglist and transform
4905    the expression into a call of that binding.  */
4906
4907 static gfc_try
4908 resolve_typebound_generic_call (gfc_expr* e)
4909 {
4910   gfc_typebound_proc* genproc;
4911   const char* genname;
4912
4913   gcc_assert (e->expr_type == EXPR_COMPCALL);
4914   genname = e->value.compcall.name;
4915   genproc = e->value.compcall.tbp;
4916
4917   if (!genproc->is_generic)
4918     return SUCCESS;
4919
4920   /* Try the bindings on this type and in the inheritance hierarchy.  */
4921   for (; genproc; genproc = genproc->overridden)
4922     {
4923       gfc_tbp_generic* g;
4924
4925       gcc_assert (genproc->is_generic);
4926       for (g = genproc->u.generic; g; g = g->next)
4927         {
4928           gfc_symbol* target;
4929           gfc_actual_arglist* args;
4930           bool matches;
4931
4932           gcc_assert (g->specific);
4933
4934           if (g->specific->error)
4935             continue;
4936
4937           target = g->specific->u.specific->n.sym;
4938
4939           /* Get the right arglist by handling PASS/NOPASS.  */
4940           args = gfc_copy_actual_arglist (e->value.compcall.actual);
4941           if (!g->specific->nopass)
4942             {
4943               gfc_expr* po;
4944               po = extract_compcall_passed_object (e);
4945               if (!po)
4946                 return FAILURE;
4947
4948               gcc_assert (g->specific->pass_arg_num > 0);
4949               gcc_assert (!g->specific->error);
4950               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
4951                                           g->specific->pass_arg);
4952             }
4953           resolve_actual_arglist (args, target->attr.proc,
4954                                   is_external_proc (target) && !target->formal);
4955
4956           /* Check if this arglist matches the formal.  */
4957           matches = gfc_arglist_matches_symbol (&args, target);
4958
4959           /* Clean up and break out of the loop if we've found it.  */
4960           gfc_free_actual_arglist (args);
4961           if (matches)
4962             {
4963               e->value.compcall.tbp = g->specific;
4964               goto success;
4965             }
4966         }
4967     }
4968
4969   /* Nothing matching found!  */
4970   gfc_error ("Found no matching specific binding for the call to the GENERIC"
4971              " '%s' at %L", genname, &e->where);
4972   return FAILURE;
4973
4974 success:
4975   return SUCCESS;
4976 }
4977
4978
4979 /* Resolve a call to a type-bound subroutine.  */
4980
4981 static gfc_try
4982 resolve_typebound_call (gfc_code* c)
4983 {
4984   gfc_actual_arglist* newactual;
4985   gfc_symtree* target;
4986
4987   /* Check that's really a SUBROUTINE.  */
4988   if (!c->expr1->value.compcall.tbp->subroutine)
4989     {
4990       gfc_error ("'%s' at %L should be a SUBROUTINE",
4991                  c->expr1->value.compcall.name, &c->loc);
4992       return FAILURE;
4993     }
4994
4995   if (check_typebound_baseobject (c->expr1) == FAILURE)
4996     return FAILURE;
4997
4998   if (resolve_typebound_generic_call (c->expr1) == FAILURE)
4999     return FAILURE;
5000
5001   /* Transform into an ordinary EXEC_CALL for now.  */
5002
5003   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5004     return FAILURE;
5005
5006   c->ext.actual = newactual;
5007   c->symtree = target;
5008   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5009
5010   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5011
5012   gfc_free_expr (c->expr1);
5013   c->expr1 = gfc_get_expr ();
5014   c->expr1->expr_type = EXPR_FUNCTION;
5015   c->expr1->symtree = target;
5016   c->expr1->where = c->loc;
5017
5018   return resolve_call (c);
5019 }
5020
5021
5022 /* Resolve a component-call expression.  This originally was intended
5023    only to see functions.  However, it is convenient to use it in 
5024    resolving subroutine class methods, since we do not have to add a
5025    gfc_code each time. */
5026 static gfc_try
5027 resolve_compcall (gfc_expr* e, bool fcn)
5028 {
5029   gfc_actual_arglist* newactual;
5030   gfc_symtree* target;
5031
5032   /* Check that's really a FUNCTION.  */
5033   if (fcn && !e->value.compcall.tbp->function)
5034     {
5035       gfc_error ("'%s' at %L should be a FUNCTION",
5036                  e->value.compcall.name, &e->where);
5037       return FAILURE;
5038     }
5039   else if (!fcn && !e->value.compcall.tbp->subroutine)
5040     {
5041       /* To resolve class member calls, we borrow this bit
5042          of code to select the specific procedures.  */
5043       gfc_error ("'%s' at %L should be a SUBROUTINE",
5044                  e->value.compcall.name, &e->where);
5045       return FAILURE;
5046     }
5047
5048   /* These must not be assign-calls!  */
5049   gcc_assert (!e->value.compcall.assign);
5050
5051   if (check_typebound_baseobject (e) == FAILURE)
5052     return FAILURE;
5053
5054   if (resolve_typebound_generic_call (e) == FAILURE)
5055     return FAILURE;
5056   gcc_assert (!e->value.compcall.tbp->is_generic);
5057
5058   /* Take the rank from the function's symbol.  */
5059   if (e->value.compcall.tbp->u.specific->n.sym->as)
5060     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5061
5062   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5063      arglist to the TBP's binding target.  */
5064
5065   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5066     return FAILURE;
5067
5068   e->value.function.actual = newactual;
5069   e->value.function.name = e->value.compcall.name;
5070   e->value.function.esym = target->n.sym;
5071   e->value.function.class_esym = NULL;
5072   e->value.function.isym = NULL;
5073   e->symtree = target;
5074   e->ts = target->n.sym->ts;
5075   e->expr_type = EXPR_FUNCTION;
5076
5077   /* Resolution is not necessary if this is a class subroutine; this
5078      function only has to identify the specific proc. Resolution of
5079      the call will be done next in resolve_typebound_call.  */
5080   return fcn ? gfc_resolve_expr (e) : SUCCESS;
5081 }
5082
5083
5084 /* Resolve a typebound call for the members in a class.  This group of
5085    functions implements dynamic dispatch in the provisional version
5086    of f03 OOP.  As soon as vtables are in place and contain pointers
5087    to methods, this will no longer be necessary.  */
5088 static gfc_expr *list_e;
5089 static void check_class_members (gfc_symbol *);
5090 static gfc_try class_try;
5091 static bool fcn_flag;
5092 static gfc_symbol *class_object;
5093
5094
5095 static void
5096 check_members (gfc_symbol *derived)
5097 {
5098   if (derived->attr.flavor == FL_DERIVED)
5099     check_class_members (derived);
5100 }
5101
5102
5103 static void 
5104 check_class_members (gfc_symbol *derived)
5105 {
5106   gfc_symbol* tbp_sym;
5107   gfc_expr *e;
5108   gfc_symtree *tbp;
5109   gfc_class_esym_list *etmp;
5110
5111   e = gfc_copy_expr (list_e);
5112
5113   tbp = gfc_find_typebound_proc (derived, &class_try,
5114                                  e->value.compcall.name,
5115                                  false, &e->where);
5116
5117   if (tbp == NULL)
5118     {
5119       gfc_error ("no typebound available procedure named '%s' at %L",
5120                  e->value.compcall.name, &e->where);
5121       return;
5122     }
5123
5124   if (tbp->n.tb->is_generic)
5125     {
5126       tbp_sym = NULL;
5127
5128       /* If we have to match a passed class member, force the actual
5129          expression to have the correct type.  */
5130       if (!tbp->n.tb->nopass)
5131         {
5132           if (e->value.compcall.base_object == NULL)
5133             e->value.compcall.base_object =
5134                         extract_compcall_passed_object (e);
5135
5136           e->value.compcall.base_object->ts.type = BT_DERIVED;
5137           e->value.compcall.base_object->ts.u.derived = derived;
5138         }
5139     }
5140   else
5141     tbp_sym = tbp->n.tb->u.specific->n.sym;
5142
5143   e->value.compcall.tbp = tbp->n.tb;
5144   e->value.compcall.name = tbp->name;
5145
5146   /* Let the original expresssion catch the assertion in
5147      resolve_compcall, since this flag does not appear to be reset or
5148      copied in some systems.  */
5149   e->value.compcall.assign = 0;
5150
5151   /* Do the renaming, PASSing, generic => specific and other
5152      good things for each class member.  */
5153   class_try = (resolve_compcall (e, fcn_flag) == SUCCESS)
5154                                 ? class_try : FAILURE;
5155
5156   /* Now transfer the found symbol to the esym list.  */
5157   if (class_try == SUCCESS)
5158     {
5159       etmp = list_e->value.function.class_esym;
5160       list_e->value.function.class_esym
5161                 = gfc_get_class_esym_list();
5162       list_e->value.function.class_esym->next = etmp;
5163       list_e->value.function.class_esym->derived = derived;
5164       list_e->value.function.class_esym->esym
5165                 = e->value.function.esym;
5166     }
5167
5168   gfc_free_expr (e);
5169   
5170   /* Burrow down into grandchildren types.  */
5171   if (derived->f2k_derived)
5172     gfc_traverse_ns (derived->f2k_derived, check_members);
5173 }
5174
5175
5176 /* Eliminate esym_lists where all the members point to the
5177    typebound procedure of the declared type; ie. one where
5178    type selection has no effect..  */
5179 static void
5180 resolve_class_esym (gfc_expr *e)
5181 {
5182   gfc_class_esym_list *p, *q;
5183   bool empty = true;
5184
5185   gcc_assert (e && e->expr_type == EXPR_FUNCTION);
5186
5187   p = e->value.function.class_esym;
5188   if (p == NULL)
5189     return;
5190
5191   for (; p; p = p->next)
5192     empty = empty && (e->value.function.esym == p->esym);
5193
5194   if (empty)
5195     {
5196       p = e->value.function.class_esym;
5197       for (; p; p = q)
5198         {
5199           q = p->next;
5200           gfc_free (p);
5201         }
5202       e->value.function.class_esym = NULL;
5203    }
5204 }
5205
5206
5207 /* Generate an expression for the vindex, given the reference to
5208    the class of the final expression (class_ref), the base of the
5209    full reference list (new_ref), the declared type and the class
5210    object (st).  */
5211 static gfc_expr*
5212 vindex_expr (gfc_ref *class_ref, gfc_ref *new_ref,
5213              gfc_symbol *declared, gfc_symtree *st)
5214 {
5215   gfc_expr *vindex;
5216   gfc_ref *ref;
5217
5218   /* Build an expression for the correct vindex; ie. that of the last
5219      CLASS reference.  */
5220   ref = gfc_get_ref();
5221   ref->type = REF_COMPONENT;
5222   ref->u.c.component = declared->components->next;
5223   ref->u.c.sym = declared;
5224   ref->next = NULL;
5225   if (class_ref)
5226     {
5227       class_ref->next = ref;
5228     }
5229   else
5230     {
5231       gfc_free_ref_list (new_ref);
5232       new_ref = ref;
5233     }
5234   vindex = gfc_get_expr ();
5235   vindex->expr_type = EXPR_VARIABLE;
5236   vindex->symtree = st;
5237   vindex->symtree->n.sym->refs++;
5238   vindex->ts = ref->u.c.component->ts;
5239   vindex->ref = new_ref;
5240
5241   return vindex;
5242 }
5243
5244
5245 /* Get the ultimate declared type from an expression.  In addition,
5246    return the last class/derived type reference and the copy of the
5247    reference list.  */
5248 static gfc_symbol*
5249 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5250                         gfc_expr *e)
5251 {
5252   gfc_symbol *declared;
5253   gfc_ref *ref;
5254
5255   declared = NULL;
5256   *class_ref = NULL;
5257   *new_ref = gfc_copy_ref (e->ref);
5258   for (ref = *new_ref; ref; ref = ref->next)
5259     {
5260       if (ref->type != REF_COMPONENT)
5261         continue;
5262
5263       if (ref->u.c.component->ts.type == BT_CLASS
5264             || ref->u.c.component->ts.type == BT_DERIVED)
5265         {
5266           declared = ref->u.c.component->ts.u.derived;
5267           *class_ref = ref;
5268         }
5269     }
5270
5271   if (declared == NULL)
5272     declared = e->symtree->n.sym->ts.u.derived;
5273
5274   return declared;
5275 }
5276
5277
5278 /* Resolve the argument expressions so that any arguments expressions
5279    that include class methods are resolved before the current call.
5280    This is necessary because of the static variables used in CLASS
5281    method resolution.  */
5282 static void
5283 resolve_arg_exprs (gfc_actual_arglist *arg)
5284
5285   /* Resolve the actual arglist expressions.  */
5286   for (; arg; arg = arg->next)
5287     {
5288       if (arg->expr)
5289         gfc_resolve_expr (arg->expr);
5290     }
5291 }
5292
5293
5294 /* Resolve a CLASS typebound function, or 'method'.  */
5295 static gfc_try
5296 resolve_class_compcall (gfc_expr* e)
5297 {
5298   gfc_symbol *derived, *declared;
5299   gfc_ref *new_ref;
5300   gfc_ref *class_ref;
5301   gfc_symtree *st;
5302
5303   st = e->symtree;
5304   class_object = st->n.sym;
5305
5306   /* Get the CLASS declared type.  */
5307   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5308
5309   /* Weed out cases of the ultimate component being a derived type.  */
5310   if (class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5311     {
5312       gfc_free_ref_list (new_ref);
5313       return resolve_compcall (e, true);
5314     }
5315
5316   /* Resolve the argument expressions,  */
5317   resolve_arg_exprs (e->value.function.actual); 
5318
5319   /* Get the data component, which is of the declared type.  */
5320   derived = declared->components->ts.u.derived;
5321
5322   /* Resolve the function call for each member of the class.  */
5323   class_try = SUCCESS;
5324   fcn_flag = true;
5325   list_e = gfc_copy_expr (e);
5326   check_class_members (derived);
5327
5328   class_try = (resolve_compcall (e, true) == SUCCESS)
5329                  ? class_try : FAILURE;
5330
5331   /* Transfer the class list to the original expression.  Note that
5332      the class_esym list is cleaned up in trans-expr.c, as the calls
5333      are translated.  */
5334   e->value.function.class_esym = list_e->value.function.class_esym;
5335   list_e->value.function.class_esym = NULL;
5336   gfc_free_expr (list_e);
5337
5338   resolve_class_esym (e);
5339
5340   /* More than one typebound procedure so transmit an expression for
5341      the vindex as the selector.  */
5342   if (e->value.function.class_esym != NULL)
5343     e->value.function.class_esym->vindex
5344                 = vindex_expr (class_ref, new_ref, declared, st);
5345
5346   return class_try;
5347 }
5348
5349 /* Resolve a CLASS typebound subroutine, or 'method'.  */
5350 static gfc_try
5351 resolve_class_typebound_call (gfc_code *code)
5352 {
5353   gfc_symbol *derived, *declared;
5354   gfc_ref *new_ref;
5355   gfc_ref *class_ref;
5356   gfc_symtree *st;
5357
5358   st = code->expr1->symtree;
5359   class_object = st->n.sym;
5360
5361   /* Get the CLASS declared type.  */
5362   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5363
5364   /* Weed out cases of the ultimate component being a derived type.  */
5365   if (class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5366     {
5367       gfc_free_ref_list (new_ref);
5368       return resolve_typebound_call (code);
5369     } 
5370
5371   /* Resolve the argument expressions,  */
5372   resolve_arg_exprs (code->expr1->value.compcall.actual); 
5373
5374   /* Get the data component, which is of the declared type.  */
5375   derived = declared->components->ts.u.derived;
5376
5377   class_try = SUCCESS;
5378   fcn_flag = false;
5379   list_e = gfc_copy_expr (code->expr1);
5380   check_class_members (derived);
5381
5382   class_try = (resolve_typebound_call (code) == SUCCESS)
5383                  ? class_try : FAILURE;
5384
5385   /* Transfer the class list to the original expression.  Note that
5386      the class_esym list is cleaned up in trans-expr.c, as the calls
5387      are translated.  */
5388   code->expr1->value.function.class_esym
5389                         = list_e->value.function.class_esym;
5390   list_e->value.function.class_esym = NULL;
5391   gfc_free_expr (list_e);
5392
5393   resolve_class_esym (code->expr1);
5394
5395   /* More than one typebound procedure so transmit an expression for
5396      the vindex as the selector.  */
5397   if (code->expr1->value.function.class_esym != NULL)
5398     code->expr1->value.function.class_esym->vindex
5399                 = vindex_expr (class_ref, new_ref, declared, st);
5400
5401   return class_try;
5402 }
5403
5404
5405 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5406
5407 static gfc_try
5408 resolve_ppc_call (gfc_code* c)
5409 {
5410   gfc_component *comp;
5411   bool b;
5412
5413   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5414   gcc_assert (b);
5415
5416   c->resolved_sym = c->expr1->symtree->n.sym;
5417   c->expr1->expr_type = EXPR_VARIABLE;
5418
5419   if (!comp->attr.subroutine)
5420     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5421
5422   if (resolve_ref (c->expr1) == FAILURE)
5423     return FAILURE;
5424
5425   if (update_ppc_arglist (c->expr1) == FAILURE)
5426     return FAILURE;
5427
5428   c->ext.actual = c->expr1->value.compcall.actual;
5429
5430   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5431                               comp->formal == NULL) == FAILURE)
5432     return FAILURE;
5433
5434   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5435
5436   return SUCCESS;
5437 }
5438
5439
5440 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5441
5442 static gfc_try
5443 resolve_expr_ppc (gfc_expr* e)
5444 {
5445   gfc_component *comp;
5446   bool b;
5447
5448   b = gfc_is_proc_ptr_comp (e, &comp);
5449   gcc_assert (b);
5450
5451   /* Convert to EXPR_FUNCTION.  */
5452   e->expr_type = EXPR_FUNCTION;
5453   e->value.function.isym = NULL;
5454   e->value.function.actual = e->value.compcall.actual;
5455   e->ts = comp->ts;
5456   if (comp->as != NULL)
5457     e->rank = comp->as->rank;
5458
5459   if (!comp->attr.function)
5460     gfc_add_function (&comp->attr, comp->name, &e->where);
5461
5462   if (resolve_ref (e) == FAILURE)
5463     return FAILURE;
5464
5465   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5466                               comp->formal == NULL) == FAILURE)
5467     return FAILURE;
5468
5469   if (update_ppc_arglist (e) == FAILURE)
5470     return FAILURE;
5471
5472   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5473
5474   return SUCCESS;
5475 }
5476
5477
5478 /* Resolve an expression.  That is, make sure that types of operands agree
5479    with their operators, intrinsic operators are converted to function calls
5480    for overloaded types and unresolved function references are resolved.  */
5481
5482 gfc_try
5483 gfc_resolve_expr (gfc_expr *e)
5484 {
5485   gfc_try t;
5486
5487   if (e == NULL)
5488     return SUCCESS;
5489
5490   switch (e->expr_type)
5491     {
5492     case EXPR_OP:
5493       t = resolve_operator (e);
5494       break;
5495
5496     case EXPR_FUNCTION:
5497     case EXPR_VARIABLE:
5498
5499       if (check_host_association (e))
5500         t = resolve_function (e);
5501       else
5502         {
5503           t = resolve_variable (e);
5504           if (t == SUCCESS)
5505             expression_rank (e);
5506         }
5507
5508       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5509           && e->ref->type != REF_SUBSTRING)
5510         gfc_resolve_substring_charlen (e);
5511
5512       break;
5513
5514     case EXPR_COMPCALL:
5515       if (e->symtree && e->symtree->n.sym->ts.type == BT_CLASS)
5516         t = resolve_class_compcall (e);
5517       else
5518         t = resolve_compcall (e, true);
5519       break;
5520
5521     case EXPR_SUBSTRING:
5522       t = resolve_ref (e);
5523       break;
5524
5525     case EXPR_CONSTANT:
5526     case EXPR_NULL:
5527       t = SUCCESS;
5528       break;
5529
5530     case EXPR_PPC:
5531       t = resolve_expr_ppc (e);
5532       break;
5533
5534     case EXPR_ARRAY:
5535       t = FAILURE;
5536       if (resolve_ref (e) == FAILURE)
5537         break;
5538
5539       t = gfc_resolve_array_constructor (e);
5540       /* Also try to expand a constructor.  */
5541       if (t == SUCCESS)
5542         {
5543           expression_rank (e);
5544           gfc_expand_constructor (e);
5545         }
5546
5547       /* This provides the opportunity for the length of constructors with
5548          character valued function elements to propagate the string length
5549          to the expression.  */
5550       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5551         t = gfc_resolve_character_array_constructor (e);
5552
5553       break;
5554
5555     case EXPR_STRUCTURE:
5556       t = resolve_ref (e);
5557       if (t == FAILURE)
5558         break;
5559
5560       t = resolve_structure_cons (e);
5561       if (t == FAILURE)
5562         break;
5563
5564       t = gfc_simplify_expr (e, 0);
5565       break;
5566
5567     default:
5568       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5569     }
5570
5571   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5572     fixup_charlen (e);
5573
5574   return t;
5575 }
5576
5577
5578 /* Resolve an expression from an iterator.  They must be scalar and have
5579    INTEGER or (optionally) REAL type.  */
5580
5581 static gfc_try
5582 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5583                            const char *name_msgid)
5584 {
5585   if (gfc_resolve_expr (expr) == FAILURE)
5586     return FAILURE;
5587
5588   if (expr->rank != 0)
5589     {
5590       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5591       return FAILURE;
5592     }
5593
5594   if (expr->ts.type != BT_INTEGER)
5595     {
5596       if (expr->ts.type == BT_REAL)
5597         {
5598           if (real_ok)
5599             return gfc_notify_std (GFC_STD_F95_DEL,
5600                                    "Deleted feature: %s at %L must be integer",
5601                                    _(name_msgid), &expr->where);
5602           else
5603             {
5604               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5605                          &expr->where);
5606               return FAILURE;
5607             }
5608         }
5609       else
5610         {
5611           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5612           return FAILURE;
5613         }
5614     }
5615   return SUCCESS;
5616 }
5617
5618
5619 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5620    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5621
5622 gfc_try
5623 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5624 {
5625   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5626       == FAILURE)
5627     return FAILURE;
5628
5629   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5630     {
5631       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5632                  &iter->var->where);
5633       return FAILURE;
5634     }
5635
5636   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5637                                  "Start expression in DO loop") == FAILURE)
5638     return FAILURE;
5639
5640   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5641                                  "End expression in DO loop") == FAILURE)
5642     return FAILURE;
5643
5644   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5645                                  "Step expression in DO loop") == FAILURE)
5646     return FAILURE;
5647
5648   if (iter->step->expr_type == EXPR_CONSTANT)
5649     {
5650       if ((iter->step->ts.type == BT_INTEGER
5651            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5652           || (iter->step->ts.type == BT_REAL
5653               && mpfr_sgn (iter->step->value.real) == 0))
5654         {
5655           gfc_error ("Step expression in DO loop at %L cannot be zero",
5656                      &iter->step->where);
5657           return FAILURE;
5658         }
5659     }
5660
5661   /* Convert start, end, and step to the same type as var.  */
5662   if (iter->start->ts.kind != iter->var->ts.kind
5663       || iter->start->ts.type != iter->var->ts.type)
5664     gfc_convert_type (iter->start, &iter->var->ts, 2);
5665
5666   if (iter->end->ts.kind != iter->var->ts.kind
5667       || iter->end->ts.type != iter->var->ts.type)
5668     gfc_convert_type (iter->end, &iter->var->ts, 2);
5669
5670   if (iter->step->ts.kind != iter->var->ts.kind
5671       || iter->step->ts.type != iter->var->ts.type)
5672     gfc_convert_type (iter->step, &iter->var->ts, 2);
5673
5674   if (iter->start->expr_type == EXPR_CONSTANT
5675       && iter->end->expr_type == EXPR_CONSTANT
5676       && iter->step->expr_type == EXPR_CONSTANT)
5677     {
5678       int sgn, cmp;
5679       if (iter->start->ts.type == BT_INTEGER)
5680         {
5681           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5682           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5683         }
5684       else
5685         {
5686           sgn = mpfr_sgn (iter->step->value.real);
5687           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5688         }
5689       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5690         gfc_warning ("DO loop at %L will be executed zero times",
5691                      &iter->step->where);
5692     }
5693
5694   return SUCCESS;
5695 }
5696
5697
5698 /* Traversal function for find_forall_index.  f == 2 signals that
5699    that variable itself is not to be checked - only the references.  */
5700
5701 static bool
5702 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5703 {
5704   if (expr->expr_type != EXPR_VARIABLE)
5705     return false;
5706   
5707   /* A scalar assignment  */
5708   if (!expr->ref || *f == 1)
5709     {
5710       if (expr->symtree->n.sym == sym)
5711         return true;
5712       else
5713         return false;
5714     }
5715
5716   if (*f == 2)
5717     *f = 1;
5718   return false;
5719 }
5720
5721
5722 /* Check whether the FORALL index appears in the expression or not.
5723    Returns SUCCESS if SYM is found in EXPR.  */
5724
5725 gfc_try
5726 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5727 {
5728   if (gfc_traverse_expr (expr, sym, forall_index, f))
5729     return SUCCESS;
5730   else
5731     return FAILURE;
5732 }
5733
5734
5735 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5736    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5737    INTEGERs, and if stride is a constant it must be nonzero.
5738    Furthermore "A subscript or stride in a forall-triplet-spec shall
5739    not contain a reference to any index-name in the
5740    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5741
5742 static void
5743 resolve_forall_iterators (gfc_forall_iterator *it)
5744 {
5745   gfc_forall_iterator *iter, *iter2;
5746
5747   for (iter = it; iter; iter = iter->next)
5748     {
5749       if (gfc_resolve_expr (iter->var) == SUCCESS
5750           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5751         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5752                    &iter->var->where);
5753
5754       if (gfc_resolve_expr (iter->start) == SUCCESS
5755           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5756         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5757                    &iter->start->where);
5758       if (iter->var->ts.kind != iter->start->ts.kind)
5759         gfc_convert_type (iter->start, &iter->var->ts, 2);
5760
5761       if (gfc_resolve_expr (iter->end) == SUCCESS
5762           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
5763         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
5764                    &iter->end->where);
5765       if (iter->var->ts.kind != iter->end->ts.kind)
5766         gfc_convert_type (iter->end, &iter->var->ts, 2);
5767
5768       if (gfc_resolve_expr (iter->stride) == SUCCESS)
5769         {
5770           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
5771             gfc_error ("FORALL stride expression at %L must be a scalar %s",
5772                        &iter->stride->where, "INTEGER");
5773
5774           if (iter->stride->expr_type == EXPR_CONSTANT
5775               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
5776             gfc_error ("FORALL stride expression at %L cannot be zero",
5777                        &iter->stride->where);
5778         }
5779       if (iter->var->ts.kind != iter->stride->ts.kind)
5780         gfc_convert_type (iter->stride, &iter->var->ts, 2);
5781     }
5782
5783   for (iter = it; iter; iter = iter->next)
5784     for (iter2 = iter; iter2; iter2 = iter2->next)
5785       {
5786         if (find_forall_index (iter2->start,
5787                                iter->var->symtree->n.sym, 0) == SUCCESS
5788             || find_forall_index (iter2->end,
5789                                   iter->var->symtree->n.sym, 0) == SUCCESS
5790             || find_forall_index (iter2->stride,
5791                                   iter->var->symtree->n.sym, 0) == SUCCESS)
5792           gfc_error ("FORALL index '%s' may not appear in triplet "
5793                      "specification at %L", iter->var->symtree->name,
5794                      &iter2->start->where);
5795       }
5796 }
5797
5798
5799 /* Given a pointer to a symbol that is a derived type, see if it's
5800    inaccessible, i.e. if it's defined in another module and the components are
5801    PRIVATE.  The search is recursive if necessary.  Returns zero if no
5802    inaccessible components are found, nonzero otherwise.  */
5803
5804 static int
5805 derived_inaccessible (gfc_symbol *sym)
5806 {
5807   gfc_component *c;
5808
5809   if (sym->attr.use_assoc && sym->attr.private_comp)
5810     return 1;
5811
5812   for (c = sym->components; c; c = c->next)
5813     {
5814         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
5815           return 1;
5816     }
5817
5818   return 0;
5819 }
5820
5821
5822 /* Resolve the argument of a deallocate expression.  The expression must be
5823    a pointer or a full array.  */
5824
5825 static gfc_try
5826 resolve_deallocate_expr (gfc_expr *e)
5827 {
5828   symbol_attribute attr;
5829   int allocatable, pointer, check_intent_in;
5830   gfc_ref *ref;
5831   gfc_symbol *sym;
5832   gfc_component *c;
5833
5834   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5835   check_intent_in = 1;
5836
5837   if (gfc_resolve_expr (e) == FAILURE)
5838     return FAILURE;
5839
5840   if (e->expr_type != EXPR_VARIABLE)
5841     goto bad;
5842
5843   sym = e->symtree->n.sym;
5844
5845   if (sym->ts.type == BT_CLASS)
5846     {
5847       allocatable = sym->ts.u.derived->components->attr.allocatable;
5848       pointer = sym->ts.u.derived->components->attr.pointer;
5849     }
5850   else
5851     {
5852       allocatable = sym->attr.allocatable;
5853       pointer = sym->attr.pointer;
5854     }
5855   for (ref = e->ref; ref; ref = ref->next)
5856     {
5857       if (pointer)
5858         check_intent_in = 0;
5859
5860       switch (ref->type)
5861         {
5862         case REF_ARRAY:
5863           if (ref->u.ar.type != AR_FULL)
5864             allocatable = 0;
5865           break;
5866
5867         case REF_COMPONENT:
5868           c = ref->u.c.component;
5869           if (c->ts.type == BT_CLASS)
5870             {
5871               allocatable = c->ts.u.derived->components->attr.allocatable;
5872               pointer = c->ts.u.derived->components->attr.pointer;
5873             }
5874           else
5875             {
5876               allocatable = c->attr.allocatable;
5877               pointer = c->attr.pointer;
5878             }
5879           break;
5880
5881         case REF_SUBSTRING:
5882           allocatable = 0;
5883           break;
5884         }
5885     }
5886
5887   attr = gfc_expr_attr (e);
5888
5889   if (allocatable == 0 && attr.pointer == 0)
5890     {
5891     bad:
5892       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
5893                  &e->where);
5894     }
5895
5896   if (check_intent_in && sym->attr.intent == INTENT_IN)
5897     {
5898       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
5899                  sym->name, &e->where);
5900       return FAILURE;
5901     }
5902
5903   if (e->ts.type == BT_CLASS)
5904     {
5905       /* Only deallocate the DATA component.  */
5906       gfc_add_component_ref (e, "$data");
5907     }
5908
5909   return SUCCESS;
5910 }
5911
5912
5913 /* Returns true if the expression e contains a reference to the symbol sym.  */
5914 static bool
5915 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
5916 {
5917   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
5918     return true;
5919
5920   return false;
5921 }
5922
5923 bool
5924 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
5925 {
5926   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
5927 }
5928
5929
5930 /* Given the expression node e for an allocatable/pointer of derived type to be
5931    allocated, get the expression node to be initialized afterwards (needed for
5932    derived types with default initializers, and derived types with allocatable
5933    components that need nullification.)  */
5934
5935 gfc_expr *
5936 gfc_expr_to_initialize (gfc_expr *e)
5937 {
5938   gfc_expr *result;
5939   gfc_ref *ref;
5940   int i;
5941
5942   result = gfc_copy_expr (e);
5943
5944   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
5945   for (ref = result->ref; ref; ref = ref->next)
5946     if (ref->type == REF_ARRAY && ref->next == NULL)
5947       {
5948         ref->u.ar.type = AR_FULL;
5949
5950         for (i = 0; i < ref->u.ar.dimen; i++)
5951           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
5952
5953         result->rank = ref->u.ar.dimen;
5954         break;
5955       }
5956
5957   return result;
5958 }
5959
5960
5961 /* Resolve the expression in an ALLOCATE statement, doing the additional
5962    checks to see whether the expression is OK or not.  The expression must
5963    have a trailing array reference that gives the size of the array.  */
5964
5965 static gfc_try
5966 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
5967 {
5968   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
5969   symbol_attribute attr;
5970   gfc_ref *ref, *ref2;
5971   gfc_array_ref *ar;
5972   gfc_symbol *sym;
5973   gfc_alloc *a;
5974   gfc_component *c;
5975
5976   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5977   check_intent_in = 1;
5978
5979   if (gfc_resolve_expr (e) == FAILURE)
5980     return FAILURE;
5981
5982   /* Make sure the expression is allocatable or a pointer.  If it is
5983      pointer, the next-to-last reference must be a pointer.  */
5984
5985   ref2 = NULL;
5986   if (e->symtree)
5987     sym = e->symtree->n.sym;
5988
5989   /* Check whether ultimate component is abstract and CLASS.  */
5990   is_abstract = 0;
5991
5992   if (e->expr_type != EXPR_VARIABLE)
5993     {
5994       allocatable = 0;
5995       attr = gfc_expr_attr (e);
5996       pointer = attr.pointer;
5997       dimension = attr.dimension;
5998     }
5999   else
6000     {
6001       if (sym->ts.type == BT_CLASS)
6002         {
6003           allocatable = sym->ts.u.derived->components->attr.allocatable;
6004           pointer = sym->ts.u.derived->components->attr.pointer;
6005           dimension = sym->ts.u.derived->components->attr.dimension;
6006           is_abstract = sym->ts.u.derived->components->attr.abstract;
6007         }
6008       else
6009         {
6010           allocatable = sym->attr.allocatable;
6011           pointer = sym->attr.pointer;
6012           dimension = sym->attr.dimension;
6013         }
6014
6015       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6016         {
6017           if (pointer)
6018             check_intent_in = 0;
6019
6020           switch (ref->type)
6021             {
6022               case REF_ARRAY:
6023                 if (ref->next != NULL)
6024                   pointer = 0;
6025                 break;
6026
6027               case REF_COMPONENT:
6028                 c = ref->u.c.component;
6029                 if (c->ts.type == BT_CLASS)
6030                   {
6031                     allocatable = c->ts.u.derived->components->attr.allocatable;
6032                     pointer = c->ts.u.derived->components->attr.pointer;
6033                     dimension = c->ts.u.derived->components->attr.dimension;
6034                     is_abstract = c->ts.u.derived->components->attr.abstract;
6035                   }
6036                 else
6037                   {
6038                     allocatable = c->attr.allocatable;
6039                     pointer = c->attr.pointer;
6040                     dimension = c->attr.dimension;
6041                     is_abstract = c->attr.abstract;
6042                   }
6043                 break;
6044
6045               case REF_SUBSTRING:
6046                 allocatable = 0;
6047                 pointer = 0;
6048                 break;
6049             }
6050         }
6051     }
6052
6053   if (allocatable == 0 && pointer == 0)
6054     {
6055       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6056                  &e->where);
6057       return FAILURE;
6058     }
6059
6060   if (is_abstract && !code->expr3 && code->ext.alloc.ts.type == BT_UNKNOWN)
6061     {
6062       gcc_assert (e->ts.type == BT_CLASS);
6063       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6064                  "type-spec or SOURCE=", sym->name, &e->where);
6065       return FAILURE;
6066     }
6067
6068   if (check_intent_in && sym->attr.intent == INTENT_IN)
6069     {
6070       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6071                  sym->name, &e->where);
6072       return FAILURE;
6073     }
6074
6075   if (pointer || dimension == 0)
6076     return SUCCESS;
6077
6078   /* Make sure the next-to-last reference node is an array specification.  */
6079
6080   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
6081     {
6082       gfc_error ("Array specification required in ALLOCATE statement "
6083                  "at %L", &e->where);
6084       return FAILURE;
6085     }
6086
6087   /* Make sure that the array section reference makes sense in the
6088     context of an ALLOCATE specification.  */
6089
6090   ar = &ref2->u.ar;
6091
6092   for (i = 0; i < ar->dimen; i++)
6093     {
6094       if (ref2->u.ar.type == AR_ELEMENT)
6095         goto check_symbols;
6096
6097       switch (ar->dimen_type[i])
6098         {
6099         case DIMEN_ELEMENT:
6100           break;
6101
6102         case DIMEN_RANGE:
6103           if (ar->start[i] != NULL
6104               && ar->end[i] != NULL
6105               && ar->stride[i] == NULL)
6106             break;
6107
6108           /* Fall Through...  */
6109
6110         case DIMEN_UNKNOWN:
6111         case DIMEN_VECTOR:
6112           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6113                      &e->where);
6114           return FAILURE;
6115         }
6116
6117 check_symbols:
6118
6119       for (a = code->ext.alloc.list; a; a = a->next)
6120         {
6121           sym = a->expr->symtree->n.sym;
6122
6123           /* TODO - check derived type components.  */
6124           if (sym->ts.type == BT_DERIVED)
6125             continue;
6126
6127           if ((ar->start[i] != NULL
6128                && gfc_find_sym_in_expr (sym, ar->start[i]))
6129               || (ar->end[i] != NULL
6130                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6131             {
6132               gfc_error ("'%s' must not appear in the array specification at "
6133                          "%L in the same ALLOCATE statement where it is "
6134                          "itself allocated", sym->name, &ar->where);
6135               return FAILURE;
6136             }
6137         }
6138     }
6139
6140   return SUCCESS;
6141 }
6142
6143 static void
6144 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6145 {
6146   gfc_expr *stat, *errmsg, *pe, *qe;
6147   gfc_alloc *a, *p, *q;
6148
6149   stat = code->expr1 ? code->expr1 : NULL;
6150
6151   errmsg = code->expr2 ? code->expr2 : NULL;
6152
6153   /* Check the stat variable.  */
6154   if (stat)
6155     {
6156       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6157         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6158                    stat->symtree->n.sym->name, &stat->where);
6159
6160       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6161         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6162                    &stat->where);
6163
6164       if ((stat->ts.type != BT_INTEGER
6165            && !(stat->ref && (stat->ref->type == REF_ARRAY
6166                               || stat->ref->type == REF_COMPONENT)))
6167           || stat->rank > 0)
6168         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6169                    "variable", &stat->where);
6170
6171       for (p = code->ext.alloc.list; p; p = p->next)
6172         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6173           gfc_error ("Stat-variable at %L shall not be %sd within "
6174                      "the same %s statement", &stat->where, fcn, fcn);
6175     }
6176
6177   /* Check the errmsg variable.  */
6178   if (errmsg)
6179     {
6180       if (!stat)
6181         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6182                      &errmsg->where);
6183
6184       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6185         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6186                    errmsg->symtree->n.sym->name, &errmsg->where);
6187
6188       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6189         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6190                    &errmsg->where);
6191
6192       if ((errmsg->ts.type != BT_CHARACTER
6193            && !(errmsg->ref
6194                 && (errmsg->ref->type == REF_ARRAY
6195                     || errmsg->ref->type == REF_COMPONENT)))
6196           || errmsg->rank > 0 )
6197         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6198                    "variable", &errmsg->where);
6199
6200       for (p = code->ext.alloc.list; p; p = p->next)
6201         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6202           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6203                      "the same %s statement", &errmsg->where, fcn, fcn);
6204     }
6205
6206   /* Check that an allocate-object appears only once in the statement.  
6207      FIXME: Checking derived types is disabled.  */
6208   for (p = code->ext.alloc.list; p; p = p->next)
6209     {
6210       pe = p->expr;
6211       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6212            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6213         {
6214           for (q = p->next; q; q = q->next)
6215             {
6216               qe = q->expr;
6217               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6218                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6219                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6220                 gfc_error ("Allocate-object at %L also appears at %L",
6221                            &pe->where, &qe->where);
6222             }
6223         }
6224     }
6225
6226   if (strcmp (fcn, "ALLOCATE") == 0)
6227     {
6228       for (a = code->ext.alloc.list; a; a = a->next)
6229         resolve_allocate_expr (a->expr, code);
6230     }
6231   else
6232     {
6233       for (a = code->ext.alloc.list; a; a = a->next)
6234         resolve_deallocate_expr (a->expr);
6235     }
6236 }
6237
6238
6239 /************ SELECT CASE resolution subroutines ************/
6240
6241 /* Callback function for our mergesort variant.  Determines interval
6242    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6243    op1 > op2.  Assumes we're not dealing with the default case.  
6244    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6245    There are nine situations to check.  */
6246
6247 static int
6248 compare_cases (const gfc_case *op1, const gfc_case *op2)
6249 {
6250   int retval;
6251
6252   if (op1->low == NULL) /* op1 = (:L)  */
6253     {
6254       /* op2 = (:N), so overlap.  */
6255       retval = 0;
6256       /* op2 = (M:) or (M:N),  L < M  */
6257       if (op2->low != NULL
6258           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6259         retval = -1;
6260     }
6261   else if (op1->high == NULL) /* op1 = (K:)  */
6262     {
6263       /* op2 = (M:), so overlap.  */
6264       retval = 0;
6265       /* op2 = (:N) or (M:N), K > N  */
6266       if (op2->high != NULL
6267           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6268         retval = 1;
6269     }
6270   else /* op1 = (K:L)  */
6271     {
6272       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6273         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6274                  ? 1 : 0;
6275       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6276         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6277                  ? -1 : 0;
6278       else                      /* op2 = (M:N)  */
6279         {
6280           retval =  0;
6281           /* L < M  */
6282           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6283             retval =  -1;
6284           /* K > N  */
6285           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6286             retval =  1;
6287         }
6288     }
6289
6290   return retval;
6291 }
6292
6293
6294 /* Merge-sort a double linked case list, detecting overlap in the
6295    process.  LIST is the head of the double linked case list before it
6296    is sorted.  Returns the head of the sorted list if we don't see any
6297    overlap, or NULL otherwise.  */
6298
6299 static gfc_case *
6300 check_case_overlap (gfc_case *list)
6301 {
6302   gfc_case *p, *q, *e, *tail;
6303   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6304
6305   /* If the passed list was empty, return immediately.  */
6306   if (!list)
6307     return NULL;
6308
6309   overlap_seen = 0;
6310   insize = 1;
6311
6312   /* Loop unconditionally.  The only exit from this loop is a return
6313      statement, when we've finished sorting the case list.  */
6314   for (;;)
6315     {
6316       p = list;
6317       list = NULL;
6318       tail = NULL;
6319
6320       /* Count the number of merges we do in this pass.  */
6321       nmerges = 0;
6322
6323       /* Loop while there exists a merge to be done.  */
6324       while (p)
6325         {
6326           int i;
6327
6328           /* Count this merge.  */
6329           nmerges++;
6330
6331           /* Cut the list in two pieces by stepping INSIZE places
6332              forward in the list, starting from P.  */
6333           psize = 0;
6334           q = p;
6335           for (i = 0; i < insize; i++)
6336             {
6337               psize++;
6338               q = q->right;
6339               if (!q)
6340                 break;
6341             }
6342           qsize = insize;
6343
6344           /* Now we have two lists.  Merge them!  */
6345           while (psize > 0 || (qsize > 0 && q != NULL))
6346             {
6347               /* See from which the next case to merge comes from.  */
6348               if (psize == 0)
6349                 {
6350                   /* P is empty so the next case must come from Q.  */
6351                   e = q;
6352                   q = q->right;
6353                   qsize--;
6354                 }
6355               else if (qsize == 0 || q == NULL)
6356                 {
6357                   /* Q is empty.  */
6358                   e = p;
6359                   p = p->right;
6360                   psize--;
6361                 }
6362               else
6363                 {
6364                   cmp = compare_cases (p, q);
6365                   if (cmp < 0)
6366                     {
6367                       /* The whole case range for P is less than the
6368                          one for Q.  */
6369                       e = p;
6370                       p = p->right;
6371                       psize--;
6372                     }
6373                   else if (cmp > 0)
6374                     {
6375                       /* The whole case range for Q is greater than
6376                          the case range for P.  */
6377                       e = q;
6378                       q = q->right;
6379                       qsize--;
6380                     }
6381                   else
6382                     {
6383                       /* The cases overlap, or they are the same
6384                          element in the list.  Either way, we must
6385                          issue an error and get the next case from P.  */
6386                       /* FIXME: Sort P and Q by line number.  */
6387                       gfc_error ("CASE label at %L overlaps with CASE "
6388                                  "label at %L", &p->where, &q->where);
6389                       overlap_seen = 1;
6390                       e = p;
6391                       p = p->right;
6392                       psize--;
6393                     }
6394                 }
6395
6396                 /* Add the next element to the merged list.  */
6397               if (tail)
6398                 tail->right = e;
6399               else
6400                 list = e;
6401               e->left = tail;
6402               tail = e;
6403             }
6404
6405           /* P has now stepped INSIZE places along, and so has Q.  So
6406              they're the same.  */
6407           p = q;
6408         }
6409       tail->right = NULL;
6410
6411       /* If we have done only one merge or none at all, we've
6412          finished sorting the cases.  */
6413       if (nmerges <= 1)
6414         {
6415           if (!overlap_seen)
6416             return list;
6417           else
6418             return NULL;
6419         }
6420
6421       /* Otherwise repeat, merging lists twice the size.  */
6422       insize *= 2;
6423     }
6424 }
6425
6426
6427 /* Check to see if an expression is suitable for use in a CASE statement.
6428    Makes sure that all case expressions are scalar constants of the same
6429    type.  Return FAILURE if anything is wrong.  */
6430
6431 static gfc_try
6432 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6433 {
6434   if (e == NULL) return SUCCESS;
6435
6436   if (e->ts.type != case_expr->ts.type)
6437     {
6438       gfc_error ("Expression in CASE statement at %L must be of type %s",
6439                  &e->where, gfc_basic_typename (case_expr->ts.type));
6440       return FAILURE;
6441     }
6442
6443   /* C805 (R808) For a given case-construct, each case-value shall be of
6444      the same type as case-expr.  For character type, length differences
6445      are allowed, but the kind type parameters shall be the same.  */
6446
6447   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6448     {
6449       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6450                  &e->where, case_expr->ts.kind);
6451       return FAILURE;
6452     }
6453
6454   /* Convert the case value kind to that of case expression kind, if needed.
6455      FIXME:  Should a warning be issued?  */
6456   if (e->ts.kind != case_expr->ts.kind)
6457     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6458
6459   if (e->rank != 0)
6460     {
6461       gfc_error ("Expression in CASE statement at %L must be scalar",
6462                  &e->where);
6463       return FAILURE;
6464     }
6465
6466   return SUCCESS;
6467 }
6468
6469
6470 /* Given a completely parsed select statement, we:
6471
6472      - Validate all expressions and code within the SELECT.
6473      - Make sure that the selection expression is not of the wrong type.
6474      - Make sure that no case ranges overlap.
6475      - Eliminate unreachable cases and unreachable code resulting from
6476        removing case labels.
6477
6478    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6479    they are a hassle for code generation, and to prevent that, we just
6480    cut them out here.  This is not necessary for overlapping cases
6481    because they are illegal and we never even try to generate code.
6482
6483    We have the additional caveat that a SELECT construct could have
6484    been a computed GOTO in the source code. Fortunately we can fairly
6485    easily work around that here: The case_expr for a "real" SELECT CASE
6486    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6487    we have to do is make sure that the case_expr is a scalar integer
6488    expression.  */
6489
6490 static void
6491 resolve_select (gfc_code *code)
6492 {
6493   gfc_code *body;
6494   gfc_expr *case_expr;
6495   gfc_case *cp, *default_case, *tail, *head;
6496   int seen_unreachable;
6497   int seen_logical;
6498   int ncases;
6499   bt type;
6500   gfc_try t;
6501
6502   if (code->expr1 == NULL)
6503     {
6504       /* This was actually a computed GOTO statement.  */
6505       case_expr = code->expr2;
6506       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6507         gfc_error ("Selection expression in computed GOTO statement "
6508                    "at %L must be a scalar integer expression",
6509                    &case_expr->where);
6510
6511       /* Further checking is not necessary because this SELECT was built
6512          by the compiler, so it should always be OK.  Just move the
6513          case_expr from expr2 to expr so that we can handle computed
6514          GOTOs as normal SELECTs from here on.  */
6515       code->expr1 = code->expr2;
6516       code->expr2 = NULL;
6517       return;
6518     }
6519
6520   case_expr = code->expr1;
6521
6522   type = case_expr->ts.type;
6523   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6524     {
6525       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6526                  &case_expr->where, gfc_typename (&case_expr->ts));
6527
6528       /* Punt. Going on here just produce more garbage error messages.  */
6529       return;
6530     }
6531
6532   if (case_expr->rank != 0)
6533     {
6534       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6535                  "expression", &case_expr->where);
6536
6537       /* Punt.  */
6538       return;
6539     }
6540
6541   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6542      of the SELECT CASE expression and its CASE values.  Walk the lists
6543      of case values, and if we find a mismatch, promote case_expr to
6544      the appropriate kind.  */
6545
6546   if (type == BT_LOGICAL || type == BT_INTEGER)
6547     {
6548       for (body = code->block; body; body = body->block)
6549         {
6550           /* Walk the case label list.  */
6551           for (cp = body->ext.case_list; cp; cp = cp->next)
6552             {
6553               /* Intercept the DEFAULT case.  It does not have a kind.  */
6554               if (cp->low == NULL && cp->high == NULL)
6555                 continue;
6556
6557               /* Unreachable case ranges are discarded, so ignore.  */
6558               if (cp->low != NULL && cp->high != NULL
6559                   && cp->low != cp->high
6560                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6561                 continue;
6562
6563               /* FIXME: Should a warning be issued?  */
6564               if (cp->low != NULL
6565                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6566                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6567
6568               if (cp->high != NULL
6569                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6570                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6571             }
6572          }
6573     }
6574
6575   /* Assume there is no DEFAULT case.  */
6576   default_case = NULL;
6577   head = tail = NULL;
6578   ncases = 0;
6579   seen_logical = 0;
6580
6581   for (body = code->block; body; body = body->block)
6582     {
6583       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
6584       t = SUCCESS;
6585       seen_unreachable = 0;
6586
6587       /* Walk the case label list, making sure that all case labels
6588          are legal.  */
6589       for (cp = body->ext.case_list; cp; cp = cp->next)
6590         {
6591           /* Count the number of cases in the whole construct.  */
6592           ncases++;
6593
6594           /* Intercept the DEFAULT case.  */
6595           if (cp->low == NULL && cp->high == NULL)
6596             {
6597               if (default_case != NULL)
6598                 {
6599                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
6600                              "by a second DEFAULT CASE at %L",
6601                              &default_case->where, &cp->where);
6602                   t = FAILURE;
6603                   break;
6604                 }
6605               else
6606                 {
6607                   default_case = cp;
6608                   continue;
6609                 }
6610             }
6611
6612           /* Deal with single value cases and case ranges.  Errors are
6613              issued from the validation function.  */
6614           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
6615              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
6616             {
6617               t = FAILURE;
6618               break;
6619             }
6620
6621           if (type == BT_LOGICAL
6622               && ((cp->low == NULL || cp->high == NULL)
6623                   || cp->low != cp->high))
6624             {
6625               gfc_error ("Logical range in CASE statement at %L is not "
6626                          "allowed", &cp->low->where);
6627               t = FAILURE;
6628               break;
6629             }
6630
6631           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
6632             {
6633               int value;
6634               value = cp->low->value.logical == 0 ? 2 : 1;
6635               if (value & seen_logical)
6636                 {
6637                   gfc_error ("constant logical value in CASE statement "
6638                              "is repeated at %L",
6639                              &cp->low->where);
6640                   t = FAILURE;
6641                   break;
6642                 }
6643               seen_logical |= value;
6644             }
6645
6646           if (cp->low != NULL && cp->high != NULL
6647               && cp->low != cp->high
6648               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6649             {
6650               if (gfc_option.warn_surprising)
6651                 gfc_warning ("Range specification at %L can never "
6652                              "be matched", &cp->where);
6653
6654               cp->unreachable = 1;
6655               seen_unreachable = 1;
6656             }
6657           else
6658             {
6659               /* If the case range can be matched, it can also overlap with
6660                  other cases.  To make sure it does not, we put it in a
6661                  double linked list here.  We sort that with a merge sort
6662                  later on to detect any overlapping cases.  */
6663               if (!head)
6664                 {
6665                   head = tail = cp;
6666                   head->right = head->left = NULL;
6667                 }
6668               else
6669                 {
6670                   tail->right = cp;
6671                   tail->right->left = tail;
6672                   tail = tail->right;
6673                   tail->right = NULL;
6674                 }
6675             }
6676         }
6677
6678       /* It there was a failure in the previous case label, give up
6679          for this case label list.  Continue with the next block.  */
6680       if (t == FAILURE)
6681         continue;
6682
6683       /* See if any case labels that are unreachable have been seen.
6684          If so, we eliminate them.  This is a bit of a kludge because
6685          the case lists for a single case statement (label) is a
6686          single forward linked lists.  */
6687       if (seen_unreachable)
6688       {
6689         /* Advance until the first case in the list is reachable.  */
6690         while (body->ext.case_list != NULL
6691                && body->ext.case_list->unreachable)
6692           {
6693             gfc_case *n = body->ext.case_list;
6694             body->ext.case_list = body->ext.case_list->next;
6695             n->next = NULL;
6696             gfc_free_case_list (n);
6697           }
6698
6699         /* Strip all other unreachable cases.  */
6700         if (body->ext.case_list)
6701           {
6702             for (cp = body->ext.case_list; cp->next; cp = cp->next)
6703               {
6704                 if (cp->next->unreachable)
6705                   {
6706                     gfc_case *n = cp->next;
6707                     cp->next = cp->next->next;
6708                     n->next = NULL;
6709                     gfc_free_case_list (n);
6710                   }
6711               }
6712           }
6713       }
6714     }
6715
6716   /* See if there were overlapping cases.  If the check returns NULL,
6717      there was overlap.  In that case we don't do anything.  If head
6718      is non-NULL, we prepend the DEFAULT case.  The sorted list can
6719      then used during code generation for SELECT CASE constructs with
6720      a case expression of a CHARACTER type.  */
6721   if (head)
6722     {
6723       head = check_case_overlap (head);
6724
6725       /* Prepend the default_case if it is there.  */
6726       if (head != NULL && default_case)
6727         {
6728           default_case->left = NULL;
6729           default_case->right = head;
6730           head->left = default_case;
6731         }
6732     }
6733
6734   /* Eliminate dead blocks that may be the result if we've seen
6735      unreachable case labels for a block.  */
6736   for (body = code; body && body->block; body = body->block)
6737     {
6738       if (body->block->ext.case_list == NULL)
6739         {
6740           /* Cut the unreachable block from the code chain.  */
6741           gfc_code *c = body->block;
6742           body->block = c->block;
6743
6744           /* Kill the dead block, but not the blocks below it.  */
6745           c->block = NULL;
6746           gfc_free_statements (c);
6747         }
6748     }
6749
6750   /* More than two cases is legal but insane for logical selects.
6751      Issue a warning for it.  */
6752   if (gfc_option.warn_surprising && type == BT_LOGICAL
6753       && ncases > 2)
6754     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
6755                  &code->loc);
6756 }
6757
6758
6759 /* Check if a derived type is extensible.  */
6760
6761 bool
6762 gfc_type_is_extensible (gfc_symbol *sym)
6763 {
6764   return !(sym->attr.is_bind_c || sym->attr.sequence);
6765 }
6766
6767
6768 /* Resolve a SELECT TYPE statement.  */
6769
6770 static void
6771 resolve_select_type (gfc_code *code)
6772 {
6773   gfc_symbol *selector_type;
6774   gfc_code *body, *new_st;
6775   gfc_case *c, *default_case;
6776   gfc_symtree *st;
6777   char name[GFC_MAX_SYMBOL_LEN];
6778   gfc_namespace *ns;
6779
6780   ns = code->ext.ns;
6781   gfc_resolve (ns);
6782
6783   if (code->expr2)
6784     selector_type = code->expr2->ts.u.derived->components->ts.u.derived;
6785   else
6786     selector_type = code->expr1->ts.u.derived->components->ts.u.derived;
6787
6788   /* Assume there is no DEFAULT case.  */
6789   default_case = NULL;
6790
6791   /* Loop over TYPE IS / CLASS IS cases.  */
6792   for (body = code->block; body; body = body->block)
6793     {
6794       c = body->ext.case_list;
6795
6796       /* Check F03:C815.  */
6797       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6798           && !gfc_type_is_extensible (c->ts.u.derived))
6799         {
6800           gfc_error ("Derived type '%s' at %L must be extensible",
6801                      c->ts.u.derived->name, &c->where);
6802           continue;
6803         }
6804
6805       /* Check F03:C816.  */
6806       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6807           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
6808         {
6809           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
6810                      c->ts.u.derived->name, &c->where, selector_type->name);
6811           continue;
6812         }
6813
6814       /* Intercept the DEFAULT case.  */
6815       if (c->ts.type == BT_UNKNOWN)
6816         {
6817           /* Check F03:C818.  */
6818           if (default_case != NULL)
6819             gfc_error ("The DEFAULT CASE at %L cannot be followed "
6820                        "by a second DEFAULT CASE at %L",
6821                        &default_case->where, &c->where);
6822           else
6823             default_case = c;
6824           continue;
6825         }
6826     }
6827
6828   if (code->expr2)
6829     {
6830       /* Insert assignment for selector variable.  */
6831       new_st = gfc_get_code ();
6832       new_st->op = EXEC_ASSIGN;
6833       new_st->expr1 = gfc_copy_expr (code->expr1);
6834       new_st->expr2 = gfc_copy_expr (code->expr2);
6835       ns->code = new_st;
6836     }
6837
6838   /* Put SELECT TYPE statement inside a BLOCK.  */
6839   new_st = gfc_get_code ();
6840   new_st->op = code->op;
6841   new_st->expr1 = code->expr1;
6842   new_st->expr2 = code->expr2;
6843   new_st->block = code->block;
6844   if (!ns->code)
6845     ns->code = new_st;
6846   else
6847     ns->code->next = new_st;
6848   code->op = EXEC_BLOCK;
6849   code->expr1 = code->expr2 =  NULL;
6850   code->block = NULL;
6851
6852   code = new_st;
6853
6854   /* Transform to EXEC_SELECT.  */
6855   code->op = EXEC_SELECT;
6856   gfc_add_component_ref (code->expr1, "$vindex");
6857
6858   /* Loop over TYPE IS / CLASS IS cases.  */
6859   for (body = code->block; body; body = body->block)
6860     {
6861       c = body->ext.case_list;
6862       if (c->ts.type == BT_DERIVED)
6863         c->low = c->high = gfc_int_expr (c->ts.u.derived->vindex);
6864       else if (c->ts.type == BT_CLASS)
6865         /* Currently IS CLASS blocks are simply ignored.
6866            TODO: Implement IS CLASS.  */
6867         c->unreachable = 1;
6868
6869       if (c->ts.type != BT_DERIVED)
6870         continue;
6871       /* Assign temporary to selector.  */
6872       sprintf (name, "tmp$%s", c->ts.u.derived->name);
6873       st = gfc_find_symtree (ns->sym_root, name);
6874       new_st = gfc_get_code ();
6875       new_st->op = EXEC_POINTER_ASSIGN;
6876       new_st->expr1 = gfc_get_variable_expr (st);
6877       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
6878       gfc_add_component_ref (new_st->expr2, "$data");
6879       new_st->next = body->next;
6880       body->next = new_st;
6881     }
6882
6883   /* Eliminate dead blocks.  */
6884   for (body = code; body && body->block; body = body->block)
6885     {
6886       if (body->block->ext.case_list->unreachable)
6887         {
6888           /* Cut the unreachable block from the code chain.  */
6889           gfc_code *cd = body->block;
6890           body->block = cd->block;
6891           /* Kill the dead block, but not the blocks below it.  */
6892           cd->block = NULL;
6893           gfc_free_statements (cd);
6894         }
6895     }
6896
6897   resolve_select (code);
6898
6899 }
6900
6901
6902 /* Resolve a transfer statement. This is making sure that:
6903    -- a derived type being transferred has only non-pointer components
6904    -- a derived type being transferred doesn't have private components, unless 
6905       it's being transferred from the module where the type was defined
6906    -- we're not trying to transfer a whole assumed size array.  */
6907
6908 static void
6909 resolve_transfer (gfc_code *code)
6910 {
6911   gfc_typespec *ts;
6912   gfc_symbol *sym;
6913   gfc_ref *ref;
6914   gfc_expr *exp;
6915
6916   exp = code->expr1;
6917
6918   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
6919     return;
6920
6921   sym = exp->symtree->n.sym;
6922   ts = &sym->ts;
6923
6924   /* Go to actual component transferred.  */
6925   for (ref = code->expr1->ref; ref; ref = ref->next)
6926     if (ref->type == REF_COMPONENT)
6927       ts = &ref->u.c.component->ts;
6928
6929   if (ts->type == BT_DERIVED)
6930     {
6931       /* Check that transferred derived type doesn't contain POINTER
6932          components.  */
6933       if (ts->u.derived->attr.pointer_comp)
6934         {
6935           gfc_error ("Data transfer element at %L cannot have "
6936                      "POINTER components", &code->loc);
6937           return;
6938         }
6939
6940       if (ts->u.derived->attr.alloc_comp)
6941         {
6942           gfc_error ("Data transfer element at %L cannot have "
6943                      "ALLOCATABLE components", &code->loc);
6944           return;
6945         }
6946
6947       if (derived_inaccessible (ts->u.derived))
6948         {
6949           gfc_error ("Data transfer element at %L cannot have "
6950                      "PRIVATE components",&code->loc);
6951           return;
6952         }
6953     }
6954
6955   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
6956       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
6957     {
6958       gfc_error ("Data transfer element at %L cannot be a full reference to "
6959                  "an assumed-size array", &code->loc);
6960       return;
6961     }
6962 }
6963
6964
6965 /*********** Toplevel code resolution subroutines ***********/
6966
6967 /* Find the set of labels that are reachable from this block.  We also
6968    record the last statement in each block.  */
6969      
6970 static void
6971 find_reachable_labels (gfc_code *block)
6972 {
6973   gfc_code *c;
6974
6975   if (!block)
6976     return;
6977
6978   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
6979
6980   /* Collect labels in this block.  We don't keep those corresponding
6981      to END {IF|SELECT}, these are checked in resolve_branch by going
6982      up through the code_stack.  */
6983   for (c = block; c; c = c->next)
6984     {
6985       if (c->here && c->op != EXEC_END_BLOCK)
6986         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
6987     }
6988
6989   /* Merge with labels from parent block.  */
6990   if (cs_base->prev)
6991     {
6992       gcc_assert (cs_base->prev->reachable_labels);
6993       bitmap_ior_into (cs_base->reachable_labels,
6994                        cs_base->prev->reachable_labels);
6995     }
6996 }
6997
6998 /* Given a branch to a label, see if the branch is conforming.
6999    The code node describes where the branch is located.  */
7000
7001 static void
7002 resolve_branch (gfc_st_label *label, gfc_code *code)
7003 {
7004   code_stack *stack;
7005
7006   if (label == NULL)
7007     return;
7008
7009   /* Step one: is this a valid branching target?  */
7010
7011   if (label->defined == ST_LABEL_UNKNOWN)
7012     {
7013       gfc_error ("Label %d referenced at %L is never defined", label->value,
7014                  &label->where);
7015       return;
7016     }
7017
7018   if (label->defined != ST_LABEL_TARGET)
7019     {
7020       gfc_error ("Statement at %L is not a valid branch target statement "
7021                  "for the branch statement at %L", &label->where, &code->loc);
7022       return;
7023     }
7024
7025   /* Step two: make sure this branch is not a branch to itself ;-)  */
7026
7027   if (code->here == label)
7028     {
7029       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7030       return;
7031     }
7032
7033   /* Step three:  See if the label is in the same block as the
7034      branching statement.  The hard work has been done by setting up
7035      the bitmap reachable_labels.  */
7036
7037   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7038     return;
7039
7040   /* Step four:  If we haven't found the label in the bitmap, it may
7041     still be the label of the END of the enclosing block, in which
7042     case we find it by going up the code_stack.  */
7043
7044   for (stack = cs_base; stack; stack = stack->prev)
7045     if (stack->current->next && stack->current->next->here == label)
7046       break;
7047
7048   if (stack)
7049     {
7050       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7051       return;
7052     }
7053
7054   /* The label is not in an enclosing block, so illegal.  This was
7055      allowed in Fortran 66, so we allow it as extension.  No
7056      further checks are necessary in this case.  */
7057   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7058                   "as the GOTO statement at %L", &label->where,
7059                   &code->loc);
7060   return;
7061 }
7062
7063
7064 /* Check whether EXPR1 has the same shape as EXPR2.  */
7065
7066 static gfc_try
7067 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7068 {
7069   mpz_t shape[GFC_MAX_DIMENSIONS];
7070   mpz_t shape2[GFC_MAX_DIMENSIONS];
7071   gfc_try result = FAILURE;
7072   int i;
7073
7074   /* Compare the rank.  */
7075   if (expr1->rank != expr2->rank)
7076     return result;
7077
7078   /* Compare the size of each dimension.  */
7079   for (i=0; i<expr1->rank; i++)
7080     {
7081       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7082         goto ignore;
7083
7084       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7085         goto ignore;
7086
7087       if (mpz_cmp (shape[i], shape2[i]))
7088         goto over;
7089     }
7090
7091   /* When either of the two expression is an assumed size array, we
7092      ignore the comparison of dimension sizes.  */
7093 ignore:
7094   result = SUCCESS;
7095
7096 over:
7097   for (i--; i >= 0; i--)
7098     {
7099       mpz_clear (shape[i]);
7100       mpz_clear (shape2[i]);
7101     }
7102   return result;
7103 }
7104
7105
7106 /* Check whether a WHERE assignment target or a WHERE mask expression
7107    has the same shape as the outmost WHERE mask expression.  */
7108
7109 static void
7110 resolve_where (gfc_code *code, gfc_expr *mask)
7111 {
7112   gfc_code *cblock;
7113   gfc_code *cnext;
7114   gfc_expr *e = NULL;
7115
7116   cblock = code->block;
7117
7118   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7119      In case of nested WHERE, only the outmost one is stored.  */
7120   if (mask == NULL) /* outmost WHERE */
7121     e = cblock->expr1;
7122   else /* inner WHERE */
7123     e = mask;
7124
7125   while (cblock)
7126     {
7127       if (cblock->expr1)
7128         {
7129           /* Check if the mask-expr has a consistent shape with the
7130              outmost WHERE mask-expr.  */
7131           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7132             gfc_error ("WHERE mask at %L has inconsistent shape",
7133                        &cblock->expr1->where);
7134          }
7135
7136       /* the assignment statement of a WHERE statement, or the first
7137          statement in where-body-construct of a WHERE construct */
7138       cnext = cblock->next;
7139       while (cnext)
7140         {
7141           switch (cnext->op)
7142             {
7143             /* WHERE assignment statement */
7144             case EXEC_ASSIGN:
7145
7146               /* Check shape consistent for WHERE assignment target.  */
7147               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7148                gfc_error ("WHERE assignment target at %L has "
7149                           "inconsistent shape", &cnext->expr1->where);
7150               break;
7151
7152   
7153             case EXEC_ASSIGN_CALL:
7154               resolve_call (cnext);
7155               if (!cnext->resolved_sym->attr.elemental)
7156                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7157                           &cnext->ext.actual->expr->where);
7158               break;
7159
7160             /* WHERE or WHERE construct is part of a where-body-construct */
7161             case EXEC_WHERE:
7162               resolve_where (cnext, e);
7163               break;
7164
7165             default:
7166               gfc_error ("Unsupported statement inside WHERE at %L",
7167                          &cnext->loc);
7168             }
7169          /* the next statement within the same where-body-construct */
7170          cnext = cnext->next;
7171        }
7172     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7173     cblock = cblock->block;
7174   }
7175 }
7176
7177
7178 /* Resolve assignment in FORALL construct.
7179    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7180    FORALL index variables.  */
7181
7182 static void
7183 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7184 {
7185   int n;
7186
7187   for (n = 0; n < nvar; n++)
7188     {
7189       gfc_symbol *forall_index;
7190
7191       forall_index = var_expr[n]->symtree->n.sym;
7192
7193       /* Check whether the assignment target is one of the FORALL index
7194          variable.  */
7195       if ((code->expr1->expr_type == EXPR_VARIABLE)
7196           && (code->expr1->symtree->n.sym == forall_index))
7197         gfc_error ("Assignment to a FORALL index variable at %L",
7198                    &code->expr1->where);
7199       else
7200         {
7201           /* If one of the FORALL index variables doesn't appear in the
7202              assignment variable, then there could be a many-to-one
7203              assignment.  Emit a warning rather than an error because the
7204              mask could be resolving this problem.  */
7205           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7206             gfc_warning ("The FORALL with index '%s' is not used on the "
7207                          "left side of the assignment at %L and so might "
7208                          "cause multiple assignment to this object",
7209                          var_expr[n]->symtree->name, &code->expr1->where);
7210         }
7211     }
7212 }
7213
7214
7215 /* Resolve WHERE statement in FORALL construct.  */
7216
7217 static void
7218 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7219                                   gfc_expr **var_expr)
7220 {
7221   gfc_code *cblock;
7222   gfc_code *cnext;
7223
7224   cblock = code->block;
7225   while (cblock)
7226     {
7227       /* the assignment statement of a WHERE statement, or the first
7228          statement in where-body-construct of a WHERE construct */
7229       cnext = cblock->next;
7230       while (cnext)
7231         {
7232           switch (cnext->op)
7233             {
7234             /* WHERE assignment statement */
7235             case EXEC_ASSIGN:
7236               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7237               break;
7238   
7239             /* WHERE operator assignment statement */
7240             case EXEC_ASSIGN_CALL:
7241               resolve_call (cnext);
7242               if (!cnext->resolved_sym->attr.elemental)
7243                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7244                           &cnext->ext.actual->expr->where);
7245               break;
7246
7247             /* WHERE or WHERE construct is part of a where-body-construct */
7248             case EXEC_WHERE:
7249               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7250               break;
7251
7252             default:
7253               gfc_error ("Unsupported statement inside WHERE at %L",
7254                          &cnext->loc);
7255             }
7256           /* the next statement within the same where-body-construct */
7257           cnext = cnext->next;
7258         }
7259       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7260       cblock = cblock->block;
7261     }
7262 }
7263
7264
7265 /* Traverse the FORALL body to check whether the following errors exist:
7266    1. For assignment, check if a many-to-one assignment happens.
7267    2. For WHERE statement, check the WHERE body to see if there is any
7268       many-to-one assignment.  */
7269
7270 static void
7271 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7272 {
7273   gfc_code *c;
7274
7275   c = code->block->next;
7276   while (c)
7277     {
7278       switch (c->op)
7279         {
7280         case EXEC_ASSIGN:
7281         case EXEC_POINTER_ASSIGN:
7282           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7283           break;
7284
7285         case EXEC_ASSIGN_CALL:
7286           resolve_call (c);
7287           break;
7288
7289         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7290            there is no need to handle it here.  */
7291         case EXEC_FORALL:
7292           break;
7293         case EXEC_WHERE:
7294           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7295           break;
7296         default:
7297           break;
7298         }
7299       /* The next statement in the FORALL body.  */
7300       c = c->next;
7301     }
7302 }
7303
7304
7305 /* Counts the number of iterators needed inside a forall construct, including
7306    nested forall constructs. This is used to allocate the needed memory 
7307    in gfc_resolve_forall.  */
7308
7309 static int 
7310 gfc_count_forall_iterators (gfc_code *code)
7311 {
7312   int max_iters, sub_iters, current_iters;
7313   gfc_forall_iterator *fa;
7314
7315   gcc_assert(code->op == EXEC_FORALL);
7316   max_iters = 0;
7317   current_iters = 0;
7318
7319   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7320     current_iters ++;
7321   
7322   code = code->block->next;
7323
7324   while (code)
7325     {          
7326       if (code->op == EXEC_FORALL)
7327         {
7328           sub_iters = gfc_count_forall_iterators (code);
7329           if (sub_iters > max_iters)
7330             max_iters = sub_iters;
7331         }
7332       code = code->next;
7333     }
7334
7335   return current_iters + max_iters;
7336 }
7337
7338
7339 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7340    gfc_resolve_forall_body to resolve the FORALL body.  */
7341
7342 static void
7343 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7344 {
7345   static gfc_expr **var_expr;
7346   static int total_var = 0;
7347   static int nvar = 0;
7348   int old_nvar, tmp;
7349   gfc_forall_iterator *fa;
7350   int i;
7351
7352   old_nvar = nvar;
7353
7354   /* Start to resolve a FORALL construct   */
7355   if (forall_save == 0)
7356     {
7357       /* Count the total number of FORALL index in the nested FORALL
7358          construct in order to allocate the VAR_EXPR with proper size.  */
7359       total_var = gfc_count_forall_iterators (code);
7360
7361       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7362       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7363     }
7364
7365   /* The information about FORALL iterator, including FORALL index start, end
7366      and stride. The FORALL index can not appear in start, end or stride.  */
7367   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7368     {
7369       /* Check if any outer FORALL index name is the same as the current
7370          one.  */
7371       for (i = 0; i < nvar; i++)
7372         {
7373           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7374             {
7375               gfc_error ("An outer FORALL construct already has an index "
7376                          "with this name %L", &fa->var->where);
7377             }
7378         }
7379
7380       /* Record the current FORALL index.  */
7381       var_expr[nvar] = gfc_copy_expr (fa->var);
7382
7383       nvar++;
7384
7385       /* No memory leak.  */
7386       gcc_assert (nvar <= total_var);
7387     }
7388
7389   /* Resolve the FORALL body.  */
7390   gfc_resolve_forall_body (code, nvar, var_expr);
7391
7392   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7393   gfc_resolve_blocks (code->block, ns);
7394
7395   tmp = nvar;
7396   nvar = old_nvar;
7397   /* Free only the VAR_EXPRs allocated in this frame.  */
7398   for (i = nvar; i < tmp; i++)
7399      gfc_free_expr (var_expr[i]);
7400
7401   if (nvar == 0)
7402     {
7403       /* We are in the outermost FORALL construct.  */
7404       gcc_assert (forall_save == 0);
7405
7406       /* VAR_EXPR is not needed any more.  */
7407       gfc_free (var_expr);
7408       total_var = 0;
7409     }
7410 }
7411
7412
7413 /* Resolve a BLOCK construct statement.  */
7414
7415 static void
7416 resolve_block_construct (gfc_code* code)
7417 {
7418   /* Eventually, we may want to do some checks here or handle special stuff.
7419      But so far the only thing we can do is resolving the local namespace.  */
7420
7421   gfc_resolve (code->ext.ns);
7422 }
7423
7424
7425 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
7426    DO code nodes.  */
7427
7428 static void resolve_code (gfc_code *, gfc_namespace *);
7429
7430 void
7431 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
7432 {
7433   gfc_try t;
7434
7435   for (; b; b = b->block)
7436     {
7437       t = gfc_resolve_expr (b->expr1);
7438       if (gfc_resolve_expr (b->expr2) == FAILURE)
7439         t = FAILURE;
7440
7441       switch (b->op)
7442         {
7443         case EXEC_IF:
7444           if (t == SUCCESS && b->expr1 != NULL
7445               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
7446             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7447                        &b->expr1->where);
7448           break;
7449
7450         case EXEC_WHERE:
7451           if (t == SUCCESS
7452               && b->expr1 != NULL
7453               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
7454             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
7455                        &b->expr1->where);
7456           break;
7457
7458         case EXEC_GOTO:
7459           resolve_branch (b->label1, b);
7460           break;
7461
7462         case EXEC_BLOCK:
7463           resolve_block_construct (b);
7464           break;
7465
7466         case EXEC_SELECT:
7467         case EXEC_SELECT_TYPE:
7468         case EXEC_FORALL:
7469         case EXEC_DO:
7470         case EXEC_DO_WHILE:
7471         case EXEC_READ:
7472         case EXEC_WRITE:
7473         case EXEC_IOLENGTH:
7474         case EXEC_WAIT:
7475           break;
7476
7477         case EXEC_OMP_ATOMIC:
7478         case EXEC_OMP_CRITICAL:
7479         case EXEC_OMP_DO:
7480         case EXEC_OMP_MASTER:
7481         case EXEC_OMP_ORDERED:
7482         case EXEC_OMP_PARALLEL:
7483         case EXEC_OMP_PARALLEL_DO:
7484         case EXEC_OMP_PARALLEL_SECTIONS:
7485         case EXEC_OMP_PARALLEL_WORKSHARE:
7486         case EXEC_OMP_SECTIONS:
7487         case EXEC_OMP_SINGLE:
7488         case EXEC_OMP_TASK:
7489         case EXEC_OMP_TASKWAIT:
7490         case EXEC_OMP_WORKSHARE:
7491           break;
7492
7493         default:
7494           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
7495         }
7496
7497       resolve_code (b->next, ns);
7498     }
7499 }
7500
7501
7502 /* Does everything to resolve an ordinary assignment.  Returns true
7503    if this is an interface assignment.  */
7504 static bool
7505 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
7506 {
7507   bool rval = false;
7508   gfc_expr *lhs;
7509   gfc_expr *rhs;
7510   int llen = 0;
7511   int rlen = 0;
7512   int n;
7513   gfc_ref *ref;
7514
7515   if (gfc_extend_assign (code, ns) == SUCCESS)
7516     {
7517       gfc_symbol* assign_proc;
7518       gfc_expr** rhsptr;
7519
7520       if (code->op == EXEC_ASSIGN_CALL)
7521         {
7522           lhs = code->ext.actual->expr;
7523           rhsptr = &code->ext.actual->next->expr;
7524           assign_proc = code->symtree->n.sym;
7525         }
7526       else
7527         {
7528           gfc_actual_arglist* args;
7529           gfc_typebound_proc* tbp;
7530
7531           gcc_assert (code->op == EXEC_COMPCALL);
7532
7533           args = code->expr1->value.compcall.actual;
7534           lhs = args->expr;
7535           rhsptr = &args->next->expr;
7536
7537           tbp = code->expr1->value.compcall.tbp;
7538           gcc_assert (!tbp->is_generic);
7539           assign_proc = tbp->u.specific->n.sym;
7540         }
7541
7542       /* Make a temporary rhs when there is a default initializer
7543          and rhs is the same symbol as the lhs.  */
7544       if ((*rhsptr)->expr_type == EXPR_VARIABLE
7545             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
7546             && has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
7547             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
7548         *rhsptr = gfc_get_parentheses (*rhsptr);
7549
7550       return true;
7551     }
7552
7553   lhs = code->expr1;
7554   rhs = code->expr2;
7555
7556   if (rhs->is_boz
7557       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
7558                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
7559                          &code->loc) == FAILURE)
7560     return false;
7561
7562   /* Handle the case of a BOZ literal on the RHS.  */
7563   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
7564     {
7565       int rc;
7566       if (gfc_option.warn_surprising)
7567         gfc_warning ("BOZ literal at %L is bitwise transferred "
7568                      "non-integer symbol '%s'", &code->loc,
7569                      lhs->symtree->n.sym->name);
7570
7571       if (!gfc_convert_boz (rhs, &lhs->ts))
7572         return false;
7573       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
7574         {
7575           if (rc == ARITH_UNDERFLOW)
7576             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
7577                        ". This check can be disabled with the option "
7578                        "-fno-range-check", &rhs->where);
7579           else if (rc == ARITH_OVERFLOW)
7580             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
7581                        ". This check can be disabled with the option "
7582                        "-fno-range-check", &rhs->where);
7583           else if (rc == ARITH_NAN)
7584             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
7585                        ". This check can be disabled with the option "
7586                        "-fno-range-check", &rhs->where);
7587           return false;
7588         }
7589     }
7590
7591
7592   if (lhs->ts.type == BT_CHARACTER
7593         && gfc_option.warn_character_truncation)
7594     {
7595       if (lhs->ts.u.cl != NULL
7596             && lhs->ts.u.cl->length != NULL
7597             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7598         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
7599
7600       if (rhs->expr_type == EXPR_CONSTANT)
7601         rlen = rhs->value.character.length;
7602
7603       else if (rhs->ts.u.cl != NULL
7604                  && rhs->ts.u.cl->length != NULL
7605                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7606         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
7607
7608       if (rlen && llen && rlen > llen)
7609         gfc_warning_now ("CHARACTER expression will be truncated "
7610                          "in assignment (%d/%d) at %L",
7611                          llen, rlen, &code->loc);
7612     }
7613
7614   /* Ensure that a vector index expression for the lvalue is evaluated
7615      to a temporary if the lvalue symbol is referenced in it.  */
7616   if (lhs->rank)
7617     {
7618       for (ref = lhs->ref; ref; ref= ref->next)
7619         if (ref->type == REF_ARRAY)
7620           {
7621             for (n = 0; n < ref->u.ar.dimen; n++)
7622               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
7623                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
7624                                            ref->u.ar.start[n]))
7625                 ref->u.ar.start[n]
7626                         = gfc_get_parentheses (ref->u.ar.start[n]);
7627           }
7628     }
7629
7630   if (gfc_pure (NULL))
7631     {
7632       if (gfc_impure_variable (lhs->symtree->n.sym))
7633         {
7634           gfc_error ("Cannot assign to variable '%s' in PURE "
7635                      "procedure at %L",
7636                       lhs->symtree->n.sym->name,
7637                       &lhs->where);
7638           return rval;
7639         }
7640
7641       if (lhs->ts.type == BT_DERIVED
7642             && lhs->expr_type == EXPR_VARIABLE
7643             && lhs->ts.u.derived->attr.pointer_comp
7644             && gfc_impure_variable (rhs->symtree->n.sym))
7645         {
7646           gfc_error ("The impure variable at %L is assigned to "
7647                      "a derived type variable with a POINTER "
7648                      "component in a PURE procedure (12.6)",
7649                      &rhs->where);
7650           return rval;
7651         }
7652     }
7653
7654   /* F03:7.4.1.2.  */
7655   if (lhs->ts.type == BT_CLASS)
7656     {
7657       gfc_error ("Variable must not be polymorphic in assignment at %L",
7658                  &lhs->where);
7659       return false;
7660     }
7661
7662   gfc_check_assign (lhs, rhs, 1);
7663   return false;
7664 }
7665
7666
7667 /* Given a block of code, recursively resolve everything pointed to by this
7668    code block.  */
7669
7670 static void
7671 resolve_code (gfc_code *code, gfc_namespace *ns)
7672 {
7673   int omp_workshare_save;
7674   int forall_save;
7675   code_stack frame;
7676   gfc_try t;
7677
7678   frame.prev = cs_base;
7679   frame.head = code;
7680   cs_base = &frame;
7681
7682   find_reachable_labels (code);
7683
7684   for (; code; code = code->next)
7685     {
7686       frame.current = code;
7687       forall_save = forall_flag;
7688
7689       if (code->op == EXEC_FORALL)
7690         {
7691           forall_flag = 1;
7692           gfc_resolve_forall (code, ns, forall_save);
7693           forall_flag = 2;
7694         }
7695       else if (code->block)
7696         {
7697           omp_workshare_save = -1;
7698           switch (code->op)
7699             {
7700             case EXEC_OMP_PARALLEL_WORKSHARE:
7701               omp_workshare_save = omp_workshare_flag;
7702               omp_workshare_flag = 1;
7703               gfc_resolve_omp_parallel_blocks (code, ns);
7704               break;
7705             case EXEC_OMP_PARALLEL:
7706             case EXEC_OMP_PARALLEL_DO:
7707             case EXEC_OMP_PARALLEL_SECTIONS:
7708             case EXEC_OMP_TASK:
7709               omp_workshare_save = omp_workshare_flag;
7710               omp_workshare_flag = 0;
7711               gfc_resolve_omp_parallel_blocks (code, ns);
7712               break;
7713             case EXEC_OMP_DO:
7714               gfc_resolve_omp_do_blocks (code, ns);
7715               break;
7716             case EXEC_OMP_WORKSHARE:
7717               omp_workshare_save = omp_workshare_flag;
7718               omp_workshare_flag = 1;
7719               /* FALLTHROUGH */
7720             default:
7721               gfc_resolve_blocks (code->block, ns);
7722               break;
7723             }
7724
7725           if (omp_workshare_save != -1)
7726             omp_workshare_flag = omp_workshare_save;
7727         }
7728
7729       t = SUCCESS;
7730       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
7731         t = gfc_resolve_expr (code->expr1);
7732       forall_flag = forall_save;
7733
7734       if (gfc_resolve_expr (code->expr2) == FAILURE)
7735         t = FAILURE;
7736
7737       switch (code->op)
7738         {
7739         case EXEC_NOP:
7740         case EXEC_END_BLOCK:
7741         case EXEC_CYCLE:
7742         case EXEC_PAUSE:
7743         case EXEC_STOP:
7744         case EXEC_EXIT:
7745         case EXEC_CONTINUE:
7746         case EXEC_DT_END:
7747         case EXEC_ASSIGN_CALL:
7748           break;
7749
7750         case EXEC_ENTRY:
7751           /* Keep track of which entry we are up to.  */
7752           current_entry_id = code->ext.entry->id;
7753           break;
7754
7755         case EXEC_WHERE:
7756           resolve_where (code, NULL);
7757           break;
7758
7759         case EXEC_GOTO:
7760           if (code->expr1 != NULL)
7761             {
7762               if (code->expr1->ts.type != BT_INTEGER)
7763                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
7764                            "INTEGER variable", &code->expr1->where);
7765               else if (code->expr1->symtree->n.sym->attr.assign != 1)
7766                 gfc_error ("Variable '%s' has not been assigned a target "
7767                            "label at %L", code->expr1->symtree->n.sym->name,
7768                            &code->expr1->where);
7769             }
7770           else
7771             resolve_branch (code->label1, code);
7772           break;
7773
7774         case EXEC_RETURN:
7775           if (code->expr1 != NULL
7776                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
7777             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
7778                        "INTEGER return specifier", &code->expr1->where);
7779           break;
7780
7781         case EXEC_INIT_ASSIGN:
7782         case EXEC_END_PROCEDURE:
7783           break;
7784
7785         case EXEC_ASSIGN:
7786           if (t == FAILURE)
7787             break;
7788
7789           if (resolve_ordinary_assign (code, ns))
7790             {
7791               if (code->op == EXEC_COMPCALL)
7792                 goto compcall;
7793               else
7794                 goto call;
7795             }
7796           break;
7797
7798         case EXEC_LABEL_ASSIGN:
7799           if (code->label1->defined == ST_LABEL_UNKNOWN)
7800             gfc_error ("Label %d referenced at %L is never defined",
7801                        code->label1->value, &code->label1->where);
7802           if (t == SUCCESS
7803               && (code->expr1->expr_type != EXPR_VARIABLE
7804                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
7805                   || code->expr1->symtree->n.sym->ts.kind
7806                      != gfc_default_integer_kind
7807                   || code->expr1->symtree->n.sym->as != NULL))
7808             gfc_error ("ASSIGN statement at %L requires a scalar "
7809                        "default INTEGER variable", &code->expr1->where);
7810           break;
7811
7812         case EXEC_POINTER_ASSIGN:
7813           if (t == FAILURE)
7814             break;
7815
7816           gfc_check_pointer_assign (code->expr1, code->expr2);
7817           break;
7818
7819         case EXEC_ARITHMETIC_IF:
7820           if (t == SUCCESS
7821               && code->expr1->ts.type != BT_INTEGER
7822               && code->expr1->ts.type != BT_REAL)
7823             gfc_error ("Arithmetic IF statement at %L requires a numeric "
7824                        "expression", &code->expr1->where);
7825
7826           resolve_branch (code->label1, code);
7827           resolve_branch (code->label2, code);
7828           resolve_branch (code->label3, code);
7829           break;
7830
7831         case EXEC_IF:
7832           if (t == SUCCESS && code->expr1 != NULL
7833               && (code->expr1->ts.type != BT_LOGICAL
7834                   || code->expr1->rank != 0))
7835             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7836                        &code->expr1->where);
7837           break;
7838
7839         case EXEC_CALL:
7840         call:
7841           resolve_call (code);
7842           break;
7843
7844         case EXEC_COMPCALL:
7845         compcall:
7846           if (code->expr1->symtree
7847                 && code->expr1->symtree->n.sym->ts.type == BT_CLASS)
7848             resolve_class_typebound_call (code);
7849           else
7850             resolve_typebound_call (code);
7851           break;
7852
7853         case EXEC_CALL_PPC:
7854           resolve_ppc_call (code);
7855           break;
7856
7857         case EXEC_SELECT:
7858           /* Select is complicated. Also, a SELECT construct could be
7859              a transformed computed GOTO.  */
7860           resolve_select (code);
7861           break;
7862
7863         case EXEC_SELECT_TYPE:
7864           resolve_select_type (code);
7865           break;
7866
7867         case EXEC_BLOCK:
7868           gfc_resolve (code->ext.ns);
7869           break;
7870
7871         case EXEC_DO:
7872           if (code->ext.iterator != NULL)
7873             {
7874               gfc_iterator *iter = code->ext.iterator;
7875               if (gfc_resolve_iterator (iter, true) != FAILURE)
7876                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
7877             }
7878           break;
7879
7880         case EXEC_DO_WHILE:
7881           if (code->expr1 == NULL)
7882             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
7883           if (t == SUCCESS
7884               && (code->expr1->rank != 0
7885                   || code->expr1->ts.type != BT_LOGICAL))
7886             gfc_error ("Exit condition of DO WHILE loop at %L must be "
7887                        "a scalar LOGICAL expression", &code->expr1->where);
7888           break;
7889
7890         case EXEC_ALLOCATE:
7891           if (t == SUCCESS)
7892             resolve_allocate_deallocate (code, "ALLOCATE");
7893
7894           break;
7895
7896         case EXEC_DEALLOCATE:
7897           if (t == SUCCESS)
7898             resolve_allocate_deallocate (code, "DEALLOCATE");
7899
7900           break;
7901
7902         case EXEC_OPEN:
7903           if (gfc_resolve_open (code->ext.open) == FAILURE)
7904             break;
7905
7906           resolve_branch (code->ext.open->err, code);
7907           break;
7908
7909         case EXEC_CLOSE:
7910           if (gfc_resolve_close (code->ext.close) == FAILURE)
7911             break;
7912
7913           resolve_branch (code->ext.close->err, code);
7914           break;
7915
7916         case EXEC_BACKSPACE:
7917         case EXEC_ENDFILE:
7918         case EXEC_REWIND:
7919         case EXEC_FLUSH:
7920           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
7921             break;
7922
7923           resolve_branch (code->ext.filepos->err, code);
7924           break;
7925
7926         case EXEC_INQUIRE:
7927           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
7928               break;
7929
7930           resolve_branch (code->ext.inquire->err, code);
7931           break;
7932
7933         case EXEC_IOLENGTH:
7934           gcc_assert (code->ext.inquire != NULL);
7935           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
7936             break;
7937
7938           resolve_branch (code->ext.inquire->err, code);
7939           break;
7940
7941         case EXEC_WAIT:
7942           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
7943             break;
7944
7945           resolve_branch (code->ext.wait->err, code);
7946           resolve_branch (code->ext.wait->end, code);
7947           resolve_branch (code->ext.wait->eor, code);
7948           break;
7949
7950         case EXEC_READ:
7951         case EXEC_WRITE:
7952           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
7953             break;
7954
7955           resolve_branch (code->ext.dt->err, code);
7956           resolve_branch (code->ext.dt->end, code);
7957           resolve_branch (code->ext.dt->eor, code);
7958           break;
7959
7960         case EXEC_TRANSFER:
7961           resolve_transfer (code);
7962           break;
7963
7964         case EXEC_FORALL:
7965           resolve_forall_iterators (code->ext.forall_iterator);
7966
7967           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
7968             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
7969                        "expression", &code->expr1->where);
7970           break;
7971
7972         case EXEC_OMP_ATOMIC:
7973         case EXEC_OMP_BARRIER:
7974         case EXEC_OMP_CRITICAL:
7975         case EXEC_OMP_FLUSH:
7976         case EXEC_OMP_DO:
7977         case EXEC_OMP_MASTER:
7978         case EXEC_OMP_ORDERED:
7979         case EXEC_OMP_SECTIONS:
7980         case EXEC_OMP_SINGLE:
7981         case EXEC_OMP_TASKWAIT:
7982         case EXEC_OMP_WORKSHARE:
7983           gfc_resolve_omp_directive (code, ns);
7984           break;
7985
7986         case EXEC_OMP_PARALLEL:
7987         case EXEC_OMP_PARALLEL_DO:
7988         case EXEC_OMP_PARALLEL_SECTIONS:
7989         case EXEC_OMP_PARALLEL_WORKSHARE:
7990         case EXEC_OMP_TASK:
7991           omp_workshare_save = omp_workshare_flag;
7992           omp_workshare_flag = 0;
7993           gfc_resolve_omp_directive (code, ns);
7994           omp_workshare_flag = omp_workshare_save;
7995           break;
7996
7997         default:
7998           gfc_internal_error ("resolve_code(): Bad statement code");
7999         }
8000     }
8001
8002   cs_base = frame.prev;
8003 }
8004
8005
8006 /* Resolve initial values and make sure they are compatible with
8007    the variable.  */
8008
8009 static void
8010 resolve_values (gfc_symbol *sym)
8011 {
8012   if (sym->value == NULL)
8013     return;
8014
8015   if (gfc_resolve_expr (sym->value) == FAILURE)
8016     return;
8017
8018   gfc_check_assign_symbol (sym, sym->value);
8019 }
8020
8021
8022 /* Verify the binding labels for common blocks that are BIND(C).  The label
8023    for a BIND(C) common block must be identical in all scoping units in which
8024    the common block is declared.  Further, the binding label can not collide
8025    with any other global entity in the program.  */
8026
8027 static void
8028 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8029 {
8030   if (comm_block_tree->n.common->is_bind_c == 1)
8031     {
8032       gfc_gsymbol *binding_label_gsym;
8033       gfc_gsymbol *comm_name_gsym;
8034
8035       /* See if a global symbol exists by the common block's name.  It may
8036          be NULL if the common block is use-associated.  */
8037       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8038                                          comm_block_tree->n.common->name);
8039       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8040         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8041                    "with the global entity '%s' at %L",
8042                    comm_block_tree->n.common->binding_label,
8043                    comm_block_tree->n.common->name,
8044                    &(comm_block_tree->n.common->where),
8045                    comm_name_gsym->name, &(comm_name_gsym->where));
8046       else if (comm_name_gsym != NULL
8047                && strcmp (comm_name_gsym->name,
8048                           comm_block_tree->n.common->name) == 0)
8049         {
8050           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8051              as expected.  */
8052           if (comm_name_gsym->binding_label == NULL)
8053             /* No binding label for common block stored yet; save this one.  */
8054             comm_name_gsym->binding_label =
8055               comm_block_tree->n.common->binding_label;
8056           else
8057             if (strcmp (comm_name_gsym->binding_label,
8058                         comm_block_tree->n.common->binding_label) != 0)
8059               {
8060                 /* Common block names match but binding labels do not.  */
8061                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8062                            "does not match the binding label '%s' for common "
8063                            "block '%s' at %L",
8064                            comm_block_tree->n.common->binding_label,
8065                            comm_block_tree->n.common->name,
8066                            &(comm_block_tree->n.common->where),
8067                            comm_name_gsym->binding_label,
8068                            comm_name_gsym->name,
8069                            &(comm_name_gsym->where));
8070                 return;
8071               }
8072         }
8073
8074       /* There is no binding label (NAME="") so we have nothing further to
8075          check and nothing to add as a global symbol for the label.  */
8076       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8077         return;
8078       
8079       binding_label_gsym =
8080         gfc_find_gsymbol (gfc_gsym_root,
8081                           comm_block_tree->n.common->binding_label);
8082       if (binding_label_gsym == NULL)
8083         {
8084           /* Need to make a global symbol for the binding label to prevent
8085              it from colliding with another.  */
8086           binding_label_gsym =
8087             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8088           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8089           binding_label_gsym->type = GSYM_COMMON;
8090         }
8091       else
8092         {
8093           /* If comm_name_gsym is NULL, the name common block is use
8094              associated and the name could be colliding.  */
8095           if (binding_label_gsym->type != GSYM_COMMON)
8096             gfc_error ("Binding label '%s' for common block '%s' at %L "
8097                        "collides with the global entity '%s' at %L",
8098                        comm_block_tree->n.common->binding_label,
8099                        comm_block_tree->n.common->name,
8100                        &(comm_block_tree->n.common->where),
8101                        binding_label_gsym->name,
8102                        &(binding_label_gsym->where));
8103           else if (comm_name_gsym != NULL
8104                    && (strcmp (binding_label_gsym->name,
8105                                comm_name_gsym->binding_label) != 0)
8106                    && (strcmp (binding_label_gsym->sym_name,
8107                                comm_name_gsym->name) != 0))
8108             gfc_error ("Binding label '%s' for common block '%s' at %L "
8109                        "collides with global entity '%s' at %L",
8110                        binding_label_gsym->name, binding_label_gsym->sym_name,
8111                        &(comm_block_tree->n.common->where),
8112                        comm_name_gsym->name, &(comm_name_gsym->where));
8113         }
8114     }
8115   
8116   return;
8117 }
8118
8119
8120 /* Verify any BIND(C) derived types in the namespace so we can report errors
8121    for them once, rather than for each variable declared of that type.  */
8122
8123 static void
8124 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8125 {
8126   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8127       && derived_sym->attr.is_bind_c == 1)
8128     verify_bind_c_derived_type (derived_sym);
8129   
8130   return;
8131 }
8132
8133
8134 /* Verify that any binding labels used in a given namespace do not collide 
8135    with the names or binding labels of any global symbols.  */
8136
8137 static void
8138 gfc_verify_binding_labels (gfc_symbol *sym)
8139 {
8140   int has_error = 0;
8141   
8142   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8143       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8144     {
8145       gfc_gsymbol *bind_c_sym;
8146
8147       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8148       if (bind_c_sym != NULL 
8149           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8150         {
8151           if (sym->attr.if_source == IFSRC_DECL 
8152               && (bind_c_sym->type != GSYM_SUBROUTINE 
8153                   && bind_c_sym->type != GSYM_FUNCTION) 
8154               && ((sym->attr.contained == 1 
8155                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8156                   || (sym->attr.use_assoc == 1 
8157                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8158             {
8159               /* Make sure global procedures don't collide with anything.  */
8160               gfc_error ("Binding label '%s' at %L collides with the global "
8161                          "entity '%s' at %L", sym->binding_label,
8162                          &(sym->declared_at), bind_c_sym->name,
8163                          &(bind_c_sym->where));
8164               has_error = 1;
8165             }
8166           else if (sym->attr.contained == 0 
8167                    && (sym->attr.if_source == IFSRC_IFBODY 
8168                        && sym->attr.flavor == FL_PROCEDURE) 
8169                    && (bind_c_sym->sym_name != NULL 
8170                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8171             {
8172               /* Make sure procedures in interface bodies don't collide.  */
8173               gfc_error ("Binding label '%s' in interface body at %L collides "
8174                          "with the global entity '%s' at %L",
8175                          sym->binding_label,
8176                          &(sym->declared_at), bind_c_sym->name,
8177                          &(bind_c_sym->where));
8178               has_error = 1;
8179             }
8180           else if (sym->attr.contained == 0 
8181                    && sym->attr.if_source == IFSRC_UNKNOWN)
8182             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8183                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8184                 || sym->attr.use_assoc == 0)
8185               {
8186                 gfc_error ("Binding label '%s' at %L collides with global "
8187                            "entity '%s' at %L", sym->binding_label,
8188                            &(sym->declared_at), bind_c_sym->name,
8189                            &(bind_c_sym->where));
8190                 has_error = 1;
8191               }
8192
8193           if (has_error != 0)
8194             /* Clear the binding label to prevent checking multiple times.  */
8195             sym->binding_label[0] = '\0';
8196         }
8197       else if (bind_c_sym == NULL)
8198         {
8199           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8200           bind_c_sym->where = sym->declared_at;
8201           bind_c_sym->sym_name = sym->name;
8202
8203           if (sym->attr.use_assoc == 1)
8204             bind_c_sym->mod_name = sym->module;
8205           else
8206             if (sym->ns->proc_name != NULL)
8207               bind_c_sym->mod_name = sym->ns->proc_name->name;
8208
8209           if (sym->attr.contained == 0)
8210             {
8211               if (sym->attr.subroutine)
8212                 bind_c_sym->type = GSYM_SUBROUTINE;
8213               else if (sym->attr.function)
8214                 bind_c_sym->type = GSYM_FUNCTION;
8215             }
8216         }
8217     }
8218   return;
8219 }
8220
8221
8222 /* Resolve an index expression.  */
8223
8224 static gfc_try
8225 resolve_index_expr (gfc_expr *e)
8226 {
8227   if (gfc_resolve_expr (e) == FAILURE)
8228     return FAILURE;
8229
8230   if (gfc_simplify_expr (e, 0) == FAILURE)
8231     return FAILURE;
8232
8233   if (gfc_specification_expr (e) == FAILURE)
8234     return FAILURE;
8235
8236   return SUCCESS;
8237 }
8238
8239 /* Resolve a charlen structure.  */
8240
8241 static gfc_try
8242 resolve_charlen (gfc_charlen *cl)
8243 {
8244   int i, k;
8245
8246   if (cl->resolved)
8247     return SUCCESS;
8248
8249   cl->resolved = 1;
8250
8251   specification_expr = 1;
8252
8253   if (resolve_index_expr (cl->length) == FAILURE)
8254     {
8255       specification_expr = 0;
8256       return FAILURE;
8257     }
8258
8259   /* "If the character length parameter value evaluates to a negative
8260      value, the length of character entities declared is zero."  */
8261   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8262     {
8263       gfc_warning_now ("CHARACTER variable has zero length at %L",
8264                        &cl->length->where);
8265       gfc_replace_expr (cl->length, gfc_int_expr (0));
8266     }
8267
8268   /* Check that the character length is not too large.  */
8269   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8270   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8271       && cl->length->ts.type == BT_INTEGER
8272       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8273     {
8274       gfc_error ("String length at %L is too large", &cl->length->where);
8275       return FAILURE;
8276     }
8277
8278   return SUCCESS;
8279 }
8280
8281
8282 /* Test for non-constant shape arrays.  */
8283
8284 static bool
8285 is_non_constant_shape_array (gfc_symbol *sym)
8286 {
8287   gfc_expr *e;
8288   int i;
8289   bool not_constant;
8290
8291   not_constant = false;
8292   if (sym->as != NULL)
8293     {
8294       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8295          has not been simplified; parameter array references.  Do the
8296          simplification now.  */
8297       for (i = 0; i < sym->as->rank; i++)
8298         {
8299           e = sym->as->lower[i];
8300           if (e && (resolve_index_expr (e) == FAILURE
8301                     || !gfc_is_constant_expr (e)))
8302             not_constant = true;
8303
8304           e = sym->as->upper[i];
8305           if (e && (resolve_index_expr (e) == FAILURE
8306                     || !gfc_is_constant_expr (e)))
8307             not_constant = true;
8308         }
8309     }
8310   return not_constant;
8311 }
8312
8313 /* Given a symbol and an initialization expression, add code to initialize
8314    the symbol to the function entry.  */
8315 static void
8316 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8317 {
8318   gfc_expr *lval;
8319   gfc_code *init_st;
8320   gfc_namespace *ns = sym->ns;
8321
8322   /* Search for the function namespace if this is a contained
8323      function without an explicit result.  */
8324   if (sym->attr.function && sym == sym->result
8325       && sym->name != sym->ns->proc_name->name)
8326     {
8327       ns = ns->contained;
8328       for (;ns; ns = ns->sibling)
8329         if (strcmp (ns->proc_name->name, sym->name) == 0)
8330           break;
8331     }
8332
8333   if (ns == NULL)
8334     {
8335       gfc_free_expr (init);
8336       return;
8337     }
8338
8339   /* Build an l-value expression for the result.  */
8340   lval = gfc_lval_expr_from_sym (sym);
8341
8342   /* Add the code at scope entry.  */
8343   init_st = gfc_get_code ();
8344   init_st->next = ns->code;
8345   ns->code = init_st;
8346
8347   /* Assign the default initializer to the l-value.  */
8348   init_st->loc = sym->declared_at;
8349   init_st->op = EXEC_INIT_ASSIGN;
8350   init_st->expr1 = lval;
8351   init_st->expr2 = init;
8352 }
8353
8354 /* Assign the default initializer to a derived type variable or result.  */
8355
8356 static void
8357 apply_default_init (gfc_symbol *sym)
8358 {
8359   gfc_expr *init = NULL;
8360
8361   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8362     return;
8363
8364   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
8365     init = gfc_default_initializer (&sym->ts);
8366
8367   if (init == NULL)
8368     return;
8369
8370   build_init_assign (sym, init);
8371 }
8372
8373 /* Build an initializer for a local integer, real, complex, logical, or
8374    character variable, based on the command line flags finit-local-zero,
8375    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
8376    null if the symbol should not have a default initialization.  */
8377 static gfc_expr *
8378 build_default_init_expr (gfc_symbol *sym)
8379 {
8380   int char_len;
8381   gfc_expr *init_expr;
8382   int i;
8383
8384   /* These symbols should never have a default initialization.  */
8385   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
8386       || sym->attr.external
8387       || sym->attr.dummy
8388       || sym->attr.pointer
8389       || sym->attr.in_equivalence
8390       || sym->attr.in_common
8391       || sym->attr.data
8392       || sym->module
8393       || sym->attr.cray_pointee
8394       || sym->attr.cray_pointer)
8395     return NULL;
8396
8397   /* Now we'll try to build an initializer expression.  */
8398   init_expr = gfc_get_expr ();
8399   init_expr->expr_type = EXPR_CONSTANT;
8400   init_expr->ts.type = sym->ts.type;
8401   init_expr->ts.kind = sym->ts.kind;
8402   init_expr->where = sym->declared_at;
8403   
8404   /* We will only initialize integers, reals, complex, logicals, and
8405      characters, and only if the corresponding command-line flags
8406      were set.  Otherwise, we free init_expr and return null.  */
8407   switch (sym->ts.type)
8408     {    
8409     case BT_INTEGER:
8410       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
8411         mpz_init_set_si (init_expr->value.integer, 
8412                          gfc_option.flag_init_integer_value);
8413       else
8414         {
8415           gfc_free_expr (init_expr);
8416           init_expr = NULL;
8417         }
8418       break;
8419
8420     case BT_REAL:
8421       mpfr_init (init_expr->value.real);
8422       switch (gfc_option.flag_init_real)
8423         {
8424         case GFC_INIT_REAL_SNAN:
8425           init_expr->is_snan = 1;
8426           /* Fall through.  */
8427         case GFC_INIT_REAL_NAN:
8428           mpfr_set_nan (init_expr->value.real);
8429           break;
8430
8431         case GFC_INIT_REAL_INF:
8432           mpfr_set_inf (init_expr->value.real, 1);
8433           break;
8434
8435         case GFC_INIT_REAL_NEG_INF:
8436           mpfr_set_inf (init_expr->value.real, -1);
8437           break;
8438
8439         case GFC_INIT_REAL_ZERO:
8440           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
8441           break;
8442
8443         default:
8444           gfc_free_expr (init_expr);
8445           init_expr = NULL;
8446           break;
8447         }
8448       break;
8449           
8450     case BT_COMPLEX:
8451 #ifdef HAVE_mpc
8452       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
8453 #else
8454       mpfr_init (init_expr->value.complex.r);
8455       mpfr_init (init_expr->value.complex.i);
8456 #endif
8457       switch (gfc_option.flag_init_real)
8458         {
8459         case GFC_INIT_REAL_SNAN:
8460           init_expr->is_snan = 1;
8461           /* Fall through.  */
8462         case GFC_INIT_REAL_NAN:
8463           mpfr_set_nan (mpc_realref (init_expr->value.complex));
8464           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
8465           break;
8466
8467         case GFC_INIT_REAL_INF:
8468           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
8469           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
8470           break;
8471
8472         case GFC_INIT_REAL_NEG_INF:
8473           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
8474           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
8475           break;
8476
8477         case GFC_INIT_REAL_ZERO:
8478 #ifdef HAVE_mpc
8479           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
8480 #else
8481           mpfr_set_ui (init_expr->value.complex.r, 0.0, GFC_RND_MODE);
8482           mpfr_set_ui (init_expr->value.complex.i, 0.0, GFC_RND_MODE);
8483 #endif
8484           break;
8485
8486         default:
8487           gfc_free_expr (init_expr);
8488           init_expr = NULL;
8489           break;
8490         }
8491       break;
8492           
8493     case BT_LOGICAL:
8494       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
8495         init_expr->value.logical = 0;
8496       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
8497         init_expr->value.logical = 1;
8498       else
8499         {
8500           gfc_free_expr (init_expr);
8501           init_expr = NULL;
8502         }
8503       break;
8504           
8505     case BT_CHARACTER:
8506       /* For characters, the length must be constant in order to 
8507          create a default initializer.  */
8508       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
8509           && sym->ts.u.cl->length
8510           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8511         {
8512           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
8513           init_expr->value.character.length = char_len;
8514           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
8515           for (i = 0; i < char_len; i++)
8516             init_expr->value.character.string[i]
8517               = (unsigned char) gfc_option.flag_init_character_value;
8518         }
8519       else
8520         {
8521           gfc_free_expr (init_expr);
8522           init_expr = NULL;
8523         }
8524       break;
8525           
8526     default:
8527      gfc_free_expr (init_expr);
8528      init_expr = NULL;
8529     }
8530   return init_expr;
8531 }
8532
8533 /* Add an initialization expression to a local variable.  */
8534 static void
8535 apply_default_init_local (gfc_symbol *sym)
8536 {
8537   gfc_expr *init = NULL;
8538
8539   /* The symbol should be a variable or a function return value.  */
8540   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8541       || (sym->attr.function && sym->result != sym))
8542     return;
8543
8544   /* Try to build the initializer expression.  If we can't initialize
8545      this symbol, then init will be NULL.  */
8546   init = build_default_init_expr (sym);
8547   if (init == NULL)
8548     return;
8549
8550   /* For saved variables, we don't want to add an initializer at 
8551      function entry, so we just add a static initializer.  */
8552   if (sym->attr.save || sym->ns->save_all)
8553     {
8554       /* Don't clobber an existing initializer!  */
8555       gcc_assert (sym->value == NULL);
8556       sym->value = init;
8557       return;
8558     }
8559
8560   build_init_assign (sym, init);
8561 }
8562
8563 /* Resolution of common features of flavors variable and procedure.  */
8564
8565 static gfc_try
8566 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
8567 {
8568   /* Constraints on deferred shape variable.  */
8569   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
8570     {
8571       if (sym->attr.allocatable)
8572         {
8573           if (sym->attr.dimension)
8574             {
8575               gfc_error ("Allocatable array '%s' at %L must have "
8576                          "a deferred shape", sym->name, &sym->declared_at);
8577               return FAILURE;
8578             }
8579           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
8580                                    "may not be ALLOCATABLE", sym->name,
8581                                    &sym->declared_at) == FAILURE)
8582             return FAILURE;
8583         }
8584
8585       if (sym->attr.pointer && sym->attr.dimension)
8586         {
8587           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
8588                      sym->name, &sym->declared_at);
8589           return FAILURE;
8590         }
8591
8592     }
8593   else
8594     {
8595       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
8596           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
8597         {
8598           gfc_error ("Array '%s' at %L cannot have a deferred shape",
8599                      sym->name, &sym->declared_at);
8600           return FAILURE;
8601          }
8602     }
8603   return SUCCESS;
8604 }
8605
8606
8607 /* Additional checks for symbols with flavor variable and derived
8608    type.  To be called from resolve_fl_variable.  */
8609
8610 static gfc_try
8611 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
8612 {
8613   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
8614
8615   /* Check to see if a derived type is blocked from being host
8616      associated by the presence of another class I symbol in the same
8617      namespace.  14.6.1.3 of the standard and the discussion on
8618      comp.lang.fortran.  */
8619   if (sym->ns != sym->ts.u.derived->ns
8620       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
8621     {
8622       gfc_symbol *s;
8623       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
8624       if (s && s->attr.flavor != FL_DERIVED)
8625         {
8626           gfc_error ("The type '%s' cannot be host associated at %L "
8627                      "because it is blocked by an incompatible object "
8628                      "of the same name declared at %L",
8629                      sym->ts.u.derived->name, &sym->declared_at,
8630                      &s->declared_at);
8631           return FAILURE;
8632         }
8633     }
8634
8635   /* 4th constraint in section 11.3: "If an object of a type for which
8636      component-initialization is specified (R429) appears in the
8637      specification-part of a module and does not have the ALLOCATABLE
8638      or POINTER attribute, the object shall have the SAVE attribute."
8639
8640      The check for initializers is performed with
8641      has_default_initializer because gfc_default_initializer generates
8642      a hidden default for allocatable components.  */
8643   if (!(sym->value || no_init_flag) && sym->ns->proc_name
8644       && sym->ns->proc_name->attr.flavor == FL_MODULE
8645       && !sym->ns->save_all && !sym->attr.save
8646       && !sym->attr.pointer && !sym->attr.allocatable
8647       && has_default_initializer (sym->ts.u.derived))
8648     {
8649       gfc_error("Object '%s' at %L must have the SAVE attribute for "
8650                 "default initialization of a component",
8651                 sym->name, &sym->declared_at);
8652       return FAILURE;
8653     }
8654
8655   if (sym->ts.type == BT_CLASS)
8656     {
8657       /* C502.  */
8658       if (!gfc_type_is_extensible (sym->ts.u.derived->components->ts.u.derived))
8659         {
8660           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
8661                      sym->ts.u.derived->name, sym->name, &sym->declared_at);
8662           return FAILURE;
8663         }
8664
8665       /* C509.  */
8666       /* Assume that use associated symbols were checked in the module ns.  */ 
8667       if (!sym->attr.class_ok && !sym->attr.use_assoc)
8668         {
8669           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
8670                      "or pointer", sym->name, &sym->declared_at);
8671           return FAILURE;
8672         }
8673     }
8674
8675   /* Assign default initializer.  */
8676   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
8677       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
8678     {
8679       sym->value = gfc_default_initializer (&sym->ts);
8680     }
8681
8682   return SUCCESS;
8683 }
8684
8685
8686 /* Resolve symbols with flavor variable.  */
8687
8688 static gfc_try
8689 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
8690 {
8691   int no_init_flag, automatic_flag;
8692   gfc_expr *e;
8693   const char *auto_save_msg;
8694
8695   auto_save_msg = "Automatic object '%s' at %L cannot have the "
8696                   "SAVE attribute";
8697
8698   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
8699     return FAILURE;
8700
8701   /* Set this flag to check that variables are parameters of all entries.
8702      This check is effected by the call to gfc_resolve_expr through
8703      is_non_constant_shape_array.  */
8704   specification_expr = 1;
8705
8706   if (sym->ns->proc_name
8707       && (sym->ns->proc_name->attr.flavor == FL_MODULE
8708           || sym->ns->proc_name->attr.is_main_program)
8709       && !sym->attr.use_assoc
8710       && !sym->attr.allocatable
8711       && !sym->attr.pointer
8712       && is_non_constant_shape_array (sym))
8713     {
8714       /* The shape of a main program or module array needs to be
8715          constant.  */
8716       gfc_error ("The module or main program array '%s' at %L must "
8717                  "have constant shape", sym->name, &sym->declared_at);
8718       specification_expr = 0;
8719       return FAILURE;
8720     }
8721
8722   if (sym->ts.type == BT_CHARACTER)
8723     {
8724       /* Make sure that character string variables with assumed length are
8725          dummy arguments.  */
8726       e = sym->ts.u.cl->length;
8727       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
8728         {
8729           gfc_error ("Entity with assumed character length at %L must be a "
8730                      "dummy argument or a PARAMETER", &sym->declared_at);
8731           return FAILURE;
8732         }
8733
8734       if (e && sym->attr.save && !gfc_is_constant_expr (e))
8735         {
8736           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
8737           return FAILURE;
8738         }
8739
8740       if (!gfc_is_constant_expr (e)
8741           && !(e->expr_type == EXPR_VARIABLE
8742                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
8743           && sym->ns->proc_name
8744           && (sym->ns->proc_name->attr.flavor == FL_MODULE
8745               || sym->ns->proc_name->attr.is_main_program)
8746           && !sym->attr.use_assoc)
8747         {
8748           gfc_error ("'%s' at %L must have constant character length "
8749                      "in this context", sym->name, &sym->declared_at);
8750           return FAILURE;
8751         }
8752     }
8753
8754   if (sym->value == NULL && sym->attr.referenced)
8755     apply_default_init_local (sym); /* Try to apply a default initialization.  */
8756
8757   /* Determine if the symbol may not have an initializer.  */
8758   no_init_flag = automatic_flag = 0;
8759   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
8760       || sym->attr.intrinsic || sym->attr.result)
8761     no_init_flag = 1;
8762   else if (sym->attr.dimension && !sym->attr.pointer
8763            && is_non_constant_shape_array (sym))
8764     {
8765       no_init_flag = automatic_flag = 1;
8766
8767       /* Also, they must not have the SAVE attribute.
8768          SAVE_IMPLICIT is checked below.  */
8769       if (sym->attr.save == SAVE_EXPLICIT)
8770         {
8771           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
8772           return FAILURE;
8773         }
8774     }
8775
8776   /* Ensure that any initializer is simplified.  */
8777   if (sym->value)
8778     gfc_simplify_expr (sym->value, 1);
8779
8780   /* Reject illegal initializers.  */
8781   if (!sym->mark && sym->value)
8782     {
8783       if (sym->attr.allocatable)
8784         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
8785                    sym->name, &sym->declared_at);
8786       else if (sym->attr.external)
8787         gfc_error ("External '%s' at %L cannot have an initializer",
8788                    sym->name, &sym->declared_at);
8789       else if (sym->attr.dummy
8790         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
8791         gfc_error ("Dummy '%s' at %L cannot have an initializer",
8792                    sym->name, &sym->declared_at);
8793       else if (sym->attr.intrinsic)
8794         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
8795                    sym->name, &sym->declared_at);
8796       else if (sym->attr.result)
8797         gfc_error ("Function result '%s' at %L cannot have an initializer",
8798                    sym->name, &sym->declared_at);
8799       else if (automatic_flag)
8800         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
8801                    sym->name, &sym->declared_at);
8802       else
8803         goto no_init_error;
8804       return FAILURE;
8805     }
8806
8807 no_init_error:
8808   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
8809     return resolve_fl_variable_derived (sym, no_init_flag);
8810
8811   return SUCCESS;
8812 }
8813
8814
8815 /* Resolve a procedure.  */
8816
8817 static gfc_try
8818 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
8819 {
8820   gfc_formal_arglist *arg;
8821
8822   if (sym->attr.ambiguous_interfaces && !sym->attr.referenced)
8823     gfc_warning ("Although not referenced, '%s' at %L has ambiguous "
8824                  "interfaces", sym->name, &sym->declared_at);
8825
8826   if (sym->attr.function
8827       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
8828     return FAILURE;
8829
8830   if (sym->ts.type == BT_CHARACTER)
8831     {
8832       gfc_charlen *cl = sym->ts.u.cl;
8833
8834       if (cl && cl->length && gfc_is_constant_expr (cl->length)
8835              && resolve_charlen (cl) == FAILURE)
8836         return FAILURE;
8837
8838       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
8839         {
8840           if (sym->attr.proc == PROC_ST_FUNCTION)
8841             {
8842               gfc_error ("Character-valued statement function '%s' at %L must "
8843                          "have constant length", sym->name, &sym->declared_at);
8844               return FAILURE;
8845             }
8846
8847           if (sym->attr.external && sym->formal == NULL
8848               && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
8849             {
8850               gfc_error ("Automatic character length function '%s' at %L must "
8851                          "have an explicit interface", sym->name,
8852                          &sym->declared_at);
8853               return FAILURE;
8854             }
8855         }
8856     }
8857
8858   /* Ensure that derived type for are not of a private type.  Internal
8859      module procedures are excluded by 2.2.3.3 - i.e., they are not
8860      externally accessible and can access all the objects accessible in
8861      the host.  */
8862   if (!(sym->ns->parent
8863         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
8864       && gfc_check_access(sym->attr.access, sym->ns->default_access))
8865     {
8866       gfc_interface *iface;
8867
8868       for (arg = sym->formal; arg; arg = arg->next)
8869         {
8870           if (arg->sym
8871               && arg->sym->ts.type == BT_DERIVED
8872               && !arg->sym->ts.u.derived->attr.use_assoc
8873               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
8874                                     arg->sym->ts.u.derived->ns->default_access)
8875               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
8876                                  "PRIVATE type and cannot be a dummy argument"
8877                                  " of '%s', which is PUBLIC at %L",
8878                                  arg->sym->name, sym->name, &sym->declared_at)
8879                  == FAILURE)
8880             {
8881               /* Stop this message from recurring.  */
8882               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
8883               return FAILURE;
8884             }
8885         }
8886
8887       /* PUBLIC interfaces may expose PRIVATE procedures that take types
8888          PRIVATE to the containing module.  */
8889       for (iface = sym->generic; iface; iface = iface->next)
8890         {
8891           for (arg = iface->sym->formal; arg; arg = arg->next)
8892             {
8893               if (arg->sym
8894                   && arg->sym->ts.type == BT_DERIVED
8895                   && !arg->sym->ts.u.derived->attr.use_assoc
8896                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
8897                                         arg->sym->ts.u.derived->ns->default_access)
8898                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
8899                                      "'%s' in PUBLIC interface '%s' at %L "
8900                                      "takes dummy arguments of '%s' which is "
8901                                      "PRIVATE", iface->sym->name, sym->name,
8902                                      &iface->sym->declared_at,
8903                                      gfc_typename (&arg->sym->ts)) == FAILURE)
8904                 {
8905                   /* Stop this message from recurring.  */
8906                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
8907                   return FAILURE;
8908                 }
8909              }
8910         }
8911
8912       /* PUBLIC interfaces may expose PRIVATE procedures that take types
8913          PRIVATE to the containing module.  */
8914       for (iface = sym->generic; iface; iface = iface->next)
8915         {
8916           for (arg = iface->sym->formal; arg; arg = arg->next)
8917             {
8918               if (arg->sym
8919                   && arg->sym->ts.type == BT_DERIVED
8920                   && !arg->sym->ts.u.derived->attr.use_assoc
8921                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
8922                                         arg->sym->ts.u.derived->ns->default_access)
8923                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
8924                                      "'%s' in PUBLIC interface '%s' at %L "
8925                                      "takes dummy arguments of '%s' which is "
8926                                      "PRIVATE", iface->sym->name, sym->name,
8927                                      &iface->sym->declared_at,
8928                                      gfc_typename (&arg->sym->ts)) == FAILURE)
8929                 {
8930                   /* Stop this message from recurring.  */
8931                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
8932                   return FAILURE;
8933                 }
8934              }
8935         }
8936     }
8937
8938   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
8939       && !sym->attr.proc_pointer)
8940     {
8941       gfc_error ("Function '%s' at %L cannot have an initializer",
8942                  sym->name, &sym->declared_at);
8943       return FAILURE;
8944     }
8945
8946   /* An external symbol may not have an initializer because it is taken to be
8947      a procedure. Exception: Procedure Pointers.  */
8948   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
8949     {
8950       gfc_error ("External object '%s' at %L may not have an initializer",
8951                  sym->name, &sym->declared_at);
8952       return FAILURE;
8953     }
8954
8955   /* An elemental function is required to return a scalar 12.7.1  */
8956   if (sym->attr.elemental && sym->attr.function && sym->as)
8957     {
8958       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
8959                  "result", sym->name, &sym->declared_at);
8960       /* Reset so that the error only occurs once.  */
8961       sym->attr.elemental = 0;
8962       return FAILURE;
8963     }
8964
8965   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
8966      char-len-param shall not be array-valued, pointer-valued, recursive
8967      or pure.  ....snip... A character value of * may only be used in the
8968      following ways: (i) Dummy arg of procedure - dummy associates with
8969      actual length; (ii) To declare a named constant; or (iii) External
8970      function - but length must be declared in calling scoping unit.  */
8971   if (sym->attr.function
8972       && sym->ts.type == BT_CHARACTER
8973       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
8974     {
8975       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
8976           || (sym->attr.recursive) || (sym->attr.pure))
8977         {
8978           if (sym->as && sym->as->rank)
8979             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8980                        "array-valued", sym->name, &sym->declared_at);
8981
8982           if (sym->attr.pointer)
8983             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8984                        "pointer-valued", sym->name, &sym->declared_at);
8985
8986           if (sym->attr.pure)
8987             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8988                        "pure", sym->name, &sym->declared_at);
8989
8990           if (sym->attr.recursive)
8991             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8992                        "recursive", sym->name, &sym->declared_at);
8993
8994           return FAILURE;
8995         }
8996
8997       /* Appendix B.2 of the standard.  Contained functions give an
8998          error anyway.  Fixed-form is likely to be F77/legacy.  */
8999       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9000         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9001                         "CHARACTER(*) function '%s' at %L",
9002                         sym->name, &sym->declared_at);
9003     }
9004
9005   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9006     {
9007       gfc_formal_arglist *curr_arg;
9008       int has_non_interop_arg = 0;
9009
9010       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9011                              sym->common_block) == FAILURE)
9012         {
9013           /* Clear these to prevent looking at them again if there was an
9014              error.  */
9015           sym->attr.is_bind_c = 0;
9016           sym->attr.is_c_interop = 0;
9017           sym->ts.is_c_interop = 0;
9018         }
9019       else
9020         {
9021           /* So far, no errors have been found.  */
9022           sym->attr.is_c_interop = 1;
9023           sym->ts.is_c_interop = 1;
9024         }
9025       
9026       curr_arg = sym->formal;
9027       while (curr_arg != NULL)
9028         {
9029           /* Skip implicitly typed dummy args here.  */
9030           if (curr_arg->sym->attr.implicit_type == 0)
9031             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9032               /* If something is found to fail, record the fact so we
9033                  can mark the symbol for the procedure as not being
9034                  BIND(C) to try and prevent multiple errors being
9035                  reported.  */
9036               has_non_interop_arg = 1;
9037           
9038           curr_arg = curr_arg->next;
9039         }
9040
9041       /* See if any of the arguments were not interoperable and if so, clear
9042          the procedure symbol to prevent duplicate error messages.  */
9043       if (has_non_interop_arg != 0)
9044         {
9045           sym->attr.is_c_interop = 0;
9046           sym->ts.is_c_interop = 0;
9047           sym->attr.is_bind_c = 0;
9048         }
9049     }
9050   
9051   if (!sym->attr.proc_pointer)
9052     {
9053       if (sym->attr.save == SAVE_EXPLICIT)
9054         {
9055           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9056                      "in '%s' at %L", sym->name, &sym->declared_at);
9057           return FAILURE;
9058         }
9059       if (sym->attr.intent)
9060         {
9061           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9062                      "in '%s' at %L", sym->name, &sym->declared_at);
9063           return FAILURE;
9064         }
9065       if (sym->attr.subroutine && sym->attr.result)
9066         {
9067           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9068                      "in '%s' at %L", sym->name, &sym->declared_at);
9069           return FAILURE;
9070         }
9071       if (sym->attr.external && sym->attr.function
9072           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9073               || sym->attr.contained))
9074         {
9075           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9076                      "in '%s' at %L", sym->name, &sym->declared_at);
9077           return FAILURE;
9078         }
9079       if (strcmp ("ppr@", sym->name) == 0)
9080         {
9081           gfc_error ("Procedure pointer result '%s' at %L "
9082                      "is missing the pointer attribute",
9083                      sym->ns->proc_name->name, &sym->declared_at);
9084           return FAILURE;
9085         }
9086     }
9087
9088   return SUCCESS;
9089 }
9090
9091
9092 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9093    been defined and we now know their defined arguments, check that they fulfill
9094    the requirements of the standard for procedures used as finalizers.  */
9095
9096 static gfc_try
9097 gfc_resolve_finalizers (gfc_symbol* derived)
9098 {
9099   gfc_finalizer* list;
9100   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9101   gfc_try result = SUCCESS;
9102   bool seen_scalar = false;
9103
9104   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9105     return SUCCESS;
9106
9107   /* Walk over the list of finalizer-procedures, check them, and if any one
9108      does not fit in with the standard's definition, print an error and remove
9109      it from the list.  */
9110   prev_link = &derived->f2k_derived->finalizers;
9111   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9112     {
9113       gfc_symbol* arg;
9114       gfc_finalizer* i;
9115       int my_rank;
9116
9117       /* Skip this finalizer if we already resolved it.  */
9118       if (list->proc_tree)
9119         {
9120           prev_link = &(list->next);
9121           continue;
9122         }
9123
9124       /* Check this exists and is a SUBROUTINE.  */
9125       if (!list->proc_sym->attr.subroutine)
9126         {
9127           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9128                      list->proc_sym->name, &list->where);
9129           goto error;
9130         }
9131
9132       /* We should have exactly one argument.  */
9133       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9134         {
9135           gfc_error ("FINAL procedure at %L must have exactly one argument",
9136                      &list->where);
9137           goto error;
9138         }
9139       arg = list->proc_sym->formal->sym;
9140
9141       /* This argument must be of our type.  */
9142       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9143         {
9144           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9145                      &arg->declared_at, derived->name);
9146           goto error;
9147         }
9148
9149       /* It must neither be a pointer nor allocatable nor optional.  */
9150       if (arg->attr.pointer)
9151         {
9152           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9153                      &arg->declared_at);
9154           goto error;
9155         }
9156       if (arg->attr.allocatable)
9157         {
9158           gfc_error ("Argument of FINAL procedure at %L must not be"
9159                      " ALLOCATABLE", &arg->declared_at);
9160           goto error;
9161         }
9162       if (arg->attr.optional)
9163         {
9164           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9165                      &arg->declared_at);
9166           goto error;
9167         }
9168
9169       /* It must not be INTENT(OUT).  */
9170       if (arg->attr.intent == INTENT_OUT)
9171         {
9172           gfc_error ("Argument of FINAL procedure at %L must not be"
9173                      " INTENT(OUT)", &arg->declared_at);
9174           goto error;
9175         }
9176
9177       /* Warn if the procedure is non-scalar and not assumed shape.  */
9178       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9179           && arg->as->type != AS_ASSUMED_SHAPE)
9180         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9181                      " shape argument", &arg->declared_at);
9182
9183       /* Check that it does not match in kind and rank with a FINAL procedure
9184          defined earlier.  To really loop over the *earlier* declarations,
9185          we need to walk the tail of the list as new ones were pushed at the
9186          front.  */
9187       /* TODO: Handle kind parameters once they are implemented.  */
9188       my_rank = (arg->as ? arg->as->rank : 0);
9189       for (i = list->next; i; i = i->next)
9190         {
9191           /* Argument list might be empty; that is an error signalled earlier,
9192              but we nevertheless continued resolving.  */
9193           if (i->proc_sym->formal)
9194             {
9195               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9196               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9197               if (i_rank == my_rank)
9198                 {
9199                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9200                              " rank (%d) as '%s'",
9201                              list->proc_sym->name, &list->where, my_rank, 
9202                              i->proc_sym->name);
9203                   goto error;
9204                 }
9205             }
9206         }
9207
9208         /* Is this the/a scalar finalizer procedure?  */
9209         if (!arg->as || arg->as->rank == 0)
9210           seen_scalar = true;
9211
9212         /* Find the symtree for this procedure.  */
9213         gcc_assert (!list->proc_tree);
9214         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9215
9216         prev_link = &list->next;
9217         continue;
9218
9219         /* Remove wrong nodes immediately from the list so we don't risk any
9220            troubles in the future when they might fail later expectations.  */
9221 error:
9222         result = FAILURE;
9223         i = list;
9224         *prev_link = list->next;
9225         gfc_free_finalizer (i);
9226     }
9227
9228   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9229      were nodes in the list, must have been for arrays.  It is surely a good
9230      idea to have a scalar version there if there's something to finalize.  */
9231   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9232     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9233                  " defined at %L, suggest also scalar one",
9234                  derived->name, &derived->declared_at);
9235
9236   /* TODO:  Remove this error when finalization is finished.  */
9237   gfc_error ("Finalization at %L is not yet implemented",
9238              &derived->declared_at);
9239
9240   return result;
9241 }
9242
9243
9244 /* Check that it is ok for the typebound procedure proc to override the
9245    procedure old.  */
9246
9247 static gfc_try
9248 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9249 {
9250   locus where;
9251   const gfc_symbol* proc_target;
9252   const gfc_symbol* old_target;
9253   unsigned proc_pass_arg, old_pass_arg, argpos;
9254   gfc_formal_arglist* proc_formal;
9255   gfc_formal_arglist* old_formal;
9256
9257   /* This procedure should only be called for non-GENERIC proc.  */
9258   gcc_assert (!proc->n.tb->is_generic);
9259
9260   /* If the overwritten procedure is GENERIC, this is an error.  */
9261   if (old->n.tb->is_generic)
9262     {
9263       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9264                  old->name, &proc->n.tb->where);
9265       return FAILURE;
9266     }
9267
9268   where = proc->n.tb->where;
9269   proc_target = proc->n.tb->u.specific->n.sym;
9270   old_target = old->n.tb->u.specific->n.sym;
9271
9272   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9273   if (old->n.tb->non_overridable)
9274     {
9275       gfc_error ("'%s' at %L overrides a procedure binding declared"
9276                  " NON_OVERRIDABLE", proc->name, &where);
9277       return FAILURE;
9278     }
9279
9280   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9281   if (!old->n.tb->deferred && proc->n.tb->deferred)
9282     {
9283       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9284                  " non-DEFERRED binding", proc->name, &where);
9285       return FAILURE;
9286     }
9287
9288   /* If the overridden binding is PURE, the overriding must be, too.  */
9289   if (old_target->attr.pure && !proc_target->attr.pure)
9290     {
9291       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9292                  proc->name, &where);
9293       return FAILURE;
9294     }
9295
9296   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9297      is not, the overriding must not be either.  */
9298   if (old_target->attr.elemental && !proc_target->attr.elemental)
9299     {
9300       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9301                  " ELEMENTAL", proc->name, &where);
9302       return FAILURE;
9303     }
9304   if (!old_target->attr.elemental && proc_target->attr.elemental)
9305     {
9306       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9307                  " be ELEMENTAL, either", proc->name, &where);
9308       return FAILURE;
9309     }
9310
9311   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9312      SUBROUTINE.  */
9313   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9314     {
9315       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9316                  " SUBROUTINE", proc->name, &where);
9317       return FAILURE;
9318     }
9319
9320   /* If the overridden binding is a FUNCTION, the overriding must also be a
9321      FUNCTION and have the same characteristics.  */
9322   if (old_target->attr.function)
9323     {
9324       if (!proc_target->attr.function)
9325         {
9326           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9327                      " FUNCTION", proc->name, &where);
9328           return FAILURE;
9329         }
9330
9331       /* FIXME:  Do more comprehensive checking (including, for instance, the
9332          rank and array-shape).  */
9333       gcc_assert (proc_target->result && old_target->result);
9334       if (!gfc_compare_types (&proc_target->result->ts,
9335                               &old_target->result->ts))
9336         {
9337           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9338                      " matching result types", proc->name, &where);
9339           return FAILURE;
9340         }
9341     }
9342
9343   /* If the overridden binding is PUBLIC, the overriding one must not be
9344      PRIVATE.  */
9345   if (old->n.tb->access == ACCESS_PUBLIC
9346       && proc->n.tb->access == ACCESS_PRIVATE)
9347     {
9348       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9349                  " PRIVATE", proc->name, &where);
9350       return FAILURE;
9351     }
9352
9353   /* Compare the formal argument lists of both procedures.  This is also abused
9354      to find the position of the passed-object dummy arguments of both
9355      bindings as at least the overridden one might not yet be resolved and we
9356      need those positions in the check below.  */
9357   proc_pass_arg = old_pass_arg = 0;
9358   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9359     proc_pass_arg = 1;
9360   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9361     old_pass_arg = 1;
9362   argpos = 1;
9363   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9364        proc_formal && old_formal;
9365        proc_formal = proc_formal->next, old_formal = old_formal->next)
9366     {
9367       if (proc->n.tb->pass_arg
9368           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9369         proc_pass_arg = argpos;
9370       if (old->n.tb->pass_arg
9371           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9372         old_pass_arg = argpos;
9373
9374       /* Check that the names correspond.  */
9375       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9376         {
9377           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9378                      " to match the corresponding argument of the overridden"
9379                      " procedure", proc_formal->sym->name, proc->name, &where,
9380                      old_formal->sym->name);
9381           return FAILURE;
9382         }
9383
9384       /* Check that the types correspond if neither is the passed-object
9385          argument.  */
9386       /* FIXME:  Do more comprehensive testing here.  */
9387       if (proc_pass_arg != argpos && old_pass_arg != argpos
9388           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
9389         {
9390           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L in"
9391                      " in respect to the overridden procedure",
9392                      proc_formal->sym->name, proc->name, &where);
9393           return FAILURE;
9394         }
9395
9396       ++argpos;
9397     }
9398   if (proc_formal || old_formal)
9399     {
9400       gfc_error ("'%s' at %L must have the same number of formal arguments as"
9401                  " the overridden procedure", proc->name, &where);
9402       return FAILURE;
9403     }
9404
9405   /* If the overridden binding is NOPASS, the overriding one must also be
9406      NOPASS.  */
9407   if (old->n.tb->nopass && !proc->n.tb->nopass)
9408     {
9409       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
9410                  " NOPASS", proc->name, &where);
9411       return FAILURE;
9412     }
9413
9414   /* If the overridden binding is PASS(x), the overriding one must also be
9415      PASS and the passed-object dummy arguments must correspond.  */
9416   if (!old->n.tb->nopass)
9417     {
9418       if (proc->n.tb->nopass)
9419         {
9420           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
9421                      " PASS", proc->name, &where);
9422           return FAILURE;
9423         }
9424
9425       if (proc_pass_arg != old_pass_arg)
9426         {
9427           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
9428                      " the same position as the passed-object dummy argument of"
9429                      " the overridden procedure", proc->name, &where);
9430           return FAILURE;
9431         }
9432     }
9433
9434   return SUCCESS;
9435 }
9436
9437
9438 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
9439
9440 static gfc_try
9441 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
9442                              const char* generic_name, locus where)
9443 {
9444   gfc_symbol* sym1;
9445   gfc_symbol* sym2;
9446
9447   gcc_assert (t1->specific && t2->specific);
9448   gcc_assert (!t1->specific->is_generic);
9449   gcc_assert (!t2->specific->is_generic);
9450
9451   sym1 = t1->specific->u.specific->n.sym;
9452   sym2 = t2->specific->u.specific->n.sym;
9453
9454   if (sym1 == sym2)
9455     return SUCCESS;
9456
9457   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
9458   if (sym1->attr.subroutine != sym2->attr.subroutine
9459       || sym1->attr.function != sym2->attr.function)
9460     {
9461       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
9462                  " GENERIC '%s' at %L",
9463                  sym1->name, sym2->name, generic_name, &where);
9464       return FAILURE;
9465     }
9466
9467   /* Compare the interfaces.  */
9468   if (gfc_compare_interfaces (sym1, sym2, NULL, 1, 0, NULL, 0))
9469     {
9470       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
9471                  sym1->name, sym2->name, generic_name, &where);
9472       return FAILURE;
9473     }
9474
9475   return SUCCESS;
9476 }
9477
9478
9479 /* Worker function for resolving a generic procedure binding; this is used to
9480    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
9481
9482    The difference between those cases is finding possible inherited bindings
9483    that are overridden, as one has to look for them in tb_sym_root,
9484    tb_uop_root or tb_op, respectively.  Thus the caller must already find
9485    the super-type and set p->overridden correctly.  */
9486
9487 static gfc_try
9488 resolve_tb_generic_targets (gfc_symbol* super_type,
9489                             gfc_typebound_proc* p, const char* name)
9490 {
9491   gfc_tbp_generic* target;
9492   gfc_symtree* first_target;
9493   gfc_symtree* inherited;
9494
9495   gcc_assert (p && p->is_generic);
9496
9497   /* Try to find the specific bindings for the symtrees in our target-list.  */
9498   gcc_assert (p->u.generic);
9499   for (target = p->u.generic; target; target = target->next)
9500     if (!target->specific)
9501       {
9502         gfc_typebound_proc* overridden_tbp;
9503         gfc_tbp_generic* g;
9504         const char* target_name;
9505
9506         target_name = target->specific_st->name;
9507
9508         /* Defined for this type directly.  */
9509         if (target->specific_st->n.tb)
9510           {
9511             target->specific = target->specific_st->n.tb;
9512             goto specific_found;
9513           }
9514
9515         /* Look for an inherited specific binding.  */
9516         if (super_type)
9517           {
9518             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
9519                                                  true, NULL);
9520
9521             if (inherited)
9522               {
9523                 gcc_assert (inherited->n.tb);
9524                 target->specific = inherited->n.tb;
9525                 goto specific_found;
9526               }
9527           }
9528
9529         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
9530                    " at %L", target_name, name, &p->where);
9531         return FAILURE;
9532
9533         /* Once we've found the specific binding, check it is not ambiguous with
9534            other specifics already found or inherited for the same GENERIC.  */
9535 specific_found:
9536         gcc_assert (target->specific);
9537
9538         /* This must really be a specific binding!  */
9539         if (target->specific->is_generic)
9540           {
9541             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
9542                        " '%s' is GENERIC, too", name, &p->where, target_name);
9543             return FAILURE;
9544           }
9545
9546         /* Check those already resolved on this type directly.  */
9547         for (g = p->u.generic; g; g = g->next)
9548           if (g != target && g->specific
9549               && check_generic_tbp_ambiguity (target, g, name, p->where)
9550                   == FAILURE)
9551             return FAILURE;
9552
9553         /* Check for ambiguity with inherited specific targets.  */
9554         for (overridden_tbp = p->overridden; overridden_tbp;
9555              overridden_tbp = overridden_tbp->overridden)
9556           if (overridden_tbp->is_generic)
9557             {
9558               for (g = overridden_tbp->u.generic; g; g = g->next)
9559                 {
9560                   gcc_assert (g->specific);
9561                   if (check_generic_tbp_ambiguity (target, g,
9562                                                    name, p->where) == FAILURE)
9563                     return FAILURE;
9564                 }
9565             }
9566       }
9567
9568   /* If we attempt to "overwrite" a specific binding, this is an error.  */
9569   if (p->overridden && !p->overridden->is_generic)
9570     {
9571       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
9572                  " the same name", name, &p->where);
9573       return FAILURE;
9574     }
9575
9576   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
9577      all must have the same attributes here.  */
9578   first_target = p->u.generic->specific->u.specific;
9579   gcc_assert (first_target);
9580   p->subroutine = first_target->n.sym->attr.subroutine;
9581   p->function = first_target->n.sym->attr.function;
9582
9583   return SUCCESS;
9584 }
9585
9586
9587 /* Resolve a GENERIC procedure binding for a derived type.  */
9588
9589 static gfc_try
9590 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
9591 {
9592   gfc_symbol* super_type;
9593
9594   /* Find the overridden binding if any.  */
9595   st->n.tb->overridden = NULL;
9596   super_type = gfc_get_derived_super_type (derived);
9597   if (super_type)
9598     {
9599       gfc_symtree* overridden;
9600       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
9601                                             true, NULL);
9602
9603       if (overridden && overridden->n.tb)
9604         st->n.tb->overridden = overridden->n.tb;
9605     }
9606
9607   /* Resolve using worker function.  */
9608   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
9609 }
9610
9611
9612 /* Retrieve the target-procedure of an operator binding and do some checks in
9613    common for intrinsic and user-defined type-bound operators.  */
9614
9615 static gfc_symbol*
9616 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
9617 {
9618   gfc_symbol* target_proc;
9619
9620   gcc_assert (target->specific && !target->specific->is_generic);
9621   target_proc = target->specific->u.specific->n.sym;
9622   gcc_assert (target_proc);
9623
9624   /* All operator bindings must have a passed-object dummy argument.  */
9625   if (target->specific->nopass)
9626     {
9627       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
9628       return NULL;
9629     }
9630
9631   return target_proc;
9632 }
9633
9634
9635 /* Resolve a type-bound intrinsic operator.  */
9636
9637 static gfc_try
9638 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
9639                                 gfc_typebound_proc* p)
9640 {
9641   gfc_symbol* super_type;
9642   gfc_tbp_generic* target;
9643   
9644   /* If there's already an error here, do nothing (but don't fail again).  */
9645   if (p->error)
9646     return SUCCESS;
9647
9648   /* Operators should always be GENERIC bindings.  */
9649   gcc_assert (p->is_generic);
9650
9651   /* Look for an overridden binding.  */
9652   super_type = gfc_get_derived_super_type (derived);
9653   if (super_type && super_type->f2k_derived)
9654     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
9655                                                      op, true, NULL);
9656   else
9657     p->overridden = NULL;
9658
9659   /* Resolve general GENERIC properties using worker function.  */
9660   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
9661     goto error;
9662
9663   /* Check the targets to be procedures of correct interface.  */
9664   for (target = p->u.generic; target; target = target->next)
9665     {
9666       gfc_symbol* target_proc;
9667
9668       target_proc = get_checked_tb_operator_target (target, p->where);
9669       if (!target_proc)
9670         goto error;
9671
9672       if (!gfc_check_operator_interface (target_proc, op, p->where))
9673         goto error;
9674     }
9675
9676   return SUCCESS;
9677
9678 error:
9679   p->error = 1;
9680   return FAILURE;
9681 }
9682
9683
9684 /* Resolve a type-bound user operator (tree-walker callback).  */
9685
9686 static gfc_symbol* resolve_bindings_derived;
9687 static gfc_try resolve_bindings_result;
9688
9689 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
9690
9691 static void
9692 resolve_typebound_user_op (gfc_symtree* stree)
9693 {
9694   gfc_symbol* super_type;
9695   gfc_tbp_generic* target;
9696
9697   gcc_assert (stree && stree->n.tb);
9698
9699   if (stree->n.tb->error)
9700     return;
9701
9702   /* Operators should always be GENERIC bindings.  */
9703   gcc_assert (stree->n.tb->is_generic);
9704
9705   /* Find overridden procedure, if any.  */
9706   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
9707   if (super_type && super_type->f2k_derived)
9708     {
9709       gfc_symtree* overridden;
9710       overridden = gfc_find_typebound_user_op (super_type, NULL,
9711                                                stree->name, true, NULL);
9712
9713       if (overridden && overridden->n.tb)
9714         stree->n.tb->overridden = overridden->n.tb;
9715     }
9716   else
9717     stree->n.tb->overridden = NULL;
9718
9719   /* Resolve basically using worker function.  */
9720   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
9721         == FAILURE)
9722     goto error;
9723
9724   /* Check the targets to be functions of correct interface.  */
9725   for (target = stree->n.tb->u.generic; target; target = target->next)
9726     {
9727       gfc_symbol* target_proc;
9728
9729       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
9730       if (!target_proc)
9731         goto error;
9732
9733       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
9734         goto error;
9735     }
9736
9737   return;
9738
9739 error:
9740   resolve_bindings_result = FAILURE;
9741   stree->n.tb->error = 1;
9742 }
9743
9744
9745 /* Resolve the type-bound procedures for a derived type.  */
9746
9747 static void
9748 resolve_typebound_procedure (gfc_symtree* stree)
9749 {
9750   gfc_symbol* proc;
9751   locus where;
9752   gfc_symbol* me_arg;
9753   gfc_symbol* super_type;
9754   gfc_component* comp;
9755
9756   gcc_assert (stree);
9757
9758   /* Undefined specific symbol from GENERIC target definition.  */
9759   if (!stree->n.tb)
9760     return;
9761
9762   if (stree->n.tb->error)
9763     return;
9764
9765   /* If this is a GENERIC binding, use that routine.  */
9766   if (stree->n.tb->is_generic)
9767     {
9768       if (resolve_typebound_generic (resolve_bindings_derived, stree)
9769             == FAILURE)
9770         goto error;
9771       return;
9772     }
9773
9774   /* Get the target-procedure to check it.  */
9775   gcc_assert (!stree->n.tb->is_generic);
9776   gcc_assert (stree->n.tb->u.specific);
9777   proc = stree->n.tb->u.specific->n.sym;
9778   where = stree->n.tb->where;
9779
9780   /* Default access should already be resolved from the parser.  */
9781   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
9782
9783   /* It should be a module procedure or an external procedure with explicit
9784      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
9785   if ((!proc->attr.subroutine && !proc->attr.function)
9786       || (proc->attr.proc != PROC_MODULE
9787           && proc->attr.if_source != IFSRC_IFBODY)
9788       || (proc->attr.abstract && !stree->n.tb->deferred))
9789     {
9790       gfc_error ("'%s' must be a module procedure or an external procedure with"
9791                  " an explicit interface at %L", proc->name, &where);
9792       goto error;
9793     }
9794   stree->n.tb->subroutine = proc->attr.subroutine;
9795   stree->n.tb->function = proc->attr.function;
9796
9797   /* Find the super-type of the current derived type.  We could do this once and
9798      store in a global if speed is needed, but as long as not I believe this is
9799      more readable and clearer.  */
9800   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
9801
9802   /* If PASS, resolve and check arguments if not already resolved / loaded
9803      from a .mod file.  */
9804   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
9805     {
9806       if (stree->n.tb->pass_arg)
9807         {
9808           gfc_formal_arglist* i;
9809
9810           /* If an explicit passing argument name is given, walk the arg-list
9811              and look for it.  */
9812
9813           me_arg = NULL;
9814           stree->n.tb->pass_arg_num = 1;
9815           for (i = proc->formal; i; i = i->next)
9816             {
9817               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
9818                 {
9819                   me_arg = i->sym;
9820                   break;
9821                 }
9822               ++stree->n.tb->pass_arg_num;
9823             }
9824
9825           if (!me_arg)
9826             {
9827               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
9828                          " argument '%s'",
9829                          proc->name, stree->n.tb->pass_arg, &where,
9830                          stree->n.tb->pass_arg);
9831               goto error;
9832             }
9833         }
9834       else
9835         {
9836           /* Otherwise, take the first one; there should in fact be at least
9837              one.  */
9838           stree->n.tb->pass_arg_num = 1;
9839           if (!proc->formal)
9840             {
9841               gfc_error ("Procedure '%s' with PASS at %L must have at"
9842                          " least one argument", proc->name, &where);
9843               goto error;
9844             }
9845           me_arg = proc->formal->sym;
9846         }
9847
9848       /* Now check that the argument-type matches.  */
9849       gcc_assert (me_arg);
9850       if (me_arg->ts.type != BT_CLASS)
9851         {
9852           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
9853                      " at %L", proc->name, &where);
9854           goto error;
9855         }
9856
9857       if (me_arg->ts.u.derived->components->ts.u.derived
9858           != resolve_bindings_derived)
9859         {
9860           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
9861                      " the derived-type '%s'", me_arg->name, proc->name,
9862                      me_arg->name, &where, resolve_bindings_derived->name);
9863           goto error;
9864         }
9865
9866     }
9867
9868   /* If we are extending some type, check that we don't override a procedure
9869      flagged NON_OVERRIDABLE.  */
9870   stree->n.tb->overridden = NULL;
9871   if (super_type)
9872     {
9873       gfc_symtree* overridden;
9874       overridden = gfc_find_typebound_proc (super_type, NULL,
9875                                             stree->name, true, NULL);
9876
9877       if (overridden && overridden->n.tb)
9878         stree->n.tb->overridden = overridden->n.tb;
9879
9880       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
9881         goto error;
9882     }
9883
9884   /* See if there's a name collision with a component directly in this type.  */
9885   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
9886     if (!strcmp (comp->name, stree->name))
9887       {
9888         gfc_error ("Procedure '%s' at %L has the same name as a component of"
9889                    " '%s'",
9890                    stree->name, &where, resolve_bindings_derived->name);
9891         goto error;
9892       }
9893
9894   /* Try to find a name collision with an inherited component.  */
9895   if (super_type && gfc_find_component (super_type, stree->name, true, true))
9896     {
9897       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
9898                  " component of '%s'",
9899                  stree->name, &where, resolve_bindings_derived->name);
9900       goto error;
9901     }
9902
9903   stree->n.tb->error = 0;
9904   return;
9905
9906 error:
9907   resolve_bindings_result = FAILURE;
9908   stree->n.tb->error = 1;
9909 }
9910
9911 static gfc_try
9912 resolve_typebound_procedures (gfc_symbol* derived)
9913 {
9914   int op;
9915
9916   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
9917     return SUCCESS;
9918
9919   resolve_bindings_derived = derived;
9920   resolve_bindings_result = SUCCESS;
9921
9922   if (derived->f2k_derived->tb_sym_root)
9923     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
9924                           &resolve_typebound_procedure);
9925
9926   if (derived->f2k_derived->tb_uop_root)
9927     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
9928                           &resolve_typebound_user_op);
9929
9930   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
9931     {
9932       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
9933       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
9934                                                p) == FAILURE)
9935         resolve_bindings_result = FAILURE;
9936     }
9937
9938   return resolve_bindings_result;
9939 }
9940
9941
9942 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
9943    to give all identical derived types the same backend_decl.  */
9944 static void
9945 add_dt_to_dt_list (gfc_symbol *derived)
9946 {
9947   gfc_dt_list *dt_list;
9948
9949   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
9950     if (derived == dt_list->derived)
9951       break;
9952
9953   if (dt_list == NULL)
9954     {
9955       dt_list = gfc_get_dt_list ();
9956       dt_list->next = gfc_derived_types;
9957       dt_list->derived = derived;
9958       gfc_derived_types = dt_list;
9959     }
9960 }
9961
9962
9963 /* Ensure that a derived-type is really not abstract, meaning that every
9964    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
9965
9966 static gfc_try
9967 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
9968 {
9969   if (!st)
9970     return SUCCESS;
9971
9972   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
9973     return FAILURE;
9974   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
9975     return FAILURE;
9976
9977   if (st->n.tb && st->n.tb->deferred)
9978     {
9979       gfc_symtree* overriding;
9980       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
9981       gcc_assert (overriding && overriding->n.tb);
9982       if (overriding->n.tb->deferred)
9983         {
9984           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
9985                      " '%s' is DEFERRED and not overridden",
9986                      sub->name, &sub->declared_at, st->name);
9987           return FAILURE;
9988         }
9989     }
9990
9991   return SUCCESS;
9992 }
9993
9994 static gfc_try
9995 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
9996 {
9997   /* The algorithm used here is to recursively travel up the ancestry of sub
9998      and for each ancestor-type, check all bindings.  If any of them is
9999      DEFERRED, look it up starting from sub and see if the found (overriding)
10000      binding is not DEFERRED.
10001      This is not the most efficient way to do this, but it should be ok and is
10002      clearer than something sophisticated.  */
10003
10004   gcc_assert (ancestor && ancestor->attr.abstract && !sub->attr.abstract);
10005
10006   /* Walk bindings of this ancestor.  */
10007   if (ancestor->f2k_derived)
10008     {
10009       gfc_try t;
10010       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10011       if (t == FAILURE)
10012         return FAILURE;
10013     }
10014
10015   /* Find next ancestor type and recurse on it.  */
10016   ancestor = gfc_get_derived_super_type (ancestor);
10017   if (ancestor)
10018     return ensure_not_abstract (sub, ancestor);
10019
10020   return SUCCESS;
10021 }
10022
10023
10024 static void resolve_symbol (gfc_symbol *sym);
10025
10026
10027 /* Resolve the components of a derived type.  */
10028
10029 static gfc_try
10030 resolve_fl_derived (gfc_symbol *sym)
10031 {
10032   gfc_symbol* super_type;
10033   gfc_component *c;
10034   int i;
10035
10036   super_type = gfc_get_derived_super_type (sym);
10037
10038   /* Ensure the extended type gets resolved before we do.  */
10039   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10040     return FAILURE;
10041
10042   /* An ABSTRACT type must be extensible.  */
10043   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10044     {
10045       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10046                  sym->name, &sym->declared_at);
10047       return FAILURE;
10048     }
10049
10050   for (c = sym->components; c != NULL; c = c->next)
10051     {
10052       if (c->attr.proc_pointer && c->ts.interface)
10053         {
10054           if (c->ts.interface->attr.procedure)
10055             gfc_error ("Interface '%s', used by procedure pointer component "
10056                        "'%s' at %L, is declared in a later PROCEDURE statement",
10057                        c->ts.interface->name, c->name, &c->loc);
10058
10059           /* Get the attributes from the interface (now resolved).  */
10060           if (c->ts.interface->attr.if_source
10061               || c->ts.interface->attr.intrinsic)
10062             {
10063               gfc_symbol *ifc = c->ts.interface;
10064
10065               if (ifc->formal && !ifc->formal_ns)
10066                 resolve_symbol (ifc);
10067
10068               if (ifc->attr.intrinsic)
10069                 resolve_intrinsic (ifc, &ifc->declared_at);
10070
10071               if (ifc->result)
10072                 {
10073                   c->ts = ifc->result->ts;
10074                   c->attr.allocatable = ifc->result->attr.allocatable;
10075                   c->attr.pointer = ifc->result->attr.pointer;
10076                   c->attr.dimension = ifc->result->attr.dimension;
10077                   c->as = gfc_copy_array_spec (ifc->result->as);
10078                 }
10079               else
10080                 {   
10081                   c->ts = ifc->ts;
10082                   c->attr.allocatable = ifc->attr.allocatable;
10083                   c->attr.pointer = ifc->attr.pointer;
10084                   c->attr.dimension = ifc->attr.dimension;
10085                   c->as = gfc_copy_array_spec (ifc->as);
10086                 }
10087               c->ts.interface = ifc;
10088               c->attr.function = ifc->attr.function;
10089               c->attr.subroutine = ifc->attr.subroutine;
10090               gfc_copy_formal_args_ppc (c, ifc);
10091
10092               c->attr.pure = ifc->attr.pure;
10093               c->attr.elemental = ifc->attr.elemental;
10094               c->attr.recursive = ifc->attr.recursive;
10095               c->attr.always_explicit = ifc->attr.always_explicit;
10096               c->attr.ext_attr |= ifc->attr.ext_attr;
10097               /* Replace symbols in array spec.  */
10098               if (c->as)
10099                 {
10100                   int i;
10101                   for (i = 0; i < c->as->rank; i++)
10102                     {
10103                       gfc_expr_replace_comp (c->as->lower[i], c);
10104                       gfc_expr_replace_comp (c->as->upper[i], c);
10105                     }
10106                 }
10107               /* Copy char length.  */
10108               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10109                 {
10110                   c->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10111                   gfc_expr_replace_comp (c->ts.u.cl->length, c);
10112                 }
10113             }
10114           else if (c->ts.interface->name[0] != '\0')
10115             {
10116               gfc_error ("Interface '%s' of procedure pointer component "
10117                          "'%s' at %L must be explicit", c->ts.interface->name,
10118                          c->name, &c->loc);
10119               return FAILURE;
10120             }
10121         }
10122       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10123         {
10124           c->ts = *gfc_get_default_type (c->name, NULL);
10125           c->attr.implicit_type = 1;
10126         }
10127
10128       /* Procedure pointer components: Check PASS arg.  */
10129       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0)
10130         {
10131           gfc_symbol* me_arg;
10132
10133           if (c->tb->pass_arg)
10134             {
10135               gfc_formal_arglist* i;
10136
10137               /* If an explicit passing argument name is given, walk the arg-list
10138                 and look for it.  */
10139
10140               me_arg = NULL;
10141               c->tb->pass_arg_num = 1;
10142               for (i = c->formal; i; i = i->next)
10143                 {
10144                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10145                     {
10146                       me_arg = i->sym;
10147                       break;
10148                     }
10149                   c->tb->pass_arg_num++;
10150                 }
10151
10152               if (!me_arg)
10153                 {
10154                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10155                              "at %L has no argument '%s'", c->name,
10156                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10157                   c->tb->error = 1;
10158                   return FAILURE;
10159                 }
10160             }
10161           else
10162             {
10163               /* Otherwise, take the first one; there should in fact be at least
10164                 one.  */
10165               c->tb->pass_arg_num = 1;
10166               if (!c->formal)
10167                 {
10168                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10169                              "must have at least one argument",
10170                              c->name, &c->loc);
10171                   c->tb->error = 1;
10172                   return FAILURE;
10173                 }
10174               me_arg = c->formal->sym;
10175             }
10176
10177           /* Now check that the argument-type matches.  */
10178           gcc_assert (me_arg);
10179           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10180               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10181               || (me_arg->ts.type == BT_CLASS
10182                   && me_arg->ts.u.derived->components->ts.u.derived != sym))
10183             {
10184               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10185                          " the derived type '%s'", me_arg->name, c->name,
10186                          me_arg->name, &c->loc, sym->name);
10187               c->tb->error = 1;
10188               return FAILURE;
10189             }
10190
10191           /* Check for C453.  */
10192           if (me_arg->attr.dimension)
10193             {
10194               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10195                          "must be scalar", me_arg->name, c->name, me_arg->name,
10196                          &c->loc);
10197               c->tb->error = 1;
10198               return FAILURE;
10199             }
10200
10201           if (me_arg->attr.pointer)
10202             {
10203               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10204                          "may not have the POINTER attribute", me_arg->name,
10205                          c->name, me_arg->name, &c->loc);
10206               c->tb->error = 1;
10207               return FAILURE;
10208             }
10209
10210           if (me_arg->attr.allocatable)
10211             {
10212               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10213                          "may not be ALLOCATABLE", me_arg->name, c->name,
10214                          me_arg->name, &c->loc);
10215               c->tb->error = 1;
10216               return FAILURE;
10217             }
10218
10219           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10220             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10221                        " at %L", c->name, &c->loc);
10222
10223         }
10224
10225       /* Check type-spec if this is not the parent-type component.  */
10226       if ((!sym->attr.extension || c != sym->components)
10227           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10228         return FAILURE;
10229
10230       /* If this type is an extension, see if this component has the same name
10231          as an inherited type-bound procedure.  */
10232       if (super_type
10233           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10234         {
10235           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10236                      " inherited type-bound procedure",
10237                      c->name, sym->name, &c->loc);
10238           return FAILURE;
10239         }
10240
10241       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10242         {
10243          if (c->ts.u.cl->length == NULL
10244              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10245              || !gfc_is_constant_expr (c->ts.u.cl->length))
10246            {
10247              gfc_error ("Character length of component '%s' needs to "
10248                         "be a constant specification expression at %L",
10249                         c->name,
10250                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10251              return FAILURE;
10252            }
10253         }
10254
10255       if (c->ts.type == BT_DERIVED
10256           && sym->component_access != ACCESS_PRIVATE
10257           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10258           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10259           && !c->ts.u.derived->attr.use_assoc
10260           && !gfc_check_access (c->ts.u.derived->attr.access,
10261                                 c->ts.u.derived->ns->default_access)
10262           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10263                              "is a PRIVATE type and cannot be a component of "
10264                              "'%s', which is PUBLIC at %L", c->name,
10265                              sym->name, &sym->declared_at) == FAILURE)
10266         return FAILURE;
10267
10268       if (sym->attr.sequence)
10269         {
10270           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10271             {
10272               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10273                          "not have the SEQUENCE attribute",
10274                          c->ts.u.derived->name, &sym->declared_at);
10275               return FAILURE;
10276             }
10277         }
10278
10279       if (c->ts.type == BT_DERIVED && c->attr.pointer
10280           && c->ts.u.derived->components == NULL
10281           && !c->ts.u.derived->attr.zero_comp)
10282         {
10283           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10284                      "that has not been declared", c->name, sym->name,
10285                      &c->loc);
10286           return FAILURE;
10287         }
10288
10289       /* C437.  */
10290       if (c->ts.type == BT_CLASS
10291           && !(c->ts.u.derived->components->attr.pointer
10292                || c->ts.u.derived->components->attr.allocatable))
10293         {
10294           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10295                      "or pointer", c->name, &c->loc);
10296           return FAILURE;
10297         }
10298
10299       /* Ensure that all the derived type components are put on the
10300          derived type list; even in formal namespaces, where derived type
10301          pointer components might not have been declared.  */
10302       if (c->ts.type == BT_DERIVED
10303             && c->ts.u.derived
10304             && c->ts.u.derived->components
10305             && c->attr.pointer
10306             && sym != c->ts.u.derived)
10307         add_dt_to_dt_list (c->ts.u.derived);
10308
10309       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10310           || c->as == NULL)
10311         continue;
10312
10313       for (i = 0; i < c->as->rank; i++)
10314         {
10315           if (c->as->lower[i] == NULL
10316               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
10317               || !gfc_is_constant_expr (c->as->lower[i])
10318               || c->as->upper[i] == NULL
10319               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
10320               || !gfc_is_constant_expr (c->as->upper[i]))
10321             {
10322               gfc_error ("Component '%s' of '%s' at %L must have "
10323                          "constant array bounds",
10324                          c->name, sym->name, &c->loc);
10325               return FAILURE;
10326             }
10327         }
10328     }
10329
10330   /* Resolve the type-bound procedures.  */
10331   if (resolve_typebound_procedures (sym) == FAILURE)
10332     return FAILURE;
10333
10334   /* Resolve the finalizer procedures.  */
10335   if (gfc_resolve_finalizers (sym) == FAILURE)
10336     return FAILURE;
10337
10338   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
10339      all DEFERRED bindings are overridden.  */
10340   if (super_type && super_type->attr.abstract && !sym->attr.abstract
10341       && ensure_not_abstract (sym, super_type) == FAILURE)
10342     return FAILURE;
10343
10344   /* Add derived type to the derived type list.  */
10345   add_dt_to_dt_list (sym);
10346
10347   return SUCCESS;
10348 }
10349
10350
10351 static gfc_try
10352 resolve_fl_namelist (gfc_symbol *sym)
10353 {
10354   gfc_namelist *nl;
10355   gfc_symbol *nlsym;
10356
10357   /* Reject PRIVATE objects in a PUBLIC namelist.  */
10358   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
10359     {
10360       for (nl = sym->namelist; nl; nl = nl->next)
10361         {
10362           if (!nl->sym->attr.use_assoc
10363               && !is_sym_host_assoc (nl->sym, sym->ns)
10364               && !gfc_check_access(nl->sym->attr.access,
10365                                 nl->sym->ns->default_access))
10366             {
10367               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
10368                          "cannot be member of PUBLIC namelist '%s' at %L",
10369                          nl->sym->name, sym->name, &sym->declared_at);
10370               return FAILURE;
10371             }
10372
10373           /* Types with private components that came here by USE-association.  */
10374           if (nl->sym->ts.type == BT_DERIVED
10375               && derived_inaccessible (nl->sym->ts.u.derived))
10376             {
10377               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
10378                          "components and cannot be member of namelist '%s' at %L",
10379                          nl->sym->name, sym->name, &sym->declared_at);
10380               return FAILURE;
10381             }
10382
10383           /* Types with private components that are defined in the same module.  */
10384           if (nl->sym->ts.type == BT_DERIVED
10385               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
10386               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
10387                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
10388                                         nl->sym->ns->default_access))
10389             {
10390               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
10391                          "cannot be a member of PUBLIC namelist '%s' at %L",
10392                          nl->sym->name, sym->name, &sym->declared_at);
10393               return FAILURE;
10394             }
10395         }
10396     }
10397
10398   for (nl = sym->namelist; nl; nl = nl->next)
10399     {
10400       /* Reject namelist arrays of assumed shape.  */
10401       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
10402           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
10403                              "must not have assumed shape in namelist "
10404                              "'%s' at %L", nl->sym->name, sym->name,
10405                              &sym->declared_at) == FAILURE)
10406             return FAILURE;
10407
10408       /* Reject namelist arrays that are not constant shape.  */
10409       if (is_non_constant_shape_array (nl->sym))
10410         {
10411           gfc_error ("NAMELIST array object '%s' must have constant "
10412                      "shape in namelist '%s' at %L", nl->sym->name,
10413                      sym->name, &sym->declared_at);
10414           return FAILURE;
10415         }
10416
10417       /* Namelist objects cannot have allocatable or pointer components.  */
10418       if (nl->sym->ts.type != BT_DERIVED)
10419         continue;
10420
10421       if (nl->sym->ts.u.derived->attr.alloc_comp)
10422         {
10423           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10424                      "have ALLOCATABLE components",
10425                      nl->sym->name, sym->name, &sym->declared_at);
10426           return FAILURE;
10427         }
10428
10429       if (nl->sym->ts.u.derived->attr.pointer_comp)
10430         {
10431           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10432                      "have POINTER components", 
10433                      nl->sym->name, sym->name, &sym->declared_at);
10434           return FAILURE;
10435         }
10436     }
10437
10438
10439   /* 14.1.2 A module or internal procedure represent local entities
10440      of the same type as a namelist member and so are not allowed.  */
10441   for (nl = sym->namelist; nl; nl = nl->next)
10442     {
10443       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
10444         continue;
10445
10446       if (nl->sym->attr.function && nl->sym == nl->sym->result)
10447         if ((nl->sym == sym->ns->proc_name)
10448                ||
10449             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
10450           continue;
10451
10452       nlsym = NULL;
10453       if (nl->sym && nl->sym->name)
10454         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
10455       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
10456         {
10457           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
10458                      "attribute in '%s' at %L", nlsym->name,
10459                      &sym->declared_at);
10460           return FAILURE;
10461         }
10462     }
10463
10464   return SUCCESS;
10465 }
10466
10467
10468 static gfc_try
10469 resolve_fl_parameter (gfc_symbol *sym)
10470 {
10471   /* A parameter array's shape needs to be constant.  */
10472   if (sym->as != NULL 
10473       && (sym->as->type == AS_DEFERRED
10474           || is_non_constant_shape_array (sym)))
10475     {
10476       gfc_error ("Parameter array '%s' at %L cannot be automatic "
10477                  "or of deferred shape", sym->name, &sym->declared_at);
10478       return FAILURE;
10479     }
10480
10481   /* Make sure a parameter that has been implicitly typed still
10482      matches the implicit type, since PARAMETER statements can precede
10483      IMPLICIT statements.  */
10484   if (sym->attr.implicit_type
10485       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
10486                                                              sym->ns)))
10487     {
10488       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
10489                  "later IMPLICIT type", sym->name, &sym->declared_at);
10490       return FAILURE;
10491     }
10492
10493   /* Make sure the types of derived parameters are consistent.  This
10494      type checking is deferred until resolution because the type may
10495      refer to a derived type from the host.  */
10496   if (sym->ts.type == BT_DERIVED
10497       && !gfc_compare_types (&sym->ts, &sym->value->ts))
10498     {
10499       gfc_error ("Incompatible derived type in PARAMETER at %L",
10500                  &sym->value->where);
10501       return FAILURE;
10502     }
10503   return SUCCESS;
10504 }
10505
10506
10507 /* Do anything necessary to resolve a symbol.  Right now, we just
10508    assume that an otherwise unknown symbol is a variable.  This sort
10509    of thing commonly happens for symbols in module.  */
10510
10511 static void
10512 resolve_symbol (gfc_symbol *sym)
10513 {
10514   int check_constant, mp_flag;
10515   gfc_symtree *symtree;
10516   gfc_symtree *this_symtree;
10517   gfc_namespace *ns;
10518   gfc_component *c;
10519
10520   if (sym->attr.flavor == FL_UNKNOWN)
10521     {
10522
10523     /* If we find that a flavorless symbol is an interface in one of the
10524        parent namespaces, find its symtree in this namespace, free the
10525        symbol and set the symtree to point to the interface symbol.  */
10526       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
10527         {
10528           symtree = gfc_find_symtree (ns->sym_root, sym->name);
10529           if (symtree && symtree->n.sym->generic)
10530             {
10531               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
10532                                                sym->name);
10533               sym->refs--;
10534               if (!sym->refs)
10535                 gfc_free_symbol (sym);
10536               symtree->n.sym->refs++;
10537               this_symtree->n.sym = symtree->n.sym;
10538               return;
10539             }
10540         }
10541
10542       /* Otherwise give it a flavor according to such attributes as
10543          it has.  */
10544       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
10545         sym->attr.flavor = FL_VARIABLE;
10546       else
10547         {
10548           sym->attr.flavor = FL_PROCEDURE;
10549           if (sym->attr.dimension)
10550             sym->attr.function = 1;
10551         }
10552     }
10553
10554   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
10555     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
10556
10557   if (sym->attr.procedure && sym->ts.interface
10558       && sym->attr.if_source != IFSRC_DECL)
10559     {
10560       if (sym->ts.interface == sym)
10561         {
10562           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
10563                      "interface", sym->name, &sym->declared_at);
10564           return;
10565         }
10566       if (sym->ts.interface->attr.procedure)
10567         {
10568           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
10569                      " in a later PROCEDURE statement", sym->ts.interface->name,
10570                      sym->name,&sym->declared_at);
10571           return;
10572         }
10573
10574       /* Get the attributes from the interface (now resolved).  */
10575       if (sym->ts.interface->attr.if_source
10576           || sym->ts.interface->attr.intrinsic)
10577         {
10578           gfc_symbol *ifc = sym->ts.interface;
10579           resolve_symbol (ifc);
10580
10581           if (ifc->attr.intrinsic)
10582             resolve_intrinsic (ifc, &ifc->declared_at);
10583
10584           if (ifc->result)
10585             sym->ts = ifc->result->ts;
10586           else   
10587             sym->ts = ifc->ts;
10588           sym->ts.interface = ifc;
10589           sym->attr.function = ifc->attr.function;
10590           sym->attr.subroutine = ifc->attr.subroutine;
10591           gfc_copy_formal_args (sym, ifc);
10592
10593           sym->attr.allocatable = ifc->attr.allocatable;
10594           sym->attr.pointer = ifc->attr.pointer;
10595           sym->attr.pure = ifc->attr.pure;
10596           sym->attr.elemental = ifc->attr.elemental;
10597           sym->attr.dimension = ifc->attr.dimension;
10598           sym->attr.recursive = ifc->attr.recursive;
10599           sym->attr.always_explicit = ifc->attr.always_explicit;
10600           sym->attr.ext_attr |= ifc->attr.ext_attr;
10601           /* Copy array spec.  */
10602           sym->as = gfc_copy_array_spec (ifc->as);
10603           if (sym->as)
10604             {
10605               int i;
10606               for (i = 0; i < sym->as->rank; i++)
10607                 {
10608                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
10609                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
10610                 }
10611             }
10612           /* Copy char length.  */
10613           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10614             {
10615               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10616               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
10617             }
10618         }
10619       else if (sym->ts.interface->name[0] != '\0')
10620         {
10621           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
10622                     sym->ts.interface->name, sym->name, &sym->declared_at);
10623           return;
10624         }
10625     }
10626
10627   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
10628     return;
10629
10630   /* Symbols that are module procedures with results (functions) have
10631      the types and array specification copied for type checking in
10632      procedures that call them, as well as for saving to a module
10633      file.  These symbols can't stand the scrutiny that their results
10634      can.  */
10635   mp_flag = (sym->result != NULL && sym->result != sym);
10636
10637
10638   /* Make sure that the intrinsic is consistent with its internal 
10639      representation. This needs to be done before assigning a default 
10640      type to avoid spurious warnings.  */
10641   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
10642       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
10643     return;
10644
10645   /* Assign default type to symbols that need one and don't have one.  */
10646   if (sym->ts.type == BT_UNKNOWN)
10647     {
10648       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
10649         gfc_set_default_type (sym, 1, NULL);
10650
10651       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
10652           && !sym->attr.function && !sym->attr.subroutine
10653           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
10654         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
10655
10656       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
10657         {
10658           /* The specific case of an external procedure should emit an error
10659              in the case that there is no implicit type.  */
10660           if (!mp_flag)
10661             gfc_set_default_type (sym, sym->attr.external, NULL);
10662           else
10663             {
10664               /* Result may be in another namespace.  */
10665               resolve_symbol (sym->result);
10666
10667               if (!sym->result->attr.proc_pointer)
10668                 {
10669                   sym->ts = sym->result->ts;
10670                   sym->as = gfc_copy_array_spec (sym->result->as);
10671                   sym->attr.dimension = sym->result->attr.dimension;
10672                   sym->attr.pointer = sym->result->attr.pointer;
10673                   sym->attr.allocatable = sym->result->attr.allocatable;
10674                 }
10675             }
10676         }
10677     }
10678
10679   /* Assumed size arrays and assumed shape arrays must be dummy
10680      arguments.  */
10681
10682   if (sym->as != NULL
10683       && (sym->as->type == AS_ASSUMED_SIZE
10684           || sym->as->type == AS_ASSUMED_SHAPE)
10685       && sym->attr.dummy == 0)
10686     {
10687       if (sym->as->type == AS_ASSUMED_SIZE)
10688         gfc_error ("Assumed size array at %L must be a dummy argument",
10689                    &sym->declared_at);
10690       else
10691         gfc_error ("Assumed shape array at %L must be a dummy argument",
10692                    &sym->declared_at);
10693       return;
10694     }
10695
10696   /* Make sure symbols with known intent or optional are really dummy
10697      variable.  Because of ENTRY statement, this has to be deferred
10698      until resolution time.  */
10699
10700   if (!sym->attr.dummy
10701       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
10702     {
10703       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
10704       return;
10705     }
10706
10707   if (sym->attr.value && !sym->attr.dummy)
10708     {
10709       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
10710                  "it is not a dummy argument", sym->name, &sym->declared_at);
10711       return;
10712     }
10713
10714   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
10715     {
10716       gfc_charlen *cl = sym->ts.u.cl;
10717       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10718         {
10719           gfc_error ("Character dummy variable '%s' at %L with VALUE "
10720                      "attribute must have constant length",
10721                      sym->name, &sym->declared_at);
10722           return;
10723         }
10724
10725       if (sym->ts.is_c_interop
10726           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
10727         {
10728           gfc_error ("C interoperable character dummy variable '%s' at %L "
10729                      "with VALUE attribute must have length one",
10730                      sym->name, &sym->declared_at);
10731           return;
10732         }
10733     }
10734
10735   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
10736      do this for something that was implicitly typed because that is handled
10737      in gfc_set_default_type.  Handle dummy arguments and procedure
10738      definitions separately.  Also, anything that is use associated is not
10739      handled here but instead is handled in the module it is declared in.
10740      Finally, derived type definitions are allowed to be BIND(C) since that
10741      only implies that they're interoperable, and they are checked fully for
10742      interoperability when a variable is declared of that type.  */
10743   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
10744       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
10745       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
10746     {
10747       gfc_try t = SUCCESS;
10748       
10749       /* First, make sure the variable is declared at the
10750          module-level scope (J3/04-007, Section 15.3).  */
10751       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
10752           sym->attr.in_common == 0)
10753         {
10754           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
10755                      "is neither a COMMON block nor declared at the "
10756                      "module level scope", sym->name, &(sym->declared_at));
10757           t = FAILURE;
10758         }
10759       else if (sym->common_head != NULL)
10760         {
10761           t = verify_com_block_vars_c_interop (sym->common_head);
10762         }
10763       else
10764         {
10765           /* If type() declaration, we need to verify that the components
10766              of the given type are all C interoperable, etc.  */
10767           if (sym->ts.type == BT_DERIVED &&
10768               sym->ts.u.derived->attr.is_c_interop != 1)
10769             {
10770               /* Make sure the user marked the derived type as BIND(C).  If
10771                  not, call the verify routine.  This could print an error
10772                  for the derived type more than once if multiple variables
10773                  of that type are declared.  */
10774               if (sym->ts.u.derived->attr.is_bind_c != 1)
10775                 verify_bind_c_derived_type (sym->ts.u.derived);
10776               t = FAILURE;
10777             }
10778           
10779           /* Verify the variable itself as C interoperable if it
10780              is BIND(C).  It is not possible for this to succeed if
10781              the verify_bind_c_derived_type failed, so don't have to handle
10782              any error returned by verify_bind_c_derived_type.  */
10783           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10784                                  sym->common_block);
10785         }
10786
10787       if (t == FAILURE)
10788         {
10789           /* clear the is_bind_c flag to prevent reporting errors more than
10790              once if something failed.  */
10791           sym->attr.is_bind_c = 0;
10792           return;
10793         }
10794     }
10795
10796   /* If a derived type symbol has reached this point, without its
10797      type being declared, we have an error.  Notice that most
10798      conditions that produce undefined derived types have already
10799      been dealt with.  However, the likes of:
10800      implicit type(t) (t) ..... call foo (t) will get us here if
10801      the type is not declared in the scope of the implicit
10802      statement. Change the type to BT_UNKNOWN, both because it is so
10803      and to prevent an ICE.  */
10804   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
10805       && !sym->ts.u.derived->attr.zero_comp)
10806     {
10807       gfc_error ("The derived type '%s' at %L is of type '%s', "
10808                  "which has not been defined", sym->name,
10809                   &sym->declared_at, sym->ts.u.derived->name);
10810       sym->ts.type = BT_UNKNOWN;
10811       return;
10812     }
10813
10814   /* Make sure that the derived type has been resolved and that the
10815      derived type is visible in the symbol's namespace, if it is a
10816      module function and is not PRIVATE.  */
10817   if (sym->ts.type == BT_DERIVED
10818         && sym->ts.u.derived->attr.use_assoc
10819         && sym->ns->proc_name
10820         && sym->ns->proc_name->attr.flavor == FL_MODULE)
10821     {
10822       gfc_symbol *ds;
10823
10824       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
10825         return;
10826
10827       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
10828       if (!ds && sym->attr.function
10829             && gfc_check_access (sym->attr.access, sym->ns->default_access))
10830         {
10831           symtree = gfc_new_symtree (&sym->ns->sym_root,
10832                                      sym->ts.u.derived->name);
10833           symtree->n.sym = sym->ts.u.derived;
10834           sym->ts.u.derived->refs++;
10835         }
10836     }
10837
10838   /* Unless the derived-type declaration is use associated, Fortran 95
10839      does not allow public entries of private derived types.
10840      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
10841      161 in 95-006r3.  */
10842   if (sym->ts.type == BT_DERIVED
10843       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
10844       && !sym->ts.u.derived->attr.use_assoc
10845       && gfc_check_access (sym->attr.access, sym->ns->default_access)
10846       && !gfc_check_access (sym->ts.u.derived->attr.access,
10847                             sym->ts.u.derived->ns->default_access)
10848       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
10849                          "of PRIVATE derived type '%s'",
10850                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
10851                          : "variable", sym->name, &sym->declared_at,
10852                          sym->ts.u.derived->name) == FAILURE)
10853     return;
10854
10855   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
10856      default initialization is defined (5.1.2.4.4).  */
10857   if (sym->ts.type == BT_DERIVED
10858       && sym->attr.dummy
10859       && sym->attr.intent == INTENT_OUT
10860       && sym->as
10861       && sym->as->type == AS_ASSUMED_SIZE)
10862     {
10863       for (c = sym->ts.u.derived->components; c; c = c->next)
10864         {
10865           if (c->initializer)
10866             {
10867               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
10868                          "ASSUMED SIZE and so cannot have a default initializer",
10869                          sym->name, &sym->declared_at);
10870               return;
10871             }
10872         }
10873     }
10874
10875   switch (sym->attr.flavor)
10876     {
10877     case FL_VARIABLE:
10878       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
10879         return;
10880       break;
10881
10882     case FL_PROCEDURE:
10883       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
10884         return;
10885       break;
10886
10887     case FL_NAMELIST:
10888       if (resolve_fl_namelist (sym) == FAILURE)
10889         return;
10890       break;
10891
10892     case FL_PARAMETER:
10893       if (resolve_fl_parameter (sym) == FAILURE)
10894         return;
10895       break;
10896
10897     default:
10898       break;
10899     }
10900
10901   /* Resolve array specifier. Check as well some constraints
10902      on COMMON blocks.  */
10903
10904   check_constant = sym->attr.in_common && !sym->attr.pointer;
10905
10906   /* Set the formal_arg_flag so that check_conflict will not throw
10907      an error for host associated variables in the specification
10908      expression for an array_valued function.  */
10909   if (sym->attr.function && sym->as)
10910     formal_arg_flag = 1;
10911
10912   gfc_resolve_array_spec (sym->as, check_constant);
10913
10914   formal_arg_flag = 0;
10915
10916   /* Resolve formal namespaces.  */
10917   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
10918       && !sym->attr.contained && !sym->attr.intrinsic)
10919     gfc_resolve (sym->formal_ns);
10920
10921   /* Make sure the formal namespace is present.  */
10922   if (sym->formal && !sym->formal_ns)
10923     {
10924       gfc_formal_arglist *formal = sym->formal;
10925       while (formal && !formal->sym)
10926         formal = formal->next;
10927
10928       if (formal)
10929         {
10930           sym->formal_ns = formal->sym->ns;
10931           sym->formal_ns->refs++;
10932         }
10933     }
10934
10935   /* Check threadprivate restrictions.  */
10936   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
10937       && (!sym->attr.in_common
10938           && sym->module == NULL
10939           && (sym->ns->proc_name == NULL
10940               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
10941     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
10942
10943   /* If we have come this far we can apply default-initializers, as
10944      described in 14.7.5, to those variables that have not already
10945      been assigned one.  */
10946   if (sym->ts.type == BT_DERIVED
10947       && sym->attr.referenced
10948       && sym->ns == gfc_current_ns
10949       && !sym->value
10950       && !sym->attr.allocatable
10951       && !sym->attr.alloc_comp)
10952     {
10953       symbol_attribute *a = &sym->attr;
10954
10955       if ((!a->save && !a->dummy && !a->pointer
10956            && !a->in_common && !a->use_assoc
10957            && !(a->function && sym != sym->result))
10958           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
10959         apply_default_init (sym);
10960     }
10961
10962   /* If this symbol has a type-spec, check it.  */
10963   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
10964       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
10965     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
10966           == FAILURE)
10967       return;
10968 }
10969
10970
10971 /************* Resolve DATA statements *************/
10972
10973 static struct
10974 {
10975   gfc_data_value *vnode;
10976   mpz_t left;
10977 }
10978 values;
10979
10980
10981 /* Advance the values structure to point to the next value in the data list.  */
10982
10983 static gfc_try
10984 next_data_value (void)
10985 {
10986   while (mpz_cmp_ui (values.left, 0) == 0)
10987     {
10988       if (!gfc_is_constant_expr (values.vnode->expr))
10989         gfc_error ("non-constant DATA value at %L",
10990                    &values.vnode->expr->where);
10991
10992       if (values.vnode->next == NULL)
10993         return FAILURE;
10994
10995       values.vnode = values.vnode->next;
10996       mpz_set (values.left, values.vnode->repeat);
10997     }
10998
10999   return SUCCESS;
11000 }
11001
11002
11003 static gfc_try
11004 check_data_variable (gfc_data_variable *var, locus *where)
11005 {
11006   gfc_expr *e;
11007   mpz_t size;
11008   mpz_t offset;
11009   gfc_try t;
11010   ar_type mark = AR_UNKNOWN;
11011   int i;
11012   mpz_t section_index[GFC_MAX_DIMENSIONS];
11013   gfc_ref *ref;
11014   gfc_array_ref *ar;
11015   gfc_symbol *sym;
11016   int has_pointer;
11017
11018   if (gfc_resolve_expr (var->expr) == FAILURE)
11019     return FAILURE;
11020
11021   ar = NULL;
11022   mpz_init_set_si (offset, 0);
11023   e = var->expr;
11024
11025   if (e->expr_type != EXPR_VARIABLE)
11026     gfc_internal_error ("check_data_variable(): Bad expression");
11027
11028   sym = e->symtree->n.sym;
11029
11030   if (sym->ns->is_block_data && !sym->attr.in_common)
11031     {
11032       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11033                  sym->name, &sym->declared_at);
11034     }
11035
11036   if (e->ref == NULL && sym->as)
11037     {
11038       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11039                  " declaration", sym->name, where);
11040       return FAILURE;
11041     }
11042
11043   has_pointer = sym->attr.pointer;
11044
11045   for (ref = e->ref; ref; ref = ref->next)
11046     {
11047       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11048         has_pointer = 1;
11049
11050       if (has_pointer
11051             && ref->type == REF_ARRAY
11052             && ref->u.ar.type != AR_FULL)
11053           {
11054             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11055                         "be a full array", sym->name, where);
11056             return FAILURE;
11057           }
11058     }
11059
11060   if (e->rank == 0 || has_pointer)
11061     {
11062       mpz_init_set_ui (size, 1);
11063       ref = NULL;
11064     }
11065   else
11066     {
11067       ref = e->ref;
11068
11069       /* Find the array section reference.  */
11070       for (ref = e->ref; ref; ref = ref->next)
11071         {
11072           if (ref->type != REF_ARRAY)
11073             continue;
11074           if (ref->u.ar.type == AR_ELEMENT)
11075             continue;
11076           break;
11077         }
11078       gcc_assert (ref);
11079
11080       /* Set marks according to the reference pattern.  */
11081       switch (ref->u.ar.type)
11082         {
11083         case AR_FULL:
11084           mark = AR_FULL;
11085           break;
11086
11087         case AR_SECTION:
11088           ar = &ref->u.ar;
11089           /* Get the start position of array section.  */
11090           gfc_get_section_index (ar, section_index, &offset);
11091           mark = AR_SECTION;
11092           break;
11093
11094         default:
11095           gcc_unreachable ();
11096         }
11097
11098       if (gfc_array_size (e, &size) == FAILURE)
11099         {
11100           gfc_error ("Nonconstant array section at %L in DATA statement",
11101                      &e->where);
11102           mpz_clear (offset);
11103           return FAILURE;
11104         }
11105     }
11106
11107   t = SUCCESS;
11108
11109   while (mpz_cmp_ui (size, 0) > 0)
11110     {
11111       if (next_data_value () == FAILURE)
11112         {
11113           gfc_error ("DATA statement at %L has more variables than values",
11114                      where);
11115           t = FAILURE;
11116           break;
11117         }
11118
11119       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
11120       if (t == FAILURE)
11121         break;
11122
11123       /* If we have more than one element left in the repeat count,
11124          and we have more than one element left in the target variable,
11125          then create a range assignment.  */
11126       /* FIXME: Only done for full arrays for now, since array sections
11127          seem tricky.  */
11128       if (mark == AR_FULL && ref && ref->next == NULL
11129           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
11130         {
11131           mpz_t range;
11132
11133           if (mpz_cmp (size, values.left) >= 0)
11134             {
11135               mpz_init_set (range, values.left);
11136               mpz_sub (size, size, values.left);
11137               mpz_set_ui (values.left, 0);
11138             }
11139           else
11140             {
11141               mpz_init_set (range, size);
11142               mpz_sub (values.left, values.left, size);
11143               mpz_set_ui (size, 0);
11144             }
11145
11146           gfc_assign_data_value_range (var->expr, values.vnode->expr,
11147                                        offset, range);
11148
11149           mpz_add (offset, offset, range);
11150           mpz_clear (range);
11151         }
11152
11153       /* Assign initial value to symbol.  */
11154       else
11155         {
11156           mpz_sub_ui (values.left, values.left, 1);
11157           mpz_sub_ui (size, size, 1);
11158
11159           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11160           if (t == FAILURE)
11161             break;
11162
11163           if (mark == AR_FULL)
11164             mpz_add_ui (offset, offset, 1);
11165
11166           /* Modify the array section indexes and recalculate the offset
11167              for next element.  */
11168           else if (mark == AR_SECTION)
11169             gfc_advance_section (section_index, ar, &offset);
11170         }
11171     }
11172
11173   if (mark == AR_SECTION)
11174     {
11175       for (i = 0; i < ar->dimen; i++)
11176         mpz_clear (section_index[i]);
11177     }
11178
11179   mpz_clear (size);
11180   mpz_clear (offset);
11181
11182   return t;
11183 }
11184
11185
11186 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11187
11188 /* Iterate over a list of elements in a DATA statement.  */
11189
11190 static gfc_try
11191 traverse_data_list (gfc_data_variable *var, locus *where)
11192 {
11193   mpz_t trip;
11194   iterator_stack frame;
11195   gfc_expr *e, *start, *end, *step;
11196   gfc_try retval = SUCCESS;
11197
11198   mpz_init (frame.value);
11199
11200   start = gfc_copy_expr (var->iter.start);
11201   end = gfc_copy_expr (var->iter.end);
11202   step = gfc_copy_expr (var->iter.step);
11203
11204   if (gfc_simplify_expr (start, 1) == FAILURE
11205       || start->expr_type != EXPR_CONSTANT)
11206     {
11207       gfc_error ("iterator start at %L does not simplify", &start->where);
11208       retval = FAILURE;
11209       goto cleanup;
11210     }
11211   if (gfc_simplify_expr (end, 1) == FAILURE
11212       || end->expr_type != EXPR_CONSTANT)
11213     {
11214       gfc_error ("iterator end at %L does not simplify", &end->where);
11215       retval = FAILURE;
11216       goto cleanup;
11217     }
11218   if (gfc_simplify_expr (step, 1) == FAILURE
11219       || step->expr_type != EXPR_CONSTANT)
11220     {
11221       gfc_error ("iterator step at %L does not simplify", &step->where);
11222       retval = FAILURE;
11223       goto cleanup;
11224     }
11225
11226   mpz_init_set (trip, end->value.integer);
11227   mpz_sub (trip, trip, start->value.integer);
11228   mpz_add (trip, trip, step->value.integer);
11229
11230   mpz_div (trip, trip, step->value.integer);
11231
11232   mpz_set (frame.value, start->value.integer);
11233
11234   frame.prev = iter_stack;
11235   frame.variable = var->iter.var->symtree;
11236   iter_stack = &frame;
11237
11238   while (mpz_cmp_ui (trip, 0) > 0)
11239     {
11240       if (traverse_data_var (var->list, where) == FAILURE)
11241         {
11242           mpz_clear (trip);
11243           retval = FAILURE;
11244           goto cleanup;
11245         }
11246
11247       e = gfc_copy_expr (var->expr);
11248       if (gfc_simplify_expr (e, 1) == FAILURE)
11249         {
11250           gfc_free_expr (e);
11251           mpz_clear (trip);
11252           retval = FAILURE;
11253           goto cleanup;
11254         }
11255
11256       mpz_add (frame.value, frame.value, step->value.integer);
11257
11258       mpz_sub_ui (trip, trip, 1);
11259     }
11260
11261   mpz_clear (trip);
11262 cleanup:
11263   mpz_clear (frame.value);
11264
11265   gfc_free_expr (start);
11266   gfc_free_expr (end);
11267   gfc_free_expr (step);
11268
11269   iter_stack = frame.prev;
11270   return retval;
11271 }
11272
11273
11274 /* Type resolve variables in the variable list of a DATA statement.  */
11275
11276 static gfc_try
11277 traverse_data_var (gfc_data_variable *var, locus *where)
11278 {
11279   gfc_try t;
11280
11281   for (; var; var = var->next)
11282     {
11283       if (var->expr == NULL)
11284         t = traverse_data_list (var, where);
11285       else
11286         t = check_data_variable (var, where);
11287
11288       if (t == FAILURE)
11289         return FAILURE;
11290     }
11291
11292   return SUCCESS;
11293 }
11294
11295
11296 /* Resolve the expressions and iterators associated with a data statement.
11297    This is separate from the assignment checking because data lists should
11298    only be resolved once.  */
11299
11300 static gfc_try
11301 resolve_data_variables (gfc_data_variable *d)
11302 {
11303   for (; d; d = d->next)
11304     {
11305       if (d->list == NULL)
11306         {
11307           if (gfc_resolve_expr (d->expr) == FAILURE)
11308             return FAILURE;
11309         }
11310       else
11311         {
11312           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
11313             return FAILURE;
11314
11315           if (resolve_data_variables (d->list) == FAILURE)
11316             return FAILURE;
11317         }
11318     }
11319
11320   return SUCCESS;
11321 }
11322
11323
11324 /* Resolve a single DATA statement.  We implement this by storing a pointer to
11325    the value list into static variables, and then recursively traversing the
11326    variables list, expanding iterators and such.  */
11327
11328 static void
11329 resolve_data (gfc_data *d)
11330 {
11331
11332   if (resolve_data_variables (d->var) == FAILURE)
11333     return;
11334
11335   values.vnode = d->value;
11336   if (d->value == NULL)
11337     mpz_set_ui (values.left, 0);
11338   else
11339     mpz_set (values.left, d->value->repeat);
11340
11341   if (traverse_data_var (d->var, &d->where) == FAILURE)
11342     return;
11343
11344   /* At this point, we better not have any values left.  */
11345
11346   if (next_data_value () == SUCCESS)
11347     gfc_error ("DATA statement at %L has more values than variables",
11348                &d->where);
11349 }
11350
11351
11352 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
11353    accessed by host or use association, is a dummy argument to a pure function,
11354    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
11355    is storage associated with any such variable, shall not be used in the
11356    following contexts: (clients of this function).  */
11357
11358 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
11359    procedure.  Returns zero if assignment is OK, nonzero if there is a
11360    problem.  */
11361 int
11362 gfc_impure_variable (gfc_symbol *sym)
11363 {
11364   gfc_symbol *proc;
11365
11366   if (sym->attr.use_assoc || sym->attr.in_common)
11367     return 1;
11368
11369   if (sym->ns != gfc_current_ns)
11370     return !sym->attr.function;
11371
11372   proc = sym->ns->proc_name;
11373   if (sym->attr.dummy && gfc_pure (proc)
11374         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
11375                 ||
11376              proc->attr.function))
11377     return 1;
11378
11379   /* TODO: Sort out what can be storage associated, if anything, and include
11380      it here.  In principle equivalences should be scanned but it does not
11381      seem to be possible to storage associate an impure variable this way.  */
11382   return 0;
11383 }
11384
11385
11386 /* Test whether a symbol is pure or not.  For a NULL pointer, checks the
11387    symbol of the current procedure.  */
11388
11389 int
11390 gfc_pure (gfc_symbol *sym)
11391 {
11392   symbol_attribute attr;
11393
11394   if (sym == NULL)
11395     sym = gfc_current_ns->proc_name;
11396   if (sym == NULL)
11397     return 0;
11398
11399   attr = sym->attr;
11400
11401   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
11402 }
11403
11404
11405 /* Test whether the current procedure is elemental or not.  */
11406
11407 int
11408 gfc_elemental (gfc_symbol *sym)
11409 {
11410   symbol_attribute attr;
11411
11412   if (sym == NULL)
11413     sym = gfc_current_ns->proc_name;
11414   if (sym == NULL)
11415     return 0;
11416   attr = sym->attr;
11417
11418   return attr.flavor == FL_PROCEDURE && attr.elemental;
11419 }
11420
11421
11422 /* Warn about unused labels.  */
11423
11424 static void
11425 warn_unused_fortran_label (gfc_st_label *label)
11426 {
11427   if (label == NULL)
11428     return;
11429
11430   warn_unused_fortran_label (label->left);
11431
11432   if (label->defined == ST_LABEL_UNKNOWN)
11433     return;
11434
11435   switch (label->referenced)
11436     {
11437     case ST_LABEL_UNKNOWN:
11438       gfc_warning ("Label %d at %L defined but not used", label->value,
11439                    &label->where);
11440       break;
11441
11442     case ST_LABEL_BAD_TARGET:
11443       gfc_warning ("Label %d at %L defined but cannot be used",
11444                    label->value, &label->where);
11445       break;
11446
11447     default:
11448       break;
11449     }
11450
11451   warn_unused_fortran_label (label->right);
11452 }
11453
11454
11455 /* Returns the sequence type of a symbol or sequence.  */
11456
11457 static seq_type
11458 sequence_type (gfc_typespec ts)
11459 {
11460   seq_type result;
11461   gfc_component *c;
11462
11463   switch (ts.type)
11464   {
11465     case BT_DERIVED:
11466
11467       if (ts.u.derived->components == NULL)
11468         return SEQ_NONDEFAULT;
11469
11470       result = sequence_type (ts.u.derived->components->ts);
11471       for (c = ts.u.derived->components->next; c; c = c->next)
11472         if (sequence_type (c->ts) != result)
11473           return SEQ_MIXED;
11474
11475       return result;
11476
11477     case BT_CHARACTER:
11478       if (ts.kind != gfc_default_character_kind)
11479           return SEQ_NONDEFAULT;
11480
11481       return SEQ_CHARACTER;
11482
11483     case BT_INTEGER:
11484       if (ts.kind != gfc_default_integer_kind)
11485           return SEQ_NONDEFAULT;
11486
11487       return SEQ_NUMERIC;
11488
11489     case BT_REAL:
11490       if (!(ts.kind == gfc_default_real_kind
11491             || ts.kind == gfc_default_double_kind))
11492           return SEQ_NONDEFAULT;
11493
11494       return SEQ_NUMERIC;
11495
11496     case BT_COMPLEX:
11497       if (ts.kind != gfc_default_complex_kind)
11498           return SEQ_NONDEFAULT;
11499
11500       return SEQ_NUMERIC;
11501
11502     case BT_LOGICAL:
11503       if (ts.kind != gfc_default_logical_kind)
11504           return SEQ_NONDEFAULT;
11505
11506       return SEQ_NUMERIC;
11507
11508     default:
11509       return SEQ_NONDEFAULT;
11510   }
11511 }
11512
11513
11514 /* Resolve derived type EQUIVALENCE object.  */
11515
11516 static gfc_try
11517 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
11518 {
11519   gfc_component *c = derived->components;
11520
11521   if (!derived)
11522     return SUCCESS;
11523
11524   /* Shall not be an object of nonsequence derived type.  */
11525   if (!derived->attr.sequence)
11526     {
11527       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
11528                  "attribute to be an EQUIVALENCE object", sym->name,
11529                  &e->where);
11530       return FAILURE;
11531     }
11532
11533   /* Shall not have allocatable components.  */
11534   if (derived->attr.alloc_comp)
11535     {
11536       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
11537                  "components to be an EQUIVALENCE object",sym->name,
11538                  &e->where);
11539       return FAILURE;
11540     }
11541
11542   if (sym->attr.in_common && has_default_initializer (sym->ts.u.derived))
11543     {
11544       gfc_error ("Derived type variable '%s' at %L with default "
11545                  "initialization cannot be in EQUIVALENCE with a variable "
11546                  "in COMMON", sym->name, &e->where);
11547       return FAILURE;
11548     }
11549
11550   for (; c ; c = c->next)
11551     {
11552       if (c->ts.type == BT_DERIVED
11553           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
11554         return FAILURE;
11555
11556       /* Shall not be an object of sequence derived type containing a pointer
11557          in the structure.  */
11558       if (c->attr.pointer)
11559         {
11560           gfc_error ("Derived type variable '%s' at %L with pointer "
11561                      "component(s) cannot be an EQUIVALENCE object",
11562                      sym->name, &e->where);
11563           return FAILURE;
11564         }
11565     }
11566   return SUCCESS;
11567 }
11568
11569
11570 /* Resolve equivalence object. 
11571    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
11572    an allocatable array, an object of nonsequence derived type, an object of
11573    sequence derived type containing a pointer at any level of component
11574    selection, an automatic object, a function name, an entry name, a result
11575    name, a named constant, a structure component, or a subobject of any of
11576    the preceding objects.  A substring shall not have length zero.  A
11577    derived type shall not have components with default initialization nor
11578    shall two objects of an equivalence group be initialized.
11579    Either all or none of the objects shall have an protected attribute.
11580    The simple constraints are done in symbol.c(check_conflict) and the rest
11581    are implemented here.  */
11582
11583 static void
11584 resolve_equivalence (gfc_equiv *eq)
11585 {
11586   gfc_symbol *sym;
11587   gfc_symbol *first_sym;
11588   gfc_expr *e;
11589   gfc_ref *r;
11590   locus *last_where = NULL;
11591   seq_type eq_type, last_eq_type;
11592   gfc_typespec *last_ts;
11593   int object, cnt_protected;
11594   const char *value_name;
11595   const char *msg;
11596
11597   value_name = NULL;
11598   last_ts = &eq->expr->symtree->n.sym->ts;
11599
11600   first_sym = eq->expr->symtree->n.sym;
11601
11602   cnt_protected = 0;
11603
11604   for (object = 1; eq; eq = eq->eq, object++)
11605     {
11606       e = eq->expr;
11607
11608       e->ts = e->symtree->n.sym->ts;
11609       /* match_varspec might not know yet if it is seeing
11610          array reference or substring reference, as it doesn't
11611          know the types.  */
11612       if (e->ref && e->ref->type == REF_ARRAY)
11613         {
11614           gfc_ref *ref = e->ref;
11615           sym = e->symtree->n.sym;
11616
11617           if (sym->attr.dimension)
11618             {
11619               ref->u.ar.as = sym->as;
11620               ref = ref->next;
11621             }
11622
11623           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
11624           if (e->ts.type == BT_CHARACTER
11625               && ref
11626               && ref->type == REF_ARRAY
11627               && ref->u.ar.dimen == 1
11628               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
11629               && ref->u.ar.stride[0] == NULL)
11630             {
11631               gfc_expr *start = ref->u.ar.start[0];
11632               gfc_expr *end = ref->u.ar.end[0];
11633               void *mem = NULL;
11634
11635               /* Optimize away the (:) reference.  */
11636               if (start == NULL && end == NULL)
11637                 {
11638                   if (e->ref == ref)
11639                     e->ref = ref->next;
11640                   else
11641                     e->ref->next = ref->next;
11642                   mem = ref;
11643                 }
11644               else
11645                 {
11646                   ref->type = REF_SUBSTRING;
11647                   if (start == NULL)
11648                     start = gfc_int_expr (1);
11649                   ref->u.ss.start = start;
11650                   if (end == NULL && e->ts.u.cl)
11651                     end = gfc_copy_expr (e->ts.u.cl->length);
11652                   ref->u.ss.end = end;
11653                   ref->u.ss.length = e->ts.u.cl;
11654                   e->ts.u.cl = NULL;
11655                 }
11656               ref = ref->next;
11657               gfc_free (mem);
11658             }
11659
11660           /* Any further ref is an error.  */
11661           if (ref)
11662             {
11663               gcc_assert (ref->type == REF_ARRAY);
11664               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
11665                          &ref->u.ar.where);
11666               continue;
11667             }
11668         }
11669
11670       if (gfc_resolve_expr (e) == FAILURE)
11671         continue;
11672
11673       sym = e->symtree->n.sym;
11674
11675       if (sym->attr.is_protected)
11676         cnt_protected++;
11677       if (cnt_protected > 0 && cnt_protected != object)
11678         {
11679               gfc_error ("Either all or none of the objects in the "
11680                          "EQUIVALENCE set at %L shall have the "
11681                          "PROTECTED attribute",
11682                          &e->where);
11683               break;
11684         }
11685
11686       /* Shall not equivalence common block variables in a PURE procedure.  */
11687       if (sym->ns->proc_name
11688           && sym->ns->proc_name->attr.pure
11689           && sym->attr.in_common)
11690         {
11691           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
11692                      "object in the pure procedure '%s'",
11693                      sym->name, &e->where, sym->ns->proc_name->name);
11694           break;
11695         }
11696
11697       /* Shall not be a named constant.  */
11698       if (e->expr_type == EXPR_CONSTANT)
11699         {
11700           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
11701                      "object", sym->name, &e->where);
11702           continue;
11703         }
11704
11705       if (e->ts.type == BT_DERIVED
11706           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
11707         continue;
11708
11709       /* Check that the types correspond correctly:
11710          Note 5.28:
11711          A numeric sequence structure may be equivalenced to another sequence
11712          structure, an object of default integer type, default real type, double
11713          precision real type, default logical type such that components of the
11714          structure ultimately only become associated to objects of the same
11715          kind. A character sequence structure may be equivalenced to an object
11716          of default character kind or another character sequence structure.
11717          Other objects may be equivalenced only to objects of the same type and
11718          kind parameters.  */
11719
11720       /* Identical types are unconditionally OK.  */
11721       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
11722         goto identical_types;
11723
11724       last_eq_type = sequence_type (*last_ts);
11725       eq_type = sequence_type (sym->ts);
11726
11727       /* Since the pair of objects is not of the same type, mixed or
11728          non-default sequences can be rejected.  */
11729
11730       msg = "Sequence %s with mixed components in EQUIVALENCE "
11731             "statement at %L with different type objects";
11732       if ((object ==2
11733            && last_eq_type == SEQ_MIXED
11734            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
11735               == FAILURE)
11736           || (eq_type == SEQ_MIXED
11737               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11738                                  &e->where) == FAILURE))
11739         continue;
11740
11741       msg = "Non-default type object or sequence %s in EQUIVALENCE "
11742             "statement at %L with objects of different type";
11743       if ((object ==2
11744            && last_eq_type == SEQ_NONDEFAULT
11745            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
11746                               last_where) == FAILURE)
11747           || (eq_type == SEQ_NONDEFAULT
11748               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11749                                  &e->where) == FAILURE))
11750         continue;
11751
11752       msg ="Non-CHARACTER object '%s' in default CHARACTER "
11753            "EQUIVALENCE statement at %L";
11754       if (last_eq_type == SEQ_CHARACTER
11755           && eq_type != SEQ_CHARACTER
11756           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11757                              &e->where) == FAILURE)
11758                 continue;
11759
11760       msg ="Non-NUMERIC object '%s' in default NUMERIC "
11761            "EQUIVALENCE statement at %L";
11762       if (last_eq_type == SEQ_NUMERIC
11763           && eq_type != SEQ_NUMERIC
11764           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11765                              &e->where) == FAILURE)
11766                 continue;
11767
11768   identical_types:
11769       last_ts =&sym->ts;
11770       last_where = &e->where;
11771
11772       if (!e->ref)
11773         continue;
11774
11775       /* Shall not be an automatic array.  */
11776       if (e->ref->type == REF_ARRAY
11777           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
11778         {
11779           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
11780                      "an EQUIVALENCE object", sym->name, &e->where);
11781           continue;
11782         }
11783
11784       r = e->ref;
11785       while (r)
11786         {
11787           /* Shall not be a structure component.  */
11788           if (r->type == REF_COMPONENT)
11789             {
11790               gfc_error ("Structure component '%s' at %L cannot be an "
11791                          "EQUIVALENCE object",
11792                          r->u.c.component->name, &e->where);
11793               break;
11794             }
11795
11796           /* A substring shall not have length zero.  */
11797           if (r->type == REF_SUBSTRING)
11798             {
11799               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
11800                 {
11801                   gfc_error ("Substring at %L has length zero",
11802                              &r->u.ss.start->where);
11803                   break;
11804                 }
11805             }
11806           r = r->next;
11807         }
11808     }
11809 }
11810
11811
11812 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
11813
11814 static void
11815 resolve_fntype (gfc_namespace *ns)
11816 {
11817   gfc_entry_list *el;
11818   gfc_symbol *sym;
11819
11820   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
11821     return;
11822
11823   /* If there are any entries, ns->proc_name is the entry master
11824      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
11825   if (ns->entries)
11826     sym = ns->entries->sym;
11827   else
11828     sym = ns->proc_name;
11829   if (sym->result == sym
11830       && sym->ts.type == BT_UNKNOWN
11831       && gfc_set_default_type (sym, 0, NULL) == FAILURE
11832       && !sym->attr.untyped)
11833     {
11834       gfc_error ("Function '%s' at %L has no IMPLICIT type",
11835                  sym->name, &sym->declared_at);
11836       sym->attr.untyped = 1;
11837     }
11838
11839   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
11840       && !sym->attr.contained
11841       && !gfc_check_access (sym->ts.u.derived->attr.access,
11842                             sym->ts.u.derived->ns->default_access)
11843       && gfc_check_access (sym->attr.access, sym->ns->default_access))
11844     {
11845       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
11846                       "%L of PRIVATE type '%s'", sym->name,
11847                       &sym->declared_at, sym->ts.u.derived->name);
11848     }
11849
11850     if (ns->entries)
11851     for (el = ns->entries->next; el; el = el->next)
11852       {
11853         if (el->sym->result == el->sym
11854             && el->sym->ts.type == BT_UNKNOWN
11855             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
11856             && !el->sym->attr.untyped)
11857           {
11858             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
11859                        el->sym->name, &el->sym->declared_at);
11860             el->sym->attr.untyped = 1;
11861           }
11862       }
11863 }
11864
11865
11866 /* 12.3.2.1.1 Defined operators.  */
11867
11868 static gfc_try
11869 check_uop_procedure (gfc_symbol *sym, locus where)
11870 {
11871   gfc_formal_arglist *formal;
11872
11873   if (!sym->attr.function)
11874     {
11875       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
11876                  sym->name, &where);
11877       return FAILURE;
11878     }
11879
11880   if (sym->ts.type == BT_CHARACTER
11881       && !(sym->ts.u.cl && sym->ts.u.cl->length)
11882       && !(sym->result && sym->result->ts.u.cl
11883            && sym->result->ts.u.cl->length))
11884     {
11885       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
11886                  "character length", sym->name, &where);
11887       return FAILURE;
11888     }
11889
11890   formal = sym->formal;
11891   if (!formal || !formal->sym)
11892     {
11893       gfc_error ("User operator procedure '%s' at %L must have at least "
11894                  "one argument", sym->name, &where);
11895       return FAILURE;
11896     }
11897
11898   if (formal->sym->attr.intent != INTENT_IN)
11899     {
11900       gfc_error ("First argument of operator interface at %L must be "
11901                  "INTENT(IN)", &where);
11902       return FAILURE;
11903     }
11904
11905   if (formal->sym->attr.optional)
11906     {
11907       gfc_error ("First argument of operator interface at %L cannot be "
11908                  "optional", &where);
11909       return FAILURE;
11910     }
11911
11912   formal = formal->next;
11913   if (!formal || !formal->sym)
11914     return SUCCESS;
11915
11916   if (formal->sym->attr.intent != INTENT_IN)
11917     {
11918       gfc_error ("Second argument of operator interface at %L must be "
11919                  "INTENT(IN)", &where);
11920       return FAILURE;
11921     }
11922
11923   if (formal->sym->attr.optional)
11924     {
11925       gfc_error ("Second argument of operator interface at %L cannot be "
11926                  "optional", &where);
11927       return FAILURE;
11928     }
11929
11930   if (formal->next)
11931     {
11932       gfc_error ("Operator interface at %L must have, at most, two "
11933                  "arguments", &where);
11934       return FAILURE;
11935     }
11936
11937   return SUCCESS;
11938 }
11939
11940 static void
11941 gfc_resolve_uops (gfc_symtree *symtree)
11942 {
11943   gfc_interface *itr;
11944
11945   if (symtree == NULL)
11946     return;
11947
11948   gfc_resolve_uops (symtree->left);
11949   gfc_resolve_uops (symtree->right);
11950
11951   for (itr = symtree->n.uop->op; itr; itr = itr->next)
11952     check_uop_procedure (itr->sym, itr->sym->declared_at);
11953 }
11954
11955
11956 /* Examine all of the expressions associated with a program unit,
11957    assign types to all intermediate expressions, make sure that all
11958    assignments are to compatible types and figure out which names
11959    refer to which functions or subroutines.  It doesn't check code
11960    block, which is handled by resolve_code.  */
11961
11962 static void
11963 resolve_types (gfc_namespace *ns)
11964 {
11965   gfc_namespace *n;
11966   gfc_charlen *cl;
11967   gfc_data *d;
11968   gfc_equiv *eq;
11969   gfc_namespace* old_ns = gfc_current_ns;
11970
11971   /* Check that all IMPLICIT types are ok.  */
11972   if (!ns->seen_implicit_none)
11973     {
11974       unsigned letter;
11975       for (letter = 0; letter != GFC_LETTERS; ++letter)
11976         if (ns->set_flag[letter]
11977             && resolve_typespec_used (&ns->default_type[letter],
11978                                       &ns->implicit_loc[letter],
11979                                       NULL) == FAILURE)
11980           return;
11981     }
11982
11983   gfc_current_ns = ns;
11984
11985   resolve_entries (ns);
11986
11987   resolve_common_vars (ns->blank_common.head, false);
11988   resolve_common_blocks (ns->common_root);
11989
11990   resolve_contained_functions (ns);
11991
11992   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
11993
11994   for (cl = ns->cl_list; cl; cl = cl->next)
11995     resolve_charlen (cl);
11996
11997   gfc_traverse_ns (ns, resolve_symbol);
11998
11999   resolve_fntype (ns);
12000
12001   for (n = ns->contained; n; n = n->sibling)
12002     {
12003       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12004         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12005                    "also be PURE", n->proc_name->name,
12006                    &n->proc_name->declared_at);
12007
12008       resolve_types (n);
12009     }
12010
12011   forall_flag = 0;
12012   gfc_check_interfaces (ns);
12013
12014   gfc_traverse_ns (ns, resolve_values);
12015
12016   if (ns->save_all)
12017     gfc_save_all (ns);
12018
12019   iter_stack = NULL;
12020   for (d = ns->data; d; d = d->next)
12021     resolve_data (d);
12022
12023   iter_stack = NULL;
12024   gfc_traverse_ns (ns, gfc_formalize_init_value);
12025
12026   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12027
12028   if (ns->common_root != NULL)
12029     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12030
12031   for (eq = ns->equiv; eq; eq = eq->next)
12032     resolve_equivalence (eq);
12033
12034   /* Warn about unused labels.  */
12035   if (warn_unused_label)
12036     warn_unused_fortran_label (ns->st_labels);
12037
12038   gfc_resolve_uops (ns->uop_root);
12039
12040   gfc_current_ns = old_ns;
12041 }
12042
12043
12044 /* Call resolve_code recursively.  */
12045
12046 static void
12047 resolve_codes (gfc_namespace *ns)
12048 {
12049   gfc_namespace *n;
12050   bitmap_obstack old_obstack;
12051
12052   for (n = ns->contained; n; n = n->sibling)
12053     resolve_codes (n);
12054
12055   gfc_current_ns = ns;
12056   cs_base = NULL;
12057   /* Set to an out of range value.  */
12058   current_entry_id = -1;
12059
12060   old_obstack = labels_obstack;
12061   bitmap_obstack_initialize (&labels_obstack);
12062
12063   resolve_code (ns->code, ns);
12064
12065   bitmap_obstack_release (&labels_obstack);
12066   labels_obstack = old_obstack;
12067 }
12068
12069
12070 /* This function is called after a complete program unit has been compiled.
12071    Its purpose is to examine all of the expressions associated with a program
12072    unit, assign types to all intermediate expressions, make sure that all
12073    assignments are to compatible types and figure out which names refer to
12074    which functions or subroutines.  */
12075
12076 void
12077 gfc_resolve (gfc_namespace *ns)
12078 {
12079   gfc_namespace *old_ns;
12080   code_stack *old_cs_base;
12081
12082   if (ns->resolved)
12083     return;
12084
12085   ns->resolved = -1;
12086   old_ns = gfc_current_ns;
12087   old_cs_base = cs_base;
12088
12089   resolve_types (ns);
12090   resolve_codes (ns);
12091
12092   gfc_current_ns = old_ns;
12093   cs_base = old_cs_base;
12094   ns->resolved = 1;
12095 }