OSDN Git Service

2009-10-13 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->class_object
5165                 = class_object;
5166       list_e->value.function.class_esym->esym
5167                 = e->value.function.esym;
5168     }
5169
5170   gfc_free_expr (e);
5171   
5172   /* Burrow down into grandchildren types.  */
5173   if (derived->f2k_derived)
5174     gfc_traverse_ns (derived->f2k_derived, check_members);
5175 }
5176
5177
5178 /* Eliminate esym_lists where all the members point to the
5179    typebound procedure of the declared type; ie. one where
5180    type selection has no effect..  */
5181 static void
5182 resolve_class_esym (gfc_expr *e)
5183 {
5184   gfc_class_esym_list *p, *q;
5185   bool empty = true;
5186
5187   gcc_assert (e && e->expr_type == EXPR_FUNCTION);
5188
5189   p = e->value.function.class_esym;
5190   if (p == NULL)
5191     return;
5192
5193   for (; p; p = p->next)
5194     empty = empty && (e->value.function.esym == p->esym);
5195
5196   if (empty)
5197     {
5198       p = e->value.function.class_esym;
5199       for (; p; p = q)
5200         {
5201           q = p->next;
5202           gfc_free (p);
5203         }
5204       e->value.function.class_esym = NULL;
5205    }
5206 }
5207
5208
5209 /* Resolve a CLASS typebound function, or 'method'.  */
5210 static gfc_try
5211 resolve_class_compcall (gfc_expr* e)
5212 {
5213   gfc_symbol *derived;
5214
5215   class_object = e->symtree->n.sym;
5216
5217   /* Get the CLASS type.  */
5218   derived = e->symtree->n.sym->ts.u.derived;
5219
5220   /* Get the data component, which is of the declared type.  */
5221   derived = derived->components->ts.u.derived;
5222
5223   /* Resolve the function call for each member of the class.  */
5224   class_try = SUCCESS;
5225   fcn_flag = true;
5226   list_e = gfc_copy_expr (e);
5227   check_class_members (derived);
5228
5229   class_try = (resolve_compcall (e, true) == SUCCESS)
5230                  ? class_try : FAILURE;
5231
5232   /* Transfer the class list to the original expression.  Note that
5233      the class_esym list is cleaned up in trans-expr.c, as the calls
5234      are translated.  */
5235   e->value.function.class_esym = list_e->value.function.class_esym;
5236   list_e->value.function.class_esym = NULL;
5237   gfc_free_expr (list_e);
5238
5239   resolve_class_esym (e);
5240
5241   return class_try;
5242 }
5243
5244 /* Resolve a CLASS typebound subroutine, or 'method'.  */
5245 static gfc_try
5246 resolve_class_typebound_call (gfc_code *code)
5247 {
5248   gfc_symbol *derived;
5249
5250   class_object = code->expr1->symtree->n.sym;
5251
5252   /* Get the CLASS type.  */
5253   derived = code->expr1->symtree->n.sym->ts.u.derived;
5254
5255   /* Get the data component, which is of the declared type.  */
5256   derived = derived->components->ts.u.derived;
5257
5258   class_try = SUCCESS;
5259   fcn_flag = false;
5260   list_e = gfc_copy_expr (code->expr1);
5261   check_class_members (derived);
5262
5263   class_try = (resolve_typebound_call (code) == SUCCESS)
5264                  ? class_try : FAILURE;
5265
5266   /* Transfer the class list to the original expression.  Note that
5267      the class_esym list is cleaned up in trans-expr.c, as the calls
5268      are translated.  */
5269   code->expr1->value.function.class_esym
5270                         = list_e->value.function.class_esym;
5271   list_e->value.function.class_esym = NULL;
5272   gfc_free_expr (list_e);
5273
5274   resolve_class_esym (code->expr1);
5275
5276   return class_try;
5277 }
5278
5279
5280 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5281
5282 static gfc_try
5283 resolve_ppc_call (gfc_code* c)
5284 {
5285   gfc_component *comp;
5286   bool b;
5287
5288   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5289   gcc_assert (b);
5290
5291   c->resolved_sym = c->expr1->symtree->n.sym;
5292   c->expr1->expr_type = EXPR_VARIABLE;
5293
5294   if (!comp->attr.subroutine)
5295     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5296
5297   if (resolve_ref (c->expr1) == FAILURE)
5298     return FAILURE;
5299
5300   if (update_ppc_arglist (c->expr1) == FAILURE)
5301     return FAILURE;
5302
5303   c->ext.actual = c->expr1->value.compcall.actual;
5304
5305   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5306                               comp->formal == NULL) == FAILURE)
5307     return FAILURE;
5308
5309   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5310
5311   return SUCCESS;
5312 }
5313
5314
5315 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5316
5317 static gfc_try
5318 resolve_expr_ppc (gfc_expr* e)
5319 {
5320   gfc_component *comp;
5321   bool b;
5322
5323   b = gfc_is_proc_ptr_comp (e, &comp);
5324   gcc_assert (b);
5325
5326   /* Convert to EXPR_FUNCTION.  */
5327   e->expr_type = EXPR_FUNCTION;
5328   e->value.function.isym = NULL;
5329   e->value.function.actual = e->value.compcall.actual;
5330   e->ts = comp->ts;
5331   if (comp->as != NULL)
5332     e->rank = comp->as->rank;
5333
5334   if (!comp->attr.function)
5335     gfc_add_function (&comp->attr, comp->name, &e->where);
5336
5337   if (resolve_ref (e) == FAILURE)
5338     return FAILURE;
5339
5340   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5341                               comp->formal == NULL) == FAILURE)
5342     return FAILURE;
5343
5344   if (update_ppc_arglist (e) == FAILURE)
5345     return FAILURE;
5346
5347   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5348
5349   return SUCCESS;
5350 }
5351
5352
5353 /* Resolve an expression.  That is, make sure that types of operands agree
5354    with their operators, intrinsic operators are converted to function calls
5355    for overloaded types and unresolved function references are resolved.  */
5356
5357 gfc_try
5358 gfc_resolve_expr (gfc_expr *e)
5359 {
5360   gfc_try t;
5361
5362   if (e == NULL)
5363     return SUCCESS;
5364
5365   switch (e->expr_type)
5366     {
5367     case EXPR_OP:
5368       t = resolve_operator (e);
5369       break;
5370
5371     case EXPR_FUNCTION:
5372     case EXPR_VARIABLE:
5373
5374       if (check_host_association (e))
5375         t = resolve_function (e);
5376       else
5377         {
5378           t = resolve_variable (e);
5379           if (t == SUCCESS)
5380             expression_rank (e);
5381         }
5382
5383       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5384           && e->ref->type != REF_SUBSTRING)
5385         gfc_resolve_substring_charlen (e);
5386
5387       break;
5388
5389     case EXPR_COMPCALL:
5390       if (e->symtree && e->symtree->n.sym->ts.type == BT_CLASS)
5391         t = resolve_class_compcall (e);
5392       else
5393         t = resolve_compcall (e, true);
5394       break;
5395
5396     case EXPR_SUBSTRING:
5397       t = resolve_ref (e);
5398       break;
5399
5400     case EXPR_CONSTANT:
5401     case EXPR_NULL:
5402       t = SUCCESS;
5403       break;
5404
5405     case EXPR_PPC:
5406       t = resolve_expr_ppc (e);
5407       break;
5408
5409     case EXPR_ARRAY:
5410       t = FAILURE;
5411       if (resolve_ref (e) == FAILURE)
5412         break;
5413
5414       t = gfc_resolve_array_constructor (e);
5415       /* Also try to expand a constructor.  */
5416       if (t == SUCCESS)
5417         {
5418           expression_rank (e);
5419           gfc_expand_constructor (e);
5420         }
5421
5422       /* This provides the opportunity for the length of constructors with
5423          character valued function elements to propagate the string length
5424          to the expression.  */
5425       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5426         t = gfc_resolve_character_array_constructor (e);
5427
5428       break;
5429
5430     case EXPR_STRUCTURE:
5431       t = resolve_ref (e);
5432       if (t == FAILURE)
5433         break;
5434
5435       t = resolve_structure_cons (e);
5436       if (t == FAILURE)
5437         break;
5438
5439       t = gfc_simplify_expr (e, 0);
5440       break;
5441
5442     default:
5443       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5444     }
5445
5446   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5447     fixup_charlen (e);
5448
5449   return t;
5450 }
5451
5452
5453 /* Resolve an expression from an iterator.  They must be scalar and have
5454    INTEGER or (optionally) REAL type.  */
5455
5456 static gfc_try
5457 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5458                            const char *name_msgid)
5459 {
5460   if (gfc_resolve_expr (expr) == FAILURE)
5461     return FAILURE;
5462
5463   if (expr->rank != 0)
5464     {
5465       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5466       return FAILURE;
5467     }
5468
5469   if (expr->ts.type != BT_INTEGER)
5470     {
5471       if (expr->ts.type == BT_REAL)
5472         {
5473           if (real_ok)
5474             return gfc_notify_std (GFC_STD_F95_DEL,
5475                                    "Deleted feature: %s at %L must be integer",
5476                                    _(name_msgid), &expr->where);
5477           else
5478             {
5479               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5480                          &expr->where);
5481               return FAILURE;
5482             }
5483         }
5484       else
5485         {
5486           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5487           return FAILURE;
5488         }
5489     }
5490   return SUCCESS;
5491 }
5492
5493
5494 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5495    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5496
5497 gfc_try
5498 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5499 {
5500   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5501       == FAILURE)
5502     return FAILURE;
5503
5504   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5505     {
5506       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5507                  &iter->var->where);
5508       return FAILURE;
5509     }
5510
5511   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5512                                  "Start expression in DO loop") == FAILURE)
5513     return FAILURE;
5514
5515   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5516                                  "End expression in DO loop") == FAILURE)
5517     return FAILURE;
5518
5519   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5520                                  "Step expression in DO loop") == FAILURE)
5521     return FAILURE;
5522
5523   if (iter->step->expr_type == EXPR_CONSTANT)
5524     {
5525       if ((iter->step->ts.type == BT_INTEGER
5526            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5527           || (iter->step->ts.type == BT_REAL
5528               && mpfr_sgn (iter->step->value.real) == 0))
5529         {
5530           gfc_error ("Step expression in DO loop at %L cannot be zero",
5531                      &iter->step->where);
5532           return FAILURE;
5533         }
5534     }
5535
5536   /* Convert start, end, and step to the same type as var.  */
5537   if (iter->start->ts.kind != iter->var->ts.kind
5538       || iter->start->ts.type != iter->var->ts.type)
5539     gfc_convert_type (iter->start, &iter->var->ts, 2);
5540
5541   if (iter->end->ts.kind != iter->var->ts.kind
5542       || iter->end->ts.type != iter->var->ts.type)
5543     gfc_convert_type (iter->end, &iter->var->ts, 2);
5544
5545   if (iter->step->ts.kind != iter->var->ts.kind
5546       || iter->step->ts.type != iter->var->ts.type)
5547     gfc_convert_type (iter->step, &iter->var->ts, 2);
5548
5549   if (iter->start->expr_type == EXPR_CONSTANT
5550       && iter->end->expr_type == EXPR_CONSTANT
5551       && iter->step->expr_type == EXPR_CONSTANT)
5552     {
5553       int sgn, cmp;
5554       if (iter->start->ts.type == BT_INTEGER)
5555         {
5556           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5557           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5558         }
5559       else
5560         {
5561           sgn = mpfr_sgn (iter->step->value.real);
5562           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5563         }
5564       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5565         gfc_warning ("DO loop at %L will be executed zero times",
5566                      &iter->step->where);
5567     }
5568
5569   return SUCCESS;
5570 }
5571
5572
5573 /* Traversal function for find_forall_index.  f == 2 signals that
5574    that variable itself is not to be checked - only the references.  */
5575
5576 static bool
5577 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5578 {
5579   if (expr->expr_type != EXPR_VARIABLE)
5580     return false;
5581   
5582   /* A scalar assignment  */
5583   if (!expr->ref || *f == 1)
5584     {
5585       if (expr->symtree->n.sym == sym)
5586         return true;
5587       else
5588         return false;
5589     }
5590
5591   if (*f == 2)
5592     *f = 1;
5593   return false;
5594 }
5595
5596
5597 /* Check whether the FORALL index appears in the expression or not.
5598    Returns SUCCESS if SYM is found in EXPR.  */
5599
5600 gfc_try
5601 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5602 {
5603   if (gfc_traverse_expr (expr, sym, forall_index, f))
5604     return SUCCESS;
5605   else
5606     return FAILURE;
5607 }
5608
5609
5610 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5611    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5612    INTEGERs, and if stride is a constant it must be nonzero.
5613    Furthermore "A subscript or stride in a forall-triplet-spec shall
5614    not contain a reference to any index-name in the
5615    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5616
5617 static void
5618 resolve_forall_iterators (gfc_forall_iterator *it)
5619 {
5620   gfc_forall_iterator *iter, *iter2;
5621
5622   for (iter = it; iter; iter = iter->next)
5623     {
5624       if (gfc_resolve_expr (iter->var) == SUCCESS
5625           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5626         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5627                    &iter->var->where);
5628
5629       if (gfc_resolve_expr (iter->start) == SUCCESS
5630           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5631         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5632                    &iter->start->where);
5633       if (iter->var->ts.kind != iter->start->ts.kind)
5634         gfc_convert_type (iter->start, &iter->var->ts, 2);
5635
5636       if (gfc_resolve_expr (iter->end) == SUCCESS
5637           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
5638         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
5639                    &iter->end->where);
5640       if (iter->var->ts.kind != iter->end->ts.kind)
5641         gfc_convert_type (iter->end, &iter->var->ts, 2);
5642
5643       if (gfc_resolve_expr (iter->stride) == SUCCESS)
5644         {
5645           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
5646             gfc_error ("FORALL stride expression at %L must be a scalar %s",
5647                        &iter->stride->where, "INTEGER");
5648
5649           if (iter->stride->expr_type == EXPR_CONSTANT
5650               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
5651             gfc_error ("FORALL stride expression at %L cannot be zero",
5652                        &iter->stride->where);
5653         }
5654       if (iter->var->ts.kind != iter->stride->ts.kind)
5655         gfc_convert_type (iter->stride, &iter->var->ts, 2);
5656     }
5657
5658   for (iter = it; iter; iter = iter->next)
5659     for (iter2 = iter; iter2; iter2 = iter2->next)
5660       {
5661         if (find_forall_index (iter2->start,
5662                                iter->var->symtree->n.sym, 0) == SUCCESS
5663             || find_forall_index (iter2->end,
5664                                   iter->var->symtree->n.sym, 0) == SUCCESS
5665             || find_forall_index (iter2->stride,
5666                                   iter->var->symtree->n.sym, 0) == SUCCESS)
5667           gfc_error ("FORALL index '%s' may not appear in triplet "
5668                      "specification at %L", iter->var->symtree->name,
5669                      &iter2->start->where);
5670       }
5671 }
5672
5673
5674 /* Given a pointer to a symbol that is a derived type, see if it's
5675    inaccessible, i.e. if it's defined in another module and the components are
5676    PRIVATE.  The search is recursive if necessary.  Returns zero if no
5677    inaccessible components are found, nonzero otherwise.  */
5678
5679 static int
5680 derived_inaccessible (gfc_symbol *sym)
5681 {
5682   gfc_component *c;
5683
5684   if (sym->attr.use_assoc && sym->attr.private_comp)
5685     return 1;
5686
5687   for (c = sym->components; c; c = c->next)
5688     {
5689         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
5690           return 1;
5691     }
5692
5693   return 0;
5694 }
5695
5696
5697 /* Resolve the argument of a deallocate expression.  The expression must be
5698    a pointer or a full array.  */
5699
5700 static gfc_try
5701 resolve_deallocate_expr (gfc_expr *e)
5702 {
5703   symbol_attribute attr;
5704   int allocatable, pointer, check_intent_in;
5705   gfc_ref *ref;
5706   gfc_symbol *sym;
5707   gfc_component *c;
5708
5709   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5710   check_intent_in = 1;
5711
5712   if (gfc_resolve_expr (e) == FAILURE)
5713     return FAILURE;
5714
5715   if (e->expr_type != EXPR_VARIABLE)
5716     goto bad;
5717
5718   sym = e->symtree->n.sym;
5719
5720   if (sym->ts.type == BT_CLASS)
5721     {
5722       allocatable = sym->ts.u.derived->components->attr.allocatable;
5723       pointer = sym->ts.u.derived->components->attr.pointer;
5724     }
5725   else
5726     {
5727       allocatable = sym->attr.allocatable;
5728       pointer = sym->attr.pointer;
5729     }
5730   for (ref = e->ref; ref; ref = ref->next)
5731     {
5732       if (pointer)
5733         check_intent_in = 0;
5734
5735       switch (ref->type)
5736         {
5737         case REF_ARRAY:
5738           if (ref->u.ar.type != AR_FULL)
5739             allocatable = 0;
5740           break;
5741
5742         case REF_COMPONENT:
5743           c = ref->u.c.component;
5744           if (c->ts.type == BT_CLASS)
5745             {
5746               allocatable = c->ts.u.derived->components->attr.allocatable;
5747               pointer = c->ts.u.derived->components->attr.pointer;
5748             }
5749           else
5750             {
5751               allocatable = c->attr.allocatable;
5752               pointer = c->attr.pointer;
5753             }
5754           break;
5755
5756         case REF_SUBSTRING:
5757           allocatable = 0;
5758           break;
5759         }
5760     }
5761
5762   attr = gfc_expr_attr (e);
5763
5764   if (allocatable == 0 && attr.pointer == 0)
5765     {
5766     bad:
5767       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
5768                  &e->where);
5769     }
5770
5771   if (check_intent_in && sym->attr.intent == INTENT_IN)
5772     {
5773       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
5774                  sym->name, &e->where);
5775       return FAILURE;
5776     }
5777
5778   if (e->ts.type == BT_CLASS)
5779     {
5780       /* Only deallocate the DATA component.  */
5781       gfc_add_component_ref (e, "$data");
5782     }
5783
5784   return SUCCESS;
5785 }
5786
5787
5788 /* Returns true if the expression e contains a reference to the symbol sym.  */
5789 static bool
5790 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
5791 {
5792   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
5793     return true;
5794
5795   return false;
5796 }
5797
5798 bool
5799 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
5800 {
5801   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
5802 }
5803
5804
5805 /* Given the expression node e for an allocatable/pointer of derived type to be
5806    allocated, get the expression node to be initialized afterwards (needed for
5807    derived types with default initializers, and derived types with allocatable
5808    components that need nullification.)  */
5809
5810 gfc_expr *
5811 gfc_expr_to_initialize (gfc_expr *e)
5812 {
5813   gfc_expr *result;
5814   gfc_ref *ref;
5815   int i;
5816
5817   result = gfc_copy_expr (e);
5818
5819   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
5820   for (ref = result->ref; ref; ref = ref->next)
5821     if (ref->type == REF_ARRAY && ref->next == NULL)
5822       {
5823         ref->u.ar.type = AR_FULL;
5824
5825         for (i = 0; i < ref->u.ar.dimen; i++)
5826           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
5827
5828         result->rank = ref->u.ar.dimen;
5829         break;
5830       }
5831
5832   return result;
5833 }
5834
5835
5836 /* Resolve the expression in an ALLOCATE statement, doing the additional
5837    checks to see whether the expression is OK or not.  The expression must
5838    have a trailing array reference that gives the size of the array.  */
5839
5840 static gfc_try
5841 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
5842 {
5843   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
5844   symbol_attribute attr;
5845   gfc_ref *ref, *ref2;
5846   gfc_array_ref *ar;
5847   gfc_symbol *sym;
5848   gfc_alloc *a;
5849   gfc_component *c;
5850
5851   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5852   check_intent_in = 1;
5853
5854   if (gfc_resolve_expr (e) == FAILURE)
5855     return FAILURE;
5856
5857   /* Make sure the expression is allocatable or a pointer.  If it is
5858      pointer, the next-to-last reference must be a pointer.  */
5859
5860   ref2 = NULL;
5861   if (e->symtree)
5862     sym = e->symtree->n.sym;
5863
5864   /* Check whether ultimate component is abstract and CLASS.  */
5865   is_abstract = 0;
5866
5867   if (e->expr_type != EXPR_VARIABLE)
5868     {
5869       allocatable = 0;
5870       attr = gfc_expr_attr (e);
5871       pointer = attr.pointer;
5872       dimension = attr.dimension;
5873     }
5874   else
5875     {
5876       if (sym->ts.type == BT_CLASS)
5877         {
5878           allocatable = sym->ts.u.derived->components->attr.allocatable;
5879           pointer = sym->ts.u.derived->components->attr.pointer;
5880           dimension = sym->ts.u.derived->components->attr.dimension;
5881           is_abstract = sym->ts.u.derived->components->attr.abstract;
5882         }
5883       else
5884         {
5885           allocatable = sym->attr.allocatable;
5886           pointer = sym->attr.pointer;
5887           dimension = sym->attr.dimension;
5888         }
5889
5890       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
5891         {
5892           if (pointer)
5893             check_intent_in = 0;
5894
5895           switch (ref->type)
5896             {
5897               case REF_ARRAY:
5898                 if (ref->next != NULL)
5899                   pointer = 0;
5900                 break;
5901
5902               case REF_COMPONENT:
5903                 c = ref->u.c.component;
5904                 if (c->ts.type == BT_CLASS)
5905                   {
5906                     allocatable = c->ts.u.derived->components->attr.allocatable;
5907                     pointer = c->ts.u.derived->components->attr.pointer;
5908                     dimension = c->ts.u.derived->components->attr.dimension;
5909                     is_abstract = c->ts.u.derived->components->attr.abstract;
5910                   }
5911                 else
5912                   {
5913                     allocatable = c->attr.allocatable;
5914                     pointer = c->attr.pointer;
5915                     dimension = c->attr.dimension;
5916                     is_abstract = c->attr.abstract;
5917                   }
5918                 break;
5919
5920               case REF_SUBSTRING:
5921                 allocatable = 0;
5922                 pointer = 0;
5923                 break;
5924             }
5925         }
5926     }
5927
5928   if (allocatable == 0 && pointer == 0)
5929     {
5930       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
5931                  &e->where);
5932       return FAILURE;
5933     }
5934
5935   if (is_abstract && !code->expr3 && code->ext.alloc.ts.type == BT_UNKNOWN)
5936     {
5937       gcc_assert (e->ts.type == BT_CLASS);
5938       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
5939                  "type-spec or SOURCE=", sym->name, &e->where);
5940       return FAILURE;
5941     }
5942
5943   if (check_intent_in && sym->attr.intent == INTENT_IN)
5944     {
5945       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
5946                  sym->name, &e->where);
5947       return FAILURE;
5948     }
5949
5950   if (pointer || dimension == 0)
5951     return SUCCESS;
5952
5953   /* Make sure the next-to-last reference node is an array specification.  */
5954
5955   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
5956     {
5957       gfc_error ("Array specification required in ALLOCATE statement "
5958                  "at %L", &e->where);
5959       return FAILURE;
5960     }
5961
5962   /* Make sure that the array section reference makes sense in the
5963     context of an ALLOCATE specification.  */
5964
5965   ar = &ref2->u.ar;
5966
5967   for (i = 0; i < ar->dimen; i++)
5968     {
5969       if (ref2->u.ar.type == AR_ELEMENT)
5970         goto check_symbols;
5971
5972       switch (ar->dimen_type[i])
5973         {
5974         case DIMEN_ELEMENT:
5975           break;
5976
5977         case DIMEN_RANGE:
5978           if (ar->start[i] != NULL
5979               && ar->end[i] != NULL
5980               && ar->stride[i] == NULL)
5981             break;
5982
5983           /* Fall Through...  */
5984
5985         case DIMEN_UNKNOWN:
5986         case DIMEN_VECTOR:
5987           gfc_error ("Bad array specification in ALLOCATE statement at %L",
5988                      &e->where);
5989           return FAILURE;
5990         }
5991
5992 check_symbols:
5993
5994       for (a = code->ext.alloc.list; a; a = a->next)
5995         {
5996           sym = a->expr->symtree->n.sym;
5997
5998           /* TODO - check derived type components.  */
5999           if (sym->ts.type == BT_DERIVED)
6000             continue;
6001
6002           if ((ar->start[i] != NULL
6003                && gfc_find_sym_in_expr (sym, ar->start[i]))
6004               || (ar->end[i] != NULL
6005                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6006             {
6007               gfc_error ("'%s' must not appear in the array specification at "
6008                          "%L in the same ALLOCATE statement where it is "
6009                          "itself allocated", sym->name, &ar->where);
6010               return FAILURE;
6011             }
6012         }
6013     }
6014
6015   return SUCCESS;
6016 }
6017
6018 static void
6019 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6020 {
6021   gfc_expr *stat, *errmsg, *pe, *qe;
6022   gfc_alloc *a, *p, *q;
6023
6024   stat = code->expr1 ? code->expr1 : NULL;
6025
6026   errmsg = code->expr2 ? code->expr2 : NULL;
6027
6028   /* Check the stat variable.  */
6029   if (stat)
6030     {
6031       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6032         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6033                    stat->symtree->n.sym->name, &stat->where);
6034
6035       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6036         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6037                    &stat->where);
6038
6039       if ((stat->ts.type != BT_INTEGER
6040            && !(stat->ref && (stat->ref->type == REF_ARRAY
6041                               || stat->ref->type == REF_COMPONENT)))
6042           || stat->rank > 0)
6043         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6044                    "variable", &stat->where);
6045
6046       for (p = code->ext.alloc.list; p; p = p->next)
6047         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6048           gfc_error ("Stat-variable at %L shall not be %sd within "
6049                      "the same %s statement", &stat->where, fcn, fcn);
6050     }
6051
6052   /* Check the errmsg variable.  */
6053   if (errmsg)
6054     {
6055       if (!stat)
6056         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6057                      &errmsg->where);
6058
6059       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6060         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6061                    errmsg->symtree->n.sym->name, &errmsg->where);
6062
6063       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6064         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6065                    &errmsg->where);
6066
6067       if ((errmsg->ts.type != BT_CHARACTER
6068            && !(errmsg->ref
6069                 && (errmsg->ref->type == REF_ARRAY
6070                     || errmsg->ref->type == REF_COMPONENT)))
6071           || errmsg->rank > 0 )
6072         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6073                    "variable", &errmsg->where);
6074
6075       for (p = code->ext.alloc.list; p; p = p->next)
6076         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6077           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6078                      "the same %s statement", &errmsg->where, fcn, fcn);
6079     }
6080
6081   /* Check that an allocate-object appears only once in the statement.  
6082      FIXME: Checking derived types is disabled.  */
6083   for (p = code->ext.alloc.list; p; p = p->next)
6084     {
6085       pe = p->expr;
6086       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6087            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6088         {
6089           for (q = p->next; q; q = q->next)
6090             {
6091               qe = q->expr;
6092               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6093                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6094                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6095                 gfc_error ("Allocate-object at %L also appears at %L",
6096                            &pe->where, &qe->where);
6097             }
6098         }
6099     }
6100
6101   if (strcmp (fcn, "ALLOCATE") == 0)
6102     {
6103       for (a = code->ext.alloc.list; a; a = a->next)
6104         resolve_allocate_expr (a->expr, code);
6105     }
6106   else
6107     {
6108       for (a = code->ext.alloc.list; a; a = a->next)
6109         resolve_deallocate_expr (a->expr);
6110     }
6111 }
6112
6113
6114 /************ SELECT CASE resolution subroutines ************/
6115
6116 /* Callback function for our mergesort variant.  Determines interval
6117    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6118    op1 > op2.  Assumes we're not dealing with the default case.  
6119    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6120    There are nine situations to check.  */
6121
6122 static int
6123 compare_cases (const gfc_case *op1, const gfc_case *op2)
6124 {
6125   int retval;
6126
6127   if (op1->low == NULL) /* op1 = (:L)  */
6128     {
6129       /* op2 = (:N), so overlap.  */
6130       retval = 0;
6131       /* op2 = (M:) or (M:N),  L < M  */
6132       if (op2->low != NULL
6133           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6134         retval = -1;
6135     }
6136   else if (op1->high == NULL) /* op1 = (K:)  */
6137     {
6138       /* op2 = (M:), so overlap.  */
6139       retval = 0;
6140       /* op2 = (:N) or (M:N), K > N  */
6141       if (op2->high != NULL
6142           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6143         retval = 1;
6144     }
6145   else /* op1 = (K:L)  */
6146     {
6147       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6148         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6149                  ? 1 : 0;
6150       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6151         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6152                  ? -1 : 0;
6153       else                      /* op2 = (M:N)  */
6154         {
6155           retval =  0;
6156           /* L < M  */
6157           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6158             retval =  -1;
6159           /* K > N  */
6160           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6161             retval =  1;
6162         }
6163     }
6164
6165   return retval;
6166 }
6167
6168
6169 /* Merge-sort a double linked case list, detecting overlap in the
6170    process.  LIST is the head of the double linked case list before it
6171    is sorted.  Returns the head of the sorted list if we don't see any
6172    overlap, or NULL otherwise.  */
6173
6174 static gfc_case *
6175 check_case_overlap (gfc_case *list)
6176 {
6177   gfc_case *p, *q, *e, *tail;
6178   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6179
6180   /* If the passed list was empty, return immediately.  */
6181   if (!list)
6182     return NULL;
6183
6184   overlap_seen = 0;
6185   insize = 1;
6186
6187   /* Loop unconditionally.  The only exit from this loop is a return
6188      statement, when we've finished sorting the case list.  */
6189   for (;;)
6190     {
6191       p = list;
6192       list = NULL;
6193       tail = NULL;
6194
6195       /* Count the number of merges we do in this pass.  */
6196       nmerges = 0;
6197
6198       /* Loop while there exists a merge to be done.  */
6199       while (p)
6200         {
6201           int i;
6202
6203           /* Count this merge.  */
6204           nmerges++;
6205
6206           /* Cut the list in two pieces by stepping INSIZE places
6207              forward in the list, starting from P.  */
6208           psize = 0;
6209           q = p;
6210           for (i = 0; i < insize; i++)
6211             {
6212               psize++;
6213               q = q->right;
6214               if (!q)
6215                 break;
6216             }
6217           qsize = insize;
6218
6219           /* Now we have two lists.  Merge them!  */
6220           while (psize > 0 || (qsize > 0 && q != NULL))
6221             {
6222               /* See from which the next case to merge comes from.  */
6223               if (psize == 0)
6224                 {
6225                   /* P is empty so the next case must come from Q.  */
6226                   e = q;
6227                   q = q->right;
6228                   qsize--;
6229                 }
6230               else if (qsize == 0 || q == NULL)
6231                 {
6232                   /* Q is empty.  */
6233                   e = p;
6234                   p = p->right;
6235                   psize--;
6236                 }
6237               else
6238                 {
6239                   cmp = compare_cases (p, q);
6240                   if (cmp < 0)
6241                     {
6242                       /* The whole case range for P is less than the
6243                          one for Q.  */
6244                       e = p;
6245                       p = p->right;
6246                       psize--;
6247                     }
6248                   else if (cmp > 0)
6249                     {
6250                       /* The whole case range for Q is greater than
6251                          the case range for P.  */
6252                       e = q;
6253                       q = q->right;
6254                       qsize--;
6255                     }
6256                   else
6257                     {
6258                       /* The cases overlap, or they are the same
6259                          element in the list.  Either way, we must
6260                          issue an error and get the next case from P.  */
6261                       /* FIXME: Sort P and Q by line number.  */
6262                       gfc_error ("CASE label at %L overlaps with CASE "
6263                                  "label at %L", &p->where, &q->where);
6264                       overlap_seen = 1;
6265                       e = p;
6266                       p = p->right;
6267                       psize--;
6268                     }
6269                 }
6270
6271                 /* Add the next element to the merged list.  */
6272               if (tail)
6273                 tail->right = e;
6274               else
6275                 list = e;
6276               e->left = tail;
6277               tail = e;
6278             }
6279
6280           /* P has now stepped INSIZE places along, and so has Q.  So
6281              they're the same.  */
6282           p = q;
6283         }
6284       tail->right = NULL;
6285
6286       /* If we have done only one merge or none at all, we've
6287          finished sorting the cases.  */
6288       if (nmerges <= 1)
6289         {
6290           if (!overlap_seen)
6291             return list;
6292           else
6293             return NULL;
6294         }
6295
6296       /* Otherwise repeat, merging lists twice the size.  */
6297       insize *= 2;
6298     }
6299 }
6300
6301
6302 /* Check to see if an expression is suitable for use in a CASE statement.
6303    Makes sure that all case expressions are scalar constants of the same
6304    type.  Return FAILURE if anything is wrong.  */
6305
6306 static gfc_try
6307 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6308 {
6309   if (e == NULL) return SUCCESS;
6310
6311   if (e->ts.type != case_expr->ts.type)
6312     {
6313       gfc_error ("Expression in CASE statement at %L must be of type %s",
6314                  &e->where, gfc_basic_typename (case_expr->ts.type));
6315       return FAILURE;
6316     }
6317
6318   /* C805 (R808) For a given case-construct, each case-value shall be of
6319      the same type as case-expr.  For character type, length differences
6320      are allowed, but the kind type parameters shall be the same.  */
6321
6322   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6323     {
6324       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6325                  &e->where, case_expr->ts.kind);
6326       return FAILURE;
6327     }
6328
6329   /* Convert the case value kind to that of case expression kind, if needed.
6330      FIXME:  Should a warning be issued?  */
6331   if (e->ts.kind != case_expr->ts.kind)
6332     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6333
6334   if (e->rank != 0)
6335     {
6336       gfc_error ("Expression in CASE statement at %L must be scalar",
6337                  &e->where);
6338       return FAILURE;
6339     }
6340
6341   return SUCCESS;
6342 }
6343
6344
6345 /* Given a completely parsed select statement, we:
6346
6347      - Validate all expressions and code within the SELECT.
6348      - Make sure that the selection expression is not of the wrong type.
6349      - Make sure that no case ranges overlap.
6350      - Eliminate unreachable cases and unreachable code resulting from
6351        removing case labels.
6352
6353    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6354    they are a hassle for code generation, and to prevent that, we just
6355    cut them out here.  This is not necessary for overlapping cases
6356    because they are illegal and we never even try to generate code.
6357
6358    We have the additional caveat that a SELECT construct could have
6359    been a computed GOTO in the source code. Fortunately we can fairly
6360    easily work around that here: The case_expr for a "real" SELECT CASE
6361    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6362    we have to do is make sure that the case_expr is a scalar integer
6363    expression.  */
6364
6365 static void
6366 resolve_select (gfc_code *code)
6367 {
6368   gfc_code *body;
6369   gfc_expr *case_expr;
6370   gfc_case *cp, *default_case, *tail, *head;
6371   int seen_unreachable;
6372   int seen_logical;
6373   int ncases;
6374   bt type;
6375   gfc_try t;
6376
6377   if (code->expr1 == NULL)
6378     {
6379       /* This was actually a computed GOTO statement.  */
6380       case_expr = code->expr2;
6381       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6382         gfc_error ("Selection expression in computed GOTO statement "
6383                    "at %L must be a scalar integer expression",
6384                    &case_expr->where);
6385
6386       /* Further checking is not necessary because this SELECT was built
6387          by the compiler, so it should always be OK.  Just move the
6388          case_expr from expr2 to expr so that we can handle computed
6389          GOTOs as normal SELECTs from here on.  */
6390       code->expr1 = code->expr2;
6391       code->expr2 = NULL;
6392       return;
6393     }
6394
6395   case_expr = code->expr1;
6396
6397   type = case_expr->ts.type;
6398   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6399     {
6400       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6401                  &case_expr->where, gfc_typename (&case_expr->ts));
6402
6403       /* Punt. Going on here just produce more garbage error messages.  */
6404       return;
6405     }
6406
6407   if (case_expr->rank != 0)
6408     {
6409       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6410                  "expression", &case_expr->where);
6411
6412       /* Punt.  */
6413       return;
6414     }
6415
6416   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6417      of the SELECT CASE expression and its CASE values.  Walk the lists
6418      of case values, and if we find a mismatch, promote case_expr to
6419      the appropriate kind.  */
6420
6421   if (type == BT_LOGICAL || type == BT_INTEGER)
6422     {
6423       for (body = code->block; body; body = body->block)
6424         {
6425           /* Walk the case label list.  */
6426           for (cp = body->ext.case_list; cp; cp = cp->next)
6427             {
6428               /* Intercept the DEFAULT case.  It does not have a kind.  */
6429               if (cp->low == NULL && cp->high == NULL)
6430                 continue;
6431
6432               /* Unreachable case ranges are discarded, so ignore.  */
6433               if (cp->low != NULL && cp->high != NULL
6434                   && cp->low != cp->high
6435                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6436                 continue;
6437
6438               /* FIXME: Should a warning be issued?  */
6439               if (cp->low != NULL
6440                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6441                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6442
6443               if (cp->high != NULL
6444                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6445                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6446             }
6447          }
6448     }
6449
6450   /* Assume there is no DEFAULT case.  */
6451   default_case = NULL;
6452   head = tail = NULL;
6453   ncases = 0;
6454   seen_logical = 0;
6455
6456   for (body = code->block; body; body = body->block)
6457     {
6458       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
6459       t = SUCCESS;
6460       seen_unreachable = 0;
6461
6462       /* Walk the case label list, making sure that all case labels
6463          are legal.  */
6464       for (cp = body->ext.case_list; cp; cp = cp->next)
6465         {
6466           /* Count the number of cases in the whole construct.  */
6467           ncases++;
6468
6469           /* Intercept the DEFAULT case.  */
6470           if (cp->low == NULL && cp->high == NULL)
6471             {
6472               if (default_case != NULL)
6473                 {
6474                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
6475                              "by a second DEFAULT CASE at %L",
6476                              &default_case->where, &cp->where);
6477                   t = FAILURE;
6478                   break;
6479                 }
6480               else
6481                 {
6482                   default_case = cp;
6483                   continue;
6484                 }
6485             }
6486
6487           /* Deal with single value cases and case ranges.  Errors are
6488              issued from the validation function.  */
6489           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
6490              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
6491             {
6492               t = FAILURE;
6493               break;
6494             }
6495
6496           if (type == BT_LOGICAL
6497               && ((cp->low == NULL || cp->high == NULL)
6498                   || cp->low != cp->high))
6499             {
6500               gfc_error ("Logical range in CASE statement at %L is not "
6501                          "allowed", &cp->low->where);
6502               t = FAILURE;
6503               break;
6504             }
6505
6506           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
6507             {
6508               int value;
6509               value = cp->low->value.logical == 0 ? 2 : 1;
6510               if (value & seen_logical)
6511                 {
6512                   gfc_error ("constant logical value in CASE statement "
6513                              "is repeated at %L",
6514                              &cp->low->where);
6515                   t = FAILURE;
6516                   break;
6517                 }
6518               seen_logical |= value;
6519             }
6520
6521           if (cp->low != NULL && cp->high != NULL
6522               && cp->low != cp->high
6523               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6524             {
6525               if (gfc_option.warn_surprising)
6526                 gfc_warning ("Range specification at %L can never "
6527                              "be matched", &cp->where);
6528
6529               cp->unreachable = 1;
6530               seen_unreachable = 1;
6531             }
6532           else
6533             {
6534               /* If the case range can be matched, it can also overlap with
6535                  other cases.  To make sure it does not, we put it in a
6536                  double linked list here.  We sort that with a merge sort
6537                  later on to detect any overlapping cases.  */
6538               if (!head)
6539                 {
6540                   head = tail = cp;
6541                   head->right = head->left = NULL;
6542                 }
6543               else
6544                 {
6545                   tail->right = cp;
6546                   tail->right->left = tail;
6547                   tail = tail->right;
6548                   tail->right = NULL;
6549                 }
6550             }
6551         }
6552
6553       /* It there was a failure in the previous case label, give up
6554          for this case label list.  Continue with the next block.  */
6555       if (t == FAILURE)
6556         continue;
6557
6558       /* See if any case labels that are unreachable have been seen.
6559          If so, we eliminate them.  This is a bit of a kludge because
6560          the case lists for a single case statement (label) is a
6561          single forward linked lists.  */
6562       if (seen_unreachable)
6563       {
6564         /* Advance until the first case in the list is reachable.  */
6565         while (body->ext.case_list != NULL
6566                && body->ext.case_list->unreachable)
6567           {
6568             gfc_case *n = body->ext.case_list;
6569             body->ext.case_list = body->ext.case_list->next;
6570             n->next = NULL;
6571             gfc_free_case_list (n);
6572           }
6573
6574         /* Strip all other unreachable cases.  */
6575         if (body->ext.case_list)
6576           {
6577             for (cp = body->ext.case_list; cp->next; cp = cp->next)
6578               {
6579                 if (cp->next->unreachable)
6580                   {
6581                     gfc_case *n = cp->next;
6582                     cp->next = cp->next->next;
6583                     n->next = NULL;
6584                     gfc_free_case_list (n);
6585                   }
6586               }
6587           }
6588       }
6589     }
6590
6591   /* See if there were overlapping cases.  If the check returns NULL,
6592      there was overlap.  In that case we don't do anything.  If head
6593      is non-NULL, we prepend the DEFAULT case.  The sorted list can
6594      then used during code generation for SELECT CASE constructs with
6595      a case expression of a CHARACTER type.  */
6596   if (head)
6597     {
6598       head = check_case_overlap (head);
6599
6600       /* Prepend the default_case if it is there.  */
6601       if (head != NULL && default_case)
6602         {
6603           default_case->left = NULL;
6604           default_case->right = head;
6605           head->left = default_case;
6606         }
6607     }
6608
6609   /* Eliminate dead blocks that may be the result if we've seen
6610      unreachable case labels for a block.  */
6611   for (body = code; body && body->block; body = body->block)
6612     {
6613       if (body->block->ext.case_list == NULL)
6614         {
6615           /* Cut the unreachable block from the code chain.  */
6616           gfc_code *c = body->block;
6617           body->block = c->block;
6618
6619           /* Kill the dead block, but not the blocks below it.  */
6620           c->block = NULL;
6621           gfc_free_statements (c);
6622         }
6623     }
6624
6625   /* More than two cases is legal but insane for logical selects.
6626      Issue a warning for it.  */
6627   if (gfc_option.warn_surprising && type == BT_LOGICAL
6628       && ncases > 2)
6629     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
6630                  &code->loc);
6631 }
6632
6633
6634 /* Check if a derived type is extensible.  */
6635
6636 bool
6637 gfc_type_is_extensible (gfc_symbol *sym)
6638 {
6639   return !(sym->attr.is_bind_c || sym->attr.sequence);
6640 }
6641
6642
6643 /* Resolve a SELECT TYPE statement.  */
6644
6645 static void
6646 resolve_select_type (gfc_code *code)
6647 {
6648   gfc_symbol *selector_type;
6649   gfc_code *body, *new_st;
6650   gfc_case *c, *default_case;
6651   gfc_symtree *st;
6652   char name[GFC_MAX_SYMBOL_LEN];
6653   gfc_namespace *ns;
6654
6655   ns = code->ext.ns;
6656   gfc_resolve (ns);
6657
6658   if (code->expr2)
6659     selector_type = code->expr2->ts.u.derived->components->ts.u.derived;
6660   else
6661     selector_type = code->expr1->ts.u.derived->components->ts.u.derived;
6662
6663   /* Assume there is no DEFAULT case.  */
6664   default_case = NULL;
6665
6666   /* Loop over TYPE IS / CLASS IS cases.  */
6667   for (body = code->block; body; body = body->block)
6668     {
6669       c = body->ext.case_list;
6670
6671       /* Check F03:C815.  */
6672       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6673           && !gfc_type_is_extensible (c->ts.u.derived))
6674         {
6675           gfc_error ("Derived type '%s' at %L must be extensible",
6676                      c->ts.u.derived->name, &c->where);
6677           continue;
6678         }
6679
6680       /* Check F03:C816.  */
6681       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6682           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
6683         {
6684           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
6685                      c->ts.u.derived->name, &c->where, selector_type->name);
6686           continue;
6687         }
6688
6689       /* Intercept the DEFAULT case.  */
6690       if (c->ts.type == BT_UNKNOWN)
6691         {
6692           /* Check F03:C818.  */
6693           if (default_case != NULL)
6694             gfc_error ("The DEFAULT CASE at %L cannot be followed "
6695                        "by a second DEFAULT CASE at %L",
6696                        &default_case->where, &c->where);
6697           else
6698             default_case = c;
6699           continue;
6700         }
6701     }
6702
6703   if (code->expr2)
6704     {
6705       /* Insert assignment for selector variable.  */
6706       new_st = gfc_get_code ();
6707       new_st->op = EXEC_ASSIGN;
6708       new_st->expr1 = gfc_copy_expr (code->expr1);
6709       new_st->expr2 = gfc_copy_expr (code->expr2);
6710       ns->code = new_st;
6711     }
6712
6713   /* Put SELECT TYPE statement inside a BLOCK.  */
6714   new_st = gfc_get_code ();
6715   new_st->op = code->op;
6716   new_st->expr1 = code->expr1;
6717   new_st->expr2 = code->expr2;
6718   new_st->block = code->block;
6719   if (!ns->code)
6720     ns->code = new_st;
6721   else
6722     ns->code->next = new_st;
6723   code->op = EXEC_BLOCK;
6724   code->expr1 = code->expr2 =  NULL;
6725   code->block = NULL;
6726
6727   code = new_st;
6728
6729   /* Transform to EXEC_SELECT.  */
6730   code->op = EXEC_SELECT;
6731   gfc_add_component_ref (code->expr1, "$vindex");
6732
6733   /* Loop over TYPE IS / CLASS IS cases.  */
6734   for (body = code->block; body; body = body->block)
6735     {
6736       c = body->ext.case_list;
6737       if (c->ts.type == BT_DERIVED)
6738         c->low = c->high = gfc_int_expr (c->ts.u.derived->vindex);
6739       else if (c->ts.type == BT_CLASS)
6740         /* Currently IS CLASS blocks are simply ignored.
6741            TODO: Implement IS CLASS.  */
6742         c->unreachable = 1;
6743
6744       if (c->ts.type != BT_DERIVED)
6745         continue;
6746       /* Assign temporary to selector.  */
6747       sprintf (name, "tmp$%s", c->ts.u.derived->name);
6748       st = gfc_find_symtree (ns->sym_root, name);
6749       new_st = gfc_get_code ();
6750       new_st->op = EXEC_POINTER_ASSIGN;
6751       new_st->expr1 = gfc_get_variable_expr (st);
6752       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
6753       gfc_add_component_ref (new_st->expr2, "$data");
6754       new_st->next = body->next;
6755       body->next = new_st;
6756     }
6757
6758   /* Eliminate dead blocks.  */
6759   for (body = code; body && body->block; body = body->block)
6760     {
6761       if (body->block->ext.case_list->unreachable)
6762         {
6763           /* Cut the unreachable block from the code chain.  */
6764           gfc_code *cd = body->block;
6765           body->block = cd->block;
6766           /* Kill the dead block, but not the blocks below it.  */
6767           cd->block = NULL;
6768           gfc_free_statements (cd);
6769         }
6770     }
6771
6772   resolve_select (code);
6773
6774 }
6775
6776
6777 /* Resolve a transfer statement. This is making sure that:
6778    -- a derived type being transferred has only non-pointer components
6779    -- a derived type being transferred doesn't have private components, unless 
6780       it's being transferred from the module where the type was defined
6781    -- we're not trying to transfer a whole assumed size array.  */
6782
6783 static void
6784 resolve_transfer (gfc_code *code)
6785 {
6786   gfc_typespec *ts;
6787   gfc_symbol *sym;
6788   gfc_ref *ref;
6789   gfc_expr *exp;
6790
6791   exp = code->expr1;
6792
6793   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
6794     return;
6795
6796   sym = exp->symtree->n.sym;
6797   ts = &sym->ts;
6798
6799   /* Go to actual component transferred.  */
6800   for (ref = code->expr1->ref; ref; ref = ref->next)
6801     if (ref->type == REF_COMPONENT)
6802       ts = &ref->u.c.component->ts;
6803
6804   if (ts->type == BT_DERIVED)
6805     {
6806       /* Check that transferred derived type doesn't contain POINTER
6807          components.  */
6808       if (ts->u.derived->attr.pointer_comp)
6809         {
6810           gfc_error ("Data transfer element at %L cannot have "
6811                      "POINTER components", &code->loc);
6812           return;
6813         }
6814
6815       if (ts->u.derived->attr.alloc_comp)
6816         {
6817           gfc_error ("Data transfer element at %L cannot have "
6818                      "ALLOCATABLE components", &code->loc);
6819           return;
6820         }
6821
6822       if (derived_inaccessible (ts->u.derived))
6823         {
6824           gfc_error ("Data transfer element at %L cannot have "
6825                      "PRIVATE components",&code->loc);
6826           return;
6827         }
6828     }
6829
6830   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
6831       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
6832     {
6833       gfc_error ("Data transfer element at %L cannot be a full reference to "
6834                  "an assumed-size array", &code->loc);
6835       return;
6836     }
6837 }
6838
6839
6840 /*********** Toplevel code resolution subroutines ***********/
6841
6842 /* Find the set of labels that are reachable from this block.  We also
6843    record the last statement in each block.  */
6844      
6845 static void
6846 find_reachable_labels (gfc_code *block)
6847 {
6848   gfc_code *c;
6849
6850   if (!block)
6851     return;
6852
6853   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
6854
6855   /* Collect labels in this block.  We don't keep those corresponding
6856      to END {IF|SELECT}, these are checked in resolve_branch by going
6857      up through the code_stack.  */
6858   for (c = block; c; c = c->next)
6859     {
6860       if (c->here && c->op != EXEC_END_BLOCK)
6861         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
6862     }
6863
6864   /* Merge with labels from parent block.  */
6865   if (cs_base->prev)
6866     {
6867       gcc_assert (cs_base->prev->reachable_labels);
6868       bitmap_ior_into (cs_base->reachable_labels,
6869                        cs_base->prev->reachable_labels);
6870     }
6871 }
6872
6873 /* Given a branch to a label, see if the branch is conforming.
6874    The code node describes where the branch is located.  */
6875
6876 static void
6877 resolve_branch (gfc_st_label *label, gfc_code *code)
6878 {
6879   code_stack *stack;
6880
6881   if (label == NULL)
6882     return;
6883
6884   /* Step one: is this a valid branching target?  */
6885
6886   if (label->defined == ST_LABEL_UNKNOWN)
6887     {
6888       gfc_error ("Label %d referenced at %L is never defined", label->value,
6889                  &label->where);
6890       return;
6891     }
6892
6893   if (label->defined != ST_LABEL_TARGET)
6894     {
6895       gfc_error ("Statement at %L is not a valid branch target statement "
6896                  "for the branch statement at %L", &label->where, &code->loc);
6897       return;
6898     }
6899
6900   /* Step two: make sure this branch is not a branch to itself ;-)  */
6901
6902   if (code->here == label)
6903     {
6904       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
6905       return;
6906     }
6907
6908   /* Step three:  See if the label is in the same block as the
6909      branching statement.  The hard work has been done by setting up
6910      the bitmap reachable_labels.  */
6911
6912   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
6913     return;
6914
6915   /* Step four:  If we haven't found the label in the bitmap, it may
6916     still be the label of the END of the enclosing block, in which
6917     case we find it by going up the code_stack.  */
6918
6919   for (stack = cs_base; stack; stack = stack->prev)
6920     if (stack->current->next && stack->current->next->here == label)
6921       break;
6922
6923   if (stack)
6924     {
6925       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
6926       return;
6927     }
6928
6929   /* The label is not in an enclosing block, so illegal.  This was
6930      allowed in Fortran 66, so we allow it as extension.  No
6931      further checks are necessary in this case.  */
6932   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
6933                   "as the GOTO statement at %L", &label->where,
6934                   &code->loc);
6935   return;
6936 }
6937
6938
6939 /* Check whether EXPR1 has the same shape as EXPR2.  */
6940
6941 static gfc_try
6942 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
6943 {
6944   mpz_t shape[GFC_MAX_DIMENSIONS];
6945   mpz_t shape2[GFC_MAX_DIMENSIONS];
6946   gfc_try result = FAILURE;
6947   int i;
6948
6949   /* Compare the rank.  */
6950   if (expr1->rank != expr2->rank)
6951     return result;
6952
6953   /* Compare the size of each dimension.  */
6954   for (i=0; i<expr1->rank; i++)
6955     {
6956       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
6957         goto ignore;
6958
6959       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
6960         goto ignore;
6961
6962       if (mpz_cmp (shape[i], shape2[i]))
6963         goto over;
6964     }
6965
6966   /* When either of the two expression is an assumed size array, we
6967      ignore the comparison of dimension sizes.  */
6968 ignore:
6969   result = SUCCESS;
6970
6971 over:
6972   for (i--; i >= 0; i--)
6973     {
6974       mpz_clear (shape[i]);
6975       mpz_clear (shape2[i]);
6976     }
6977   return result;
6978 }
6979
6980
6981 /* Check whether a WHERE assignment target or a WHERE mask expression
6982    has the same shape as the outmost WHERE mask expression.  */
6983
6984 static void
6985 resolve_where (gfc_code *code, gfc_expr *mask)
6986 {
6987   gfc_code *cblock;
6988   gfc_code *cnext;
6989   gfc_expr *e = NULL;
6990
6991   cblock = code->block;
6992
6993   /* Store the first WHERE mask-expr of the WHERE statement or construct.
6994      In case of nested WHERE, only the outmost one is stored.  */
6995   if (mask == NULL) /* outmost WHERE */
6996     e = cblock->expr1;
6997   else /* inner WHERE */
6998     e = mask;
6999
7000   while (cblock)
7001     {
7002       if (cblock->expr1)
7003         {
7004           /* Check if the mask-expr has a consistent shape with the
7005              outmost WHERE mask-expr.  */
7006           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7007             gfc_error ("WHERE mask at %L has inconsistent shape",
7008                        &cblock->expr1->where);
7009          }
7010
7011       /* the assignment statement of a WHERE statement, or the first
7012          statement in where-body-construct of a WHERE construct */
7013       cnext = cblock->next;
7014       while (cnext)
7015         {
7016           switch (cnext->op)
7017             {
7018             /* WHERE assignment statement */
7019             case EXEC_ASSIGN:
7020
7021               /* Check shape consistent for WHERE assignment target.  */
7022               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7023                gfc_error ("WHERE assignment target at %L has "
7024                           "inconsistent shape", &cnext->expr1->where);
7025               break;
7026
7027   
7028             case EXEC_ASSIGN_CALL:
7029               resolve_call (cnext);
7030               if (!cnext->resolved_sym->attr.elemental)
7031                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7032                           &cnext->ext.actual->expr->where);
7033               break;
7034
7035             /* WHERE or WHERE construct is part of a where-body-construct */
7036             case EXEC_WHERE:
7037               resolve_where (cnext, e);
7038               break;
7039
7040             default:
7041               gfc_error ("Unsupported statement inside WHERE at %L",
7042                          &cnext->loc);
7043             }
7044          /* the next statement within the same where-body-construct */
7045          cnext = cnext->next;
7046        }
7047     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7048     cblock = cblock->block;
7049   }
7050 }
7051
7052
7053 /* Resolve assignment in FORALL construct.
7054    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7055    FORALL index variables.  */
7056
7057 static void
7058 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7059 {
7060   int n;
7061
7062   for (n = 0; n < nvar; n++)
7063     {
7064       gfc_symbol *forall_index;
7065
7066       forall_index = var_expr[n]->symtree->n.sym;
7067
7068       /* Check whether the assignment target is one of the FORALL index
7069          variable.  */
7070       if ((code->expr1->expr_type == EXPR_VARIABLE)
7071           && (code->expr1->symtree->n.sym == forall_index))
7072         gfc_error ("Assignment to a FORALL index variable at %L",
7073                    &code->expr1->where);
7074       else
7075         {
7076           /* If one of the FORALL index variables doesn't appear in the
7077              assignment variable, then there could be a many-to-one
7078              assignment.  Emit a warning rather than an error because the
7079              mask could be resolving this problem.  */
7080           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7081             gfc_warning ("The FORALL with index '%s' is not used on the "
7082                          "left side of the assignment at %L and so might "
7083                          "cause multiple assignment to this object",
7084                          var_expr[n]->symtree->name, &code->expr1->where);
7085         }
7086     }
7087 }
7088
7089
7090 /* Resolve WHERE statement in FORALL construct.  */
7091
7092 static void
7093 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7094                                   gfc_expr **var_expr)
7095 {
7096   gfc_code *cblock;
7097   gfc_code *cnext;
7098
7099   cblock = code->block;
7100   while (cblock)
7101     {
7102       /* the assignment statement of a WHERE statement, or the first
7103          statement in where-body-construct of a WHERE construct */
7104       cnext = cblock->next;
7105       while (cnext)
7106         {
7107           switch (cnext->op)
7108             {
7109             /* WHERE assignment statement */
7110             case EXEC_ASSIGN:
7111               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7112               break;
7113   
7114             /* WHERE operator assignment statement */
7115             case EXEC_ASSIGN_CALL:
7116               resolve_call (cnext);
7117               if (!cnext->resolved_sym->attr.elemental)
7118                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7119                           &cnext->ext.actual->expr->where);
7120               break;
7121
7122             /* WHERE or WHERE construct is part of a where-body-construct */
7123             case EXEC_WHERE:
7124               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7125               break;
7126
7127             default:
7128               gfc_error ("Unsupported statement inside WHERE at %L",
7129                          &cnext->loc);
7130             }
7131           /* the next statement within the same where-body-construct */
7132           cnext = cnext->next;
7133         }
7134       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7135       cblock = cblock->block;
7136     }
7137 }
7138
7139
7140 /* Traverse the FORALL body to check whether the following errors exist:
7141    1. For assignment, check if a many-to-one assignment happens.
7142    2. For WHERE statement, check the WHERE body to see if there is any
7143       many-to-one assignment.  */
7144
7145 static void
7146 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7147 {
7148   gfc_code *c;
7149
7150   c = code->block->next;
7151   while (c)
7152     {
7153       switch (c->op)
7154         {
7155         case EXEC_ASSIGN:
7156         case EXEC_POINTER_ASSIGN:
7157           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7158           break;
7159
7160         case EXEC_ASSIGN_CALL:
7161           resolve_call (c);
7162           break;
7163
7164         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7165            there is no need to handle it here.  */
7166         case EXEC_FORALL:
7167           break;
7168         case EXEC_WHERE:
7169           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7170           break;
7171         default:
7172           break;
7173         }
7174       /* The next statement in the FORALL body.  */
7175       c = c->next;
7176     }
7177 }
7178
7179
7180 /* Counts the number of iterators needed inside a forall construct, including
7181    nested forall constructs. This is used to allocate the needed memory 
7182    in gfc_resolve_forall.  */
7183
7184 static int 
7185 gfc_count_forall_iterators (gfc_code *code)
7186 {
7187   int max_iters, sub_iters, current_iters;
7188   gfc_forall_iterator *fa;
7189
7190   gcc_assert(code->op == EXEC_FORALL);
7191   max_iters = 0;
7192   current_iters = 0;
7193
7194   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7195     current_iters ++;
7196   
7197   code = code->block->next;
7198
7199   while (code)
7200     {          
7201       if (code->op == EXEC_FORALL)
7202         {
7203           sub_iters = gfc_count_forall_iterators (code);
7204           if (sub_iters > max_iters)
7205             max_iters = sub_iters;
7206         }
7207       code = code->next;
7208     }
7209
7210   return current_iters + max_iters;
7211 }
7212
7213
7214 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7215    gfc_resolve_forall_body to resolve the FORALL body.  */
7216
7217 static void
7218 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7219 {
7220   static gfc_expr **var_expr;
7221   static int total_var = 0;
7222   static int nvar = 0;
7223   int old_nvar, tmp;
7224   gfc_forall_iterator *fa;
7225   int i;
7226
7227   old_nvar = nvar;
7228
7229   /* Start to resolve a FORALL construct   */
7230   if (forall_save == 0)
7231     {
7232       /* Count the total number of FORALL index in the nested FORALL
7233          construct in order to allocate the VAR_EXPR with proper size.  */
7234       total_var = gfc_count_forall_iterators (code);
7235
7236       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7237       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7238     }
7239
7240   /* The information about FORALL iterator, including FORALL index start, end
7241      and stride. The FORALL index can not appear in start, end or stride.  */
7242   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7243     {
7244       /* Check if any outer FORALL index name is the same as the current
7245          one.  */
7246       for (i = 0; i < nvar; i++)
7247         {
7248           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7249             {
7250               gfc_error ("An outer FORALL construct already has an index "
7251                          "with this name %L", &fa->var->where);
7252             }
7253         }
7254
7255       /* Record the current FORALL index.  */
7256       var_expr[nvar] = gfc_copy_expr (fa->var);
7257
7258       nvar++;
7259
7260       /* No memory leak.  */
7261       gcc_assert (nvar <= total_var);
7262     }
7263
7264   /* Resolve the FORALL body.  */
7265   gfc_resolve_forall_body (code, nvar, var_expr);
7266
7267   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7268   gfc_resolve_blocks (code->block, ns);
7269
7270   tmp = nvar;
7271   nvar = old_nvar;
7272   /* Free only the VAR_EXPRs allocated in this frame.  */
7273   for (i = nvar; i < tmp; i++)
7274      gfc_free_expr (var_expr[i]);
7275
7276   if (nvar == 0)
7277     {
7278       /* We are in the outermost FORALL construct.  */
7279       gcc_assert (forall_save == 0);
7280
7281       /* VAR_EXPR is not needed any more.  */
7282       gfc_free (var_expr);
7283       total_var = 0;
7284     }
7285 }
7286
7287
7288 /* Resolve a BLOCK construct statement.  */
7289
7290 static void
7291 resolve_block_construct (gfc_code* code)
7292 {
7293   /* Eventually, we may want to do some checks here or handle special stuff.
7294      But so far the only thing we can do is resolving the local namespace.  */
7295
7296   gfc_resolve (code->ext.ns);
7297 }
7298
7299
7300 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
7301    DO code nodes.  */
7302
7303 static void resolve_code (gfc_code *, gfc_namespace *);
7304
7305 void
7306 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
7307 {
7308   gfc_try t;
7309
7310   for (; b; b = b->block)
7311     {
7312       t = gfc_resolve_expr (b->expr1);
7313       if (gfc_resolve_expr (b->expr2) == FAILURE)
7314         t = FAILURE;
7315
7316       switch (b->op)
7317         {
7318         case EXEC_IF:
7319           if (t == SUCCESS && b->expr1 != NULL
7320               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
7321             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7322                        &b->expr1->where);
7323           break;
7324
7325         case EXEC_WHERE:
7326           if (t == SUCCESS
7327               && b->expr1 != NULL
7328               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
7329             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
7330                        &b->expr1->where);
7331           break;
7332
7333         case EXEC_GOTO:
7334           resolve_branch (b->label1, b);
7335           break;
7336
7337         case EXEC_BLOCK:
7338           resolve_block_construct (b);
7339           break;
7340
7341         case EXEC_SELECT:
7342         case EXEC_SELECT_TYPE:
7343         case EXEC_FORALL:
7344         case EXEC_DO:
7345         case EXEC_DO_WHILE:
7346         case EXEC_READ:
7347         case EXEC_WRITE:
7348         case EXEC_IOLENGTH:
7349         case EXEC_WAIT:
7350           break;
7351
7352         case EXEC_OMP_ATOMIC:
7353         case EXEC_OMP_CRITICAL:
7354         case EXEC_OMP_DO:
7355         case EXEC_OMP_MASTER:
7356         case EXEC_OMP_ORDERED:
7357         case EXEC_OMP_PARALLEL:
7358         case EXEC_OMP_PARALLEL_DO:
7359         case EXEC_OMP_PARALLEL_SECTIONS:
7360         case EXEC_OMP_PARALLEL_WORKSHARE:
7361         case EXEC_OMP_SECTIONS:
7362         case EXEC_OMP_SINGLE:
7363         case EXEC_OMP_TASK:
7364         case EXEC_OMP_TASKWAIT:
7365         case EXEC_OMP_WORKSHARE:
7366           break;
7367
7368         default:
7369           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
7370         }
7371
7372       resolve_code (b->next, ns);
7373     }
7374 }
7375
7376
7377 /* Does everything to resolve an ordinary assignment.  Returns true
7378    if this is an interface assignment.  */
7379 static bool
7380 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
7381 {
7382   bool rval = false;
7383   gfc_expr *lhs;
7384   gfc_expr *rhs;
7385   int llen = 0;
7386   int rlen = 0;
7387   int n;
7388   gfc_ref *ref;
7389
7390   if (gfc_extend_assign (code, ns) == SUCCESS)
7391     {
7392       gfc_symbol* assign_proc;
7393       gfc_expr** rhsptr;
7394
7395       if (code->op == EXEC_ASSIGN_CALL)
7396         {
7397           lhs = code->ext.actual->expr;
7398           rhsptr = &code->ext.actual->next->expr;
7399           assign_proc = code->symtree->n.sym;
7400         }
7401       else
7402         {
7403           gfc_actual_arglist* args;
7404           gfc_typebound_proc* tbp;
7405
7406           gcc_assert (code->op == EXEC_COMPCALL);
7407
7408           args = code->expr1->value.compcall.actual;
7409           lhs = args->expr;
7410           rhsptr = &args->next->expr;
7411
7412           tbp = code->expr1->value.compcall.tbp;
7413           gcc_assert (!tbp->is_generic);
7414           assign_proc = tbp->u.specific->n.sym;
7415         }
7416
7417       /* Make a temporary rhs when there is a default initializer
7418          and rhs is the same symbol as the lhs.  */
7419       if ((*rhsptr)->expr_type == EXPR_VARIABLE
7420             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
7421             && has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
7422             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
7423         *rhsptr = gfc_get_parentheses (*rhsptr);
7424
7425       return true;
7426     }
7427
7428   lhs = code->expr1;
7429   rhs = code->expr2;
7430
7431   if (rhs->is_boz
7432       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
7433                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
7434                          &code->loc) == FAILURE)
7435     return false;
7436
7437   /* Handle the case of a BOZ literal on the RHS.  */
7438   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
7439     {
7440       int rc;
7441       if (gfc_option.warn_surprising)
7442         gfc_warning ("BOZ literal at %L is bitwise transferred "
7443                      "non-integer symbol '%s'", &code->loc,
7444                      lhs->symtree->n.sym->name);
7445
7446       if (!gfc_convert_boz (rhs, &lhs->ts))
7447         return false;
7448       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
7449         {
7450           if (rc == ARITH_UNDERFLOW)
7451             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
7452                        ". This check can be disabled with the option "
7453                        "-fno-range-check", &rhs->where);
7454           else if (rc == ARITH_OVERFLOW)
7455             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
7456                        ". This check can be disabled with the option "
7457                        "-fno-range-check", &rhs->where);
7458           else if (rc == ARITH_NAN)
7459             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
7460                        ". This check can be disabled with the option "
7461                        "-fno-range-check", &rhs->where);
7462           return false;
7463         }
7464     }
7465
7466
7467   if (lhs->ts.type == BT_CHARACTER
7468         && gfc_option.warn_character_truncation)
7469     {
7470       if (lhs->ts.u.cl != NULL
7471             && lhs->ts.u.cl->length != NULL
7472             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7473         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
7474
7475       if (rhs->expr_type == EXPR_CONSTANT)
7476         rlen = rhs->value.character.length;
7477
7478       else if (rhs->ts.u.cl != NULL
7479                  && rhs->ts.u.cl->length != NULL
7480                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7481         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
7482
7483       if (rlen && llen && rlen > llen)
7484         gfc_warning_now ("CHARACTER expression will be truncated "
7485                          "in assignment (%d/%d) at %L",
7486                          llen, rlen, &code->loc);
7487     }
7488
7489   /* Ensure that a vector index expression for the lvalue is evaluated
7490      to a temporary if the lvalue symbol is referenced in it.  */
7491   if (lhs->rank)
7492     {
7493       for (ref = lhs->ref; ref; ref= ref->next)
7494         if (ref->type == REF_ARRAY)
7495           {
7496             for (n = 0; n < ref->u.ar.dimen; n++)
7497               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
7498                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
7499                                            ref->u.ar.start[n]))
7500                 ref->u.ar.start[n]
7501                         = gfc_get_parentheses (ref->u.ar.start[n]);
7502           }
7503     }
7504
7505   if (gfc_pure (NULL))
7506     {
7507       if (gfc_impure_variable (lhs->symtree->n.sym))
7508         {
7509           gfc_error ("Cannot assign to variable '%s' in PURE "
7510                      "procedure at %L",
7511                       lhs->symtree->n.sym->name,
7512                       &lhs->where);
7513           return rval;
7514         }
7515
7516       if (lhs->ts.type == BT_DERIVED
7517             && lhs->expr_type == EXPR_VARIABLE
7518             && lhs->ts.u.derived->attr.pointer_comp
7519             && gfc_impure_variable (rhs->symtree->n.sym))
7520         {
7521           gfc_error ("The impure variable at %L is assigned to "
7522                      "a derived type variable with a POINTER "
7523                      "component in a PURE procedure (12.6)",
7524                      &rhs->where);
7525           return rval;
7526         }
7527     }
7528
7529   gfc_check_assign (lhs, rhs, 1);
7530   return false;
7531 }
7532
7533
7534 /* Given a block of code, recursively resolve everything pointed to by this
7535    code block.  */
7536
7537 static void
7538 resolve_code (gfc_code *code, gfc_namespace *ns)
7539 {
7540   int omp_workshare_save;
7541   int forall_save;
7542   code_stack frame;
7543   gfc_try t;
7544
7545   frame.prev = cs_base;
7546   frame.head = code;
7547   cs_base = &frame;
7548
7549   find_reachable_labels (code);
7550
7551   for (; code; code = code->next)
7552     {
7553       frame.current = code;
7554       forall_save = forall_flag;
7555
7556       if (code->op == EXEC_FORALL)
7557         {
7558           forall_flag = 1;
7559           gfc_resolve_forall (code, ns, forall_save);
7560           forall_flag = 2;
7561         }
7562       else if (code->block)
7563         {
7564           omp_workshare_save = -1;
7565           switch (code->op)
7566             {
7567             case EXEC_OMP_PARALLEL_WORKSHARE:
7568               omp_workshare_save = omp_workshare_flag;
7569               omp_workshare_flag = 1;
7570               gfc_resolve_omp_parallel_blocks (code, ns);
7571               break;
7572             case EXEC_OMP_PARALLEL:
7573             case EXEC_OMP_PARALLEL_DO:
7574             case EXEC_OMP_PARALLEL_SECTIONS:
7575             case EXEC_OMP_TASK:
7576               omp_workshare_save = omp_workshare_flag;
7577               omp_workshare_flag = 0;
7578               gfc_resolve_omp_parallel_blocks (code, ns);
7579               break;
7580             case EXEC_OMP_DO:
7581               gfc_resolve_omp_do_blocks (code, ns);
7582               break;
7583             case EXEC_OMP_WORKSHARE:
7584               omp_workshare_save = omp_workshare_flag;
7585               omp_workshare_flag = 1;
7586               /* FALLTHROUGH */
7587             default:
7588               gfc_resolve_blocks (code->block, ns);
7589               break;
7590             }
7591
7592           if (omp_workshare_save != -1)
7593             omp_workshare_flag = omp_workshare_save;
7594         }
7595
7596       t = SUCCESS;
7597       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
7598         t = gfc_resolve_expr (code->expr1);
7599       forall_flag = forall_save;
7600
7601       if (gfc_resolve_expr (code->expr2) == FAILURE)
7602         t = FAILURE;
7603
7604       switch (code->op)
7605         {
7606         case EXEC_NOP:
7607         case EXEC_END_BLOCK:
7608         case EXEC_CYCLE:
7609         case EXEC_PAUSE:
7610         case EXEC_STOP:
7611         case EXEC_EXIT:
7612         case EXEC_CONTINUE:
7613         case EXEC_DT_END:
7614         case EXEC_ASSIGN_CALL:
7615           break;
7616
7617         case EXEC_ENTRY:
7618           /* Keep track of which entry we are up to.  */
7619           current_entry_id = code->ext.entry->id;
7620           break;
7621
7622         case EXEC_WHERE:
7623           resolve_where (code, NULL);
7624           break;
7625
7626         case EXEC_GOTO:
7627           if (code->expr1 != NULL)
7628             {
7629               if (code->expr1->ts.type != BT_INTEGER)
7630                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
7631                            "INTEGER variable", &code->expr1->where);
7632               else if (code->expr1->symtree->n.sym->attr.assign != 1)
7633                 gfc_error ("Variable '%s' has not been assigned a target "
7634                            "label at %L", code->expr1->symtree->n.sym->name,
7635                            &code->expr1->where);
7636             }
7637           else
7638             resolve_branch (code->label1, code);
7639           break;
7640
7641         case EXEC_RETURN:
7642           if (code->expr1 != NULL
7643                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
7644             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
7645                        "INTEGER return specifier", &code->expr1->where);
7646           break;
7647
7648         case EXEC_INIT_ASSIGN:
7649         case EXEC_END_PROCEDURE:
7650           break;
7651
7652         case EXEC_ASSIGN:
7653           if (t == FAILURE)
7654             break;
7655
7656           if (resolve_ordinary_assign (code, ns))
7657             {
7658               if (code->op == EXEC_COMPCALL)
7659                 goto compcall;
7660               else
7661                 goto call;
7662             }
7663           break;
7664
7665         case EXEC_LABEL_ASSIGN:
7666           if (code->label1->defined == ST_LABEL_UNKNOWN)
7667             gfc_error ("Label %d referenced at %L is never defined",
7668                        code->label1->value, &code->label1->where);
7669           if (t == SUCCESS
7670               && (code->expr1->expr_type != EXPR_VARIABLE
7671                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
7672                   || code->expr1->symtree->n.sym->ts.kind
7673                      != gfc_default_integer_kind
7674                   || code->expr1->symtree->n.sym->as != NULL))
7675             gfc_error ("ASSIGN statement at %L requires a scalar "
7676                        "default INTEGER variable", &code->expr1->where);
7677           break;
7678
7679         case EXEC_POINTER_ASSIGN:
7680           if (t == FAILURE)
7681             break;
7682
7683           gfc_check_pointer_assign (code->expr1, code->expr2);
7684           break;
7685
7686         case EXEC_ARITHMETIC_IF:
7687           if (t == SUCCESS
7688               && code->expr1->ts.type != BT_INTEGER
7689               && code->expr1->ts.type != BT_REAL)
7690             gfc_error ("Arithmetic IF statement at %L requires a numeric "
7691                        "expression", &code->expr1->where);
7692
7693           resolve_branch (code->label1, code);
7694           resolve_branch (code->label2, code);
7695           resolve_branch (code->label3, code);
7696           break;
7697
7698         case EXEC_IF:
7699           if (t == SUCCESS && code->expr1 != NULL
7700               && (code->expr1->ts.type != BT_LOGICAL
7701                   || code->expr1->rank != 0))
7702             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7703                        &code->expr1->where);
7704           break;
7705
7706         case EXEC_CALL:
7707         call:
7708           resolve_call (code);
7709           break;
7710
7711         case EXEC_COMPCALL:
7712         compcall:
7713           if (code->expr1->symtree
7714                 && code->expr1->symtree->n.sym->ts.type == BT_CLASS)
7715             resolve_class_typebound_call (code);
7716           else
7717             resolve_typebound_call (code);
7718           break;
7719
7720         case EXEC_CALL_PPC:
7721           resolve_ppc_call (code);
7722           break;
7723
7724         case EXEC_SELECT:
7725           /* Select is complicated. Also, a SELECT construct could be
7726              a transformed computed GOTO.  */
7727           resolve_select (code);
7728           break;
7729
7730         case EXEC_SELECT_TYPE:
7731           resolve_select_type (code);
7732           break;
7733
7734         case EXEC_BLOCK:
7735           gfc_resolve (code->ext.ns);
7736           break;
7737
7738         case EXEC_DO:
7739           if (code->ext.iterator != NULL)
7740             {
7741               gfc_iterator *iter = code->ext.iterator;
7742               if (gfc_resolve_iterator (iter, true) != FAILURE)
7743                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
7744             }
7745           break;
7746
7747         case EXEC_DO_WHILE:
7748           if (code->expr1 == NULL)
7749             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
7750           if (t == SUCCESS
7751               && (code->expr1->rank != 0
7752                   || code->expr1->ts.type != BT_LOGICAL))
7753             gfc_error ("Exit condition of DO WHILE loop at %L must be "
7754                        "a scalar LOGICAL expression", &code->expr1->where);
7755           break;
7756
7757         case EXEC_ALLOCATE:
7758           if (t == SUCCESS)
7759             resolve_allocate_deallocate (code, "ALLOCATE");
7760
7761           break;
7762
7763         case EXEC_DEALLOCATE:
7764           if (t == SUCCESS)
7765             resolve_allocate_deallocate (code, "DEALLOCATE");
7766
7767           break;
7768
7769         case EXEC_OPEN:
7770           if (gfc_resolve_open (code->ext.open) == FAILURE)
7771             break;
7772
7773           resolve_branch (code->ext.open->err, code);
7774           break;
7775
7776         case EXEC_CLOSE:
7777           if (gfc_resolve_close (code->ext.close) == FAILURE)
7778             break;
7779
7780           resolve_branch (code->ext.close->err, code);
7781           break;
7782
7783         case EXEC_BACKSPACE:
7784         case EXEC_ENDFILE:
7785         case EXEC_REWIND:
7786         case EXEC_FLUSH:
7787           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
7788             break;
7789
7790           resolve_branch (code->ext.filepos->err, code);
7791           break;
7792
7793         case EXEC_INQUIRE:
7794           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
7795               break;
7796
7797           resolve_branch (code->ext.inquire->err, code);
7798           break;
7799
7800         case EXEC_IOLENGTH:
7801           gcc_assert (code->ext.inquire != NULL);
7802           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
7803             break;
7804
7805           resolve_branch (code->ext.inquire->err, code);
7806           break;
7807
7808         case EXEC_WAIT:
7809           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
7810             break;
7811
7812           resolve_branch (code->ext.wait->err, code);
7813           resolve_branch (code->ext.wait->end, code);
7814           resolve_branch (code->ext.wait->eor, code);
7815           break;
7816
7817         case EXEC_READ:
7818         case EXEC_WRITE:
7819           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
7820             break;
7821
7822           resolve_branch (code->ext.dt->err, code);
7823           resolve_branch (code->ext.dt->end, code);
7824           resolve_branch (code->ext.dt->eor, code);
7825           break;
7826
7827         case EXEC_TRANSFER:
7828           resolve_transfer (code);
7829           break;
7830
7831         case EXEC_FORALL:
7832           resolve_forall_iterators (code->ext.forall_iterator);
7833
7834           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
7835             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
7836                        "expression", &code->expr1->where);
7837           break;
7838
7839         case EXEC_OMP_ATOMIC:
7840         case EXEC_OMP_BARRIER:
7841         case EXEC_OMP_CRITICAL:
7842         case EXEC_OMP_FLUSH:
7843         case EXEC_OMP_DO:
7844         case EXEC_OMP_MASTER:
7845         case EXEC_OMP_ORDERED:
7846         case EXEC_OMP_SECTIONS:
7847         case EXEC_OMP_SINGLE:
7848         case EXEC_OMP_TASKWAIT:
7849         case EXEC_OMP_WORKSHARE:
7850           gfc_resolve_omp_directive (code, ns);
7851           break;
7852
7853         case EXEC_OMP_PARALLEL:
7854         case EXEC_OMP_PARALLEL_DO:
7855         case EXEC_OMP_PARALLEL_SECTIONS:
7856         case EXEC_OMP_PARALLEL_WORKSHARE:
7857         case EXEC_OMP_TASK:
7858           omp_workshare_save = omp_workshare_flag;
7859           omp_workshare_flag = 0;
7860           gfc_resolve_omp_directive (code, ns);
7861           omp_workshare_flag = omp_workshare_save;
7862           break;
7863
7864         default:
7865           gfc_internal_error ("resolve_code(): Bad statement code");
7866         }
7867     }
7868
7869   cs_base = frame.prev;
7870 }
7871
7872
7873 /* Resolve initial values and make sure they are compatible with
7874    the variable.  */
7875
7876 static void
7877 resolve_values (gfc_symbol *sym)
7878 {
7879   if (sym->value == NULL)
7880     return;
7881
7882   if (gfc_resolve_expr (sym->value) == FAILURE)
7883     return;
7884
7885   gfc_check_assign_symbol (sym, sym->value);
7886 }
7887
7888
7889 /* Verify the binding labels for common blocks that are BIND(C).  The label
7890    for a BIND(C) common block must be identical in all scoping units in which
7891    the common block is declared.  Further, the binding label can not collide
7892    with any other global entity in the program.  */
7893
7894 static void
7895 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
7896 {
7897   if (comm_block_tree->n.common->is_bind_c == 1)
7898     {
7899       gfc_gsymbol *binding_label_gsym;
7900       gfc_gsymbol *comm_name_gsym;
7901
7902       /* See if a global symbol exists by the common block's name.  It may
7903          be NULL if the common block is use-associated.  */
7904       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
7905                                          comm_block_tree->n.common->name);
7906       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
7907         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
7908                    "with the global entity '%s' at %L",
7909                    comm_block_tree->n.common->binding_label,
7910                    comm_block_tree->n.common->name,
7911                    &(comm_block_tree->n.common->where),
7912                    comm_name_gsym->name, &(comm_name_gsym->where));
7913       else if (comm_name_gsym != NULL
7914                && strcmp (comm_name_gsym->name,
7915                           comm_block_tree->n.common->name) == 0)
7916         {
7917           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
7918              as expected.  */
7919           if (comm_name_gsym->binding_label == NULL)
7920             /* No binding label for common block stored yet; save this one.  */
7921             comm_name_gsym->binding_label =
7922               comm_block_tree->n.common->binding_label;
7923           else
7924             if (strcmp (comm_name_gsym->binding_label,
7925                         comm_block_tree->n.common->binding_label) != 0)
7926               {
7927                 /* Common block names match but binding labels do not.  */
7928                 gfc_error ("Binding label '%s' for common block '%s' at %L "
7929                            "does not match the binding label '%s' for common "
7930                            "block '%s' at %L",
7931                            comm_block_tree->n.common->binding_label,
7932                            comm_block_tree->n.common->name,
7933                            &(comm_block_tree->n.common->where),
7934                            comm_name_gsym->binding_label,
7935                            comm_name_gsym->name,
7936                            &(comm_name_gsym->where));
7937                 return;
7938               }
7939         }
7940
7941       /* There is no binding label (NAME="") so we have nothing further to
7942          check and nothing to add as a global symbol for the label.  */
7943       if (comm_block_tree->n.common->binding_label[0] == '\0' )
7944         return;
7945       
7946       binding_label_gsym =
7947         gfc_find_gsymbol (gfc_gsym_root,
7948                           comm_block_tree->n.common->binding_label);
7949       if (binding_label_gsym == NULL)
7950         {
7951           /* Need to make a global symbol for the binding label to prevent
7952              it from colliding with another.  */
7953           binding_label_gsym =
7954             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
7955           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
7956           binding_label_gsym->type = GSYM_COMMON;
7957         }
7958       else
7959         {
7960           /* If comm_name_gsym is NULL, the name common block is use
7961              associated and the name could be colliding.  */
7962           if (binding_label_gsym->type != GSYM_COMMON)
7963             gfc_error ("Binding label '%s' for common block '%s' at %L "
7964                        "collides with the global entity '%s' at %L",
7965                        comm_block_tree->n.common->binding_label,
7966                        comm_block_tree->n.common->name,
7967                        &(comm_block_tree->n.common->where),
7968                        binding_label_gsym->name,
7969                        &(binding_label_gsym->where));
7970           else if (comm_name_gsym != NULL
7971                    && (strcmp (binding_label_gsym->name,
7972                                comm_name_gsym->binding_label) != 0)
7973                    && (strcmp (binding_label_gsym->sym_name,
7974                                comm_name_gsym->name) != 0))
7975             gfc_error ("Binding label '%s' for common block '%s' at %L "
7976                        "collides with global entity '%s' at %L",
7977                        binding_label_gsym->name, binding_label_gsym->sym_name,
7978                        &(comm_block_tree->n.common->where),
7979                        comm_name_gsym->name, &(comm_name_gsym->where));
7980         }
7981     }
7982   
7983   return;
7984 }
7985
7986
7987 /* Verify any BIND(C) derived types in the namespace so we can report errors
7988    for them once, rather than for each variable declared of that type.  */
7989
7990 static void
7991 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
7992 {
7993   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
7994       && derived_sym->attr.is_bind_c == 1)
7995     verify_bind_c_derived_type (derived_sym);
7996   
7997   return;
7998 }
7999
8000
8001 /* Verify that any binding labels used in a given namespace do not collide 
8002    with the names or binding labels of any global symbols.  */
8003
8004 static void
8005 gfc_verify_binding_labels (gfc_symbol *sym)
8006 {
8007   int has_error = 0;
8008   
8009   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8010       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8011     {
8012       gfc_gsymbol *bind_c_sym;
8013
8014       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8015       if (bind_c_sym != NULL 
8016           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8017         {
8018           if (sym->attr.if_source == IFSRC_DECL 
8019               && (bind_c_sym->type != GSYM_SUBROUTINE 
8020                   && bind_c_sym->type != GSYM_FUNCTION) 
8021               && ((sym->attr.contained == 1 
8022                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8023                   || (sym->attr.use_assoc == 1 
8024                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8025             {
8026               /* Make sure global procedures don't collide with anything.  */
8027               gfc_error ("Binding label '%s' at %L collides with the global "
8028                          "entity '%s' at %L", sym->binding_label,
8029                          &(sym->declared_at), bind_c_sym->name,
8030                          &(bind_c_sym->where));
8031               has_error = 1;
8032             }
8033           else if (sym->attr.contained == 0 
8034                    && (sym->attr.if_source == IFSRC_IFBODY 
8035                        && sym->attr.flavor == FL_PROCEDURE) 
8036                    && (bind_c_sym->sym_name != NULL 
8037                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8038             {
8039               /* Make sure procedures in interface bodies don't collide.  */
8040               gfc_error ("Binding label '%s' in interface body at %L collides "
8041                          "with the global entity '%s' at %L",
8042                          sym->binding_label,
8043                          &(sym->declared_at), bind_c_sym->name,
8044                          &(bind_c_sym->where));
8045               has_error = 1;
8046             }
8047           else if (sym->attr.contained == 0 
8048                    && sym->attr.if_source == IFSRC_UNKNOWN)
8049             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8050                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8051                 || sym->attr.use_assoc == 0)
8052               {
8053                 gfc_error ("Binding label '%s' at %L collides with global "
8054                            "entity '%s' at %L", sym->binding_label,
8055                            &(sym->declared_at), bind_c_sym->name,
8056                            &(bind_c_sym->where));
8057                 has_error = 1;
8058               }
8059
8060           if (has_error != 0)
8061             /* Clear the binding label to prevent checking multiple times.  */
8062             sym->binding_label[0] = '\0';
8063         }
8064       else if (bind_c_sym == NULL)
8065         {
8066           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8067           bind_c_sym->where = sym->declared_at;
8068           bind_c_sym->sym_name = sym->name;
8069
8070           if (sym->attr.use_assoc == 1)
8071             bind_c_sym->mod_name = sym->module;
8072           else
8073             if (sym->ns->proc_name != NULL)
8074               bind_c_sym->mod_name = sym->ns->proc_name->name;
8075
8076           if (sym->attr.contained == 0)
8077             {
8078               if (sym->attr.subroutine)
8079                 bind_c_sym->type = GSYM_SUBROUTINE;
8080               else if (sym->attr.function)
8081                 bind_c_sym->type = GSYM_FUNCTION;
8082             }
8083         }
8084     }
8085   return;
8086 }
8087
8088
8089 /* Resolve an index expression.  */
8090
8091 static gfc_try
8092 resolve_index_expr (gfc_expr *e)
8093 {
8094   if (gfc_resolve_expr (e) == FAILURE)
8095     return FAILURE;
8096
8097   if (gfc_simplify_expr (e, 0) == FAILURE)
8098     return FAILURE;
8099
8100   if (gfc_specification_expr (e) == FAILURE)
8101     return FAILURE;
8102
8103   return SUCCESS;
8104 }
8105
8106 /* Resolve a charlen structure.  */
8107
8108 static gfc_try
8109 resolve_charlen (gfc_charlen *cl)
8110 {
8111   int i, k;
8112
8113   if (cl->resolved)
8114     return SUCCESS;
8115
8116   cl->resolved = 1;
8117
8118   specification_expr = 1;
8119
8120   if (resolve_index_expr (cl->length) == FAILURE)
8121     {
8122       specification_expr = 0;
8123       return FAILURE;
8124     }
8125
8126   /* "If the character length parameter value evaluates to a negative
8127      value, the length of character entities declared is zero."  */
8128   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8129     {
8130       gfc_warning_now ("CHARACTER variable has zero length at %L",
8131                        &cl->length->where);
8132       gfc_replace_expr (cl->length, gfc_int_expr (0));
8133     }
8134
8135   /* Check that the character length is not too large.  */
8136   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8137   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8138       && cl->length->ts.type == BT_INTEGER
8139       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8140     {
8141       gfc_error ("String length at %L is too large", &cl->length->where);
8142       return FAILURE;
8143     }
8144
8145   return SUCCESS;
8146 }
8147
8148
8149 /* Test for non-constant shape arrays.  */
8150
8151 static bool
8152 is_non_constant_shape_array (gfc_symbol *sym)
8153 {
8154   gfc_expr *e;
8155   int i;
8156   bool not_constant;
8157
8158   not_constant = false;
8159   if (sym->as != NULL)
8160     {
8161       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8162          has not been simplified; parameter array references.  Do the
8163          simplification now.  */
8164       for (i = 0; i < sym->as->rank; i++)
8165         {
8166           e = sym->as->lower[i];
8167           if (e && (resolve_index_expr (e) == FAILURE
8168                     || !gfc_is_constant_expr (e)))
8169             not_constant = true;
8170
8171           e = sym->as->upper[i];
8172           if (e && (resolve_index_expr (e) == FAILURE
8173                     || !gfc_is_constant_expr (e)))
8174             not_constant = true;
8175         }
8176     }
8177   return not_constant;
8178 }
8179
8180 /* Given a symbol and an initialization expression, add code to initialize
8181    the symbol to the function entry.  */
8182 static void
8183 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8184 {
8185   gfc_expr *lval;
8186   gfc_code *init_st;
8187   gfc_namespace *ns = sym->ns;
8188
8189   /* Search for the function namespace if this is a contained
8190      function without an explicit result.  */
8191   if (sym->attr.function && sym == sym->result
8192       && sym->name != sym->ns->proc_name->name)
8193     {
8194       ns = ns->contained;
8195       for (;ns; ns = ns->sibling)
8196         if (strcmp (ns->proc_name->name, sym->name) == 0)
8197           break;
8198     }
8199
8200   if (ns == NULL)
8201     {
8202       gfc_free_expr (init);
8203       return;
8204     }
8205
8206   /* Build an l-value expression for the result.  */
8207   lval = gfc_lval_expr_from_sym (sym);
8208
8209   /* Add the code at scope entry.  */
8210   init_st = gfc_get_code ();
8211   init_st->next = ns->code;
8212   ns->code = init_st;
8213
8214   /* Assign the default initializer to the l-value.  */
8215   init_st->loc = sym->declared_at;
8216   init_st->op = EXEC_INIT_ASSIGN;
8217   init_st->expr1 = lval;
8218   init_st->expr2 = init;
8219 }
8220
8221 /* Assign the default initializer to a derived type variable or result.  */
8222
8223 static void
8224 apply_default_init (gfc_symbol *sym)
8225 {
8226   gfc_expr *init = NULL;
8227
8228   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8229     return;
8230
8231   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
8232     init = gfc_default_initializer (&sym->ts);
8233
8234   if (init == NULL)
8235     return;
8236
8237   build_init_assign (sym, init);
8238 }
8239
8240 /* Build an initializer for a local integer, real, complex, logical, or
8241    character variable, based on the command line flags finit-local-zero,
8242    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
8243    null if the symbol should not have a default initialization.  */
8244 static gfc_expr *
8245 build_default_init_expr (gfc_symbol *sym)
8246 {
8247   int char_len;
8248   gfc_expr *init_expr;
8249   int i;
8250
8251   /* These symbols should never have a default initialization.  */
8252   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
8253       || sym->attr.external
8254       || sym->attr.dummy
8255       || sym->attr.pointer
8256       || sym->attr.in_equivalence
8257       || sym->attr.in_common
8258       || sym->attr.data
8259       || sym->module
8260       || sym->attr.cray_pointee
8261       || sym->attr.cray_pointer)
8262     return NULL;
8263
8264   /* Now we'll try to build an initializer expression.  */
8265   init_expr = gfc_get_expr ();
8266   init_expr->expr_type = EXPR_CONSTANT;
8267   init_expr->ts.type = sym->ts.type;
8268   init_expr->ts.kind = sym->ts.kind;
8269   init_expr->where = sym->declared_at;
8270   
8271   /* We will only initialize integers, reals, complex, logicals, and
8272      characters, and only if the corresponding command-line flags
8273      were set.  Otherwise, we free init_expr and return null.  */
8274   switch (sym->ts.type)
8275     {    
8276     case BT_INTEGER:
8277       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
8278         mpz_init_set_si (init_expr->value.integer, 
8279                          gfc_option.flag_init_integer_value);
8280       else
8281         {
8282           gfc_free_expr (init_expr);
8283           init_expr = NULL;
8284         }
8285       break;
8286
8287     case BT_REAL:
8288       mpfr_init (init_expr->value.real);
8289       switch (gfc_option.flag_init_real)
8290         {
8291         case GFC_INIT_REAL_SNAN:
8292           init_expr->is_snan = 1;
8293           /* Fall through.  */
8294         case GFC_INIT_REAL_NAN:
8295           mpfr_set_nan (init_expr->value.real);
8296           break;
8297
8298         case GFC_INIT_REAL_INF:
8299           mpfr_set_inf (init_expr->value.real, 1);
8300           break;
8301
8302         case GFC_INIT_REAL_NEG_INF:
8303           mpfr_set_inf (init_expr->value.real, -1);
8304           break;
8305
8306         case GFC_INIT_REAL_ZERO:
8307           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
8308           break;
8309
8310         default:
8311           gfc_free_expr (init_expr);
8312           init_expr = NULL;
8313           break;
8314         }
8315       break;
8316           
8317     case BT_COMPLEX:
8318 #ifdef HAVE_mpc
8319       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
8320 #else
8321       mpfr_init (init_expr->value.complex.r);
8322       mpfr_init (init_expr->value.complex.i);
8323 #endif
8324       switch (gfc_option.flag_init_real)
8325         {
8326         case GFC_INIT_REAL_SNAN:
8327           init_expr->is_snan = 1;
8328           /* Fall through.  */
8329         case GFC_INIT_REAL_NAN:
8330           mpfr_set_nan (mpc_realref (init_expr->value.complex));
8331           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
8332           break;
8333
8334         case GFC_INIT_REAL_INF:
8335           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
8336           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
8337           break;
8338
8339         case GFC_INIT_REAL_NEG_INF:
8340           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
8341           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
8342           break;
8343
8344         case GFC_INIT_REAL_ZERO:
8345 #ifdef HAVE_mpc
8346           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
8347 #else
8348           mpfr_set_ui (init_expr->value.complex.r, 0.0, GFC_RND_MODE);
8349           mpfr_set_ui (init_expr->value.complex.i, 0.0, GFC_RND_MODE);
8350 #endif
8351           break;
8352
8353         default:
8354           gfc_free_expr (init_expr);
8355           init_expr = NULL;
8356           break;
8357         }
8358       break;
8359           
8360     case BT_LOGICAL:
8361       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
8362         init_expr->value.logical = 0;
8363       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
8364         init_expr->value.logical = 1;
8365       else
8366         {
8367           gfc_free_expr (init_expr);
8368           init_expr = NULL;
8369         }
8370       break;
8371           
8372     case BT_CHARACTER:
8373       /* For characters, the length must be constant in order to 
8374          create a default initializer.  */
8375       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
8376           && sym->ts.u.cl->length
8377           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8378         {
8379           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
8380           init_expr->value.character.length = char_len;
8381           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
8382           for (i = 0; i < char_len; i++)
8383             init_expr->value.character.string[i]
8384               = (unsigned char) gfc_option.flag_init_character_value;
8385         }
8386       else
8387         {
8388           gfc_free_expr (init_expr);
8389           init_expr = NULL;
8390         }
8391       break;
8392           
8393     default:
8394      gfc_free_expr (init_expr);
8395      init_expr = NULL;
8396     }
8397   return init_expr;
8398 }
8399
8400 /* Add an initialization expression to a local variable.  */
8401 static void
8402 apply_default_init_local (gfc_symbol *sym)
8403 {
8404   gfc_expr *init = NULL;
8405
8406   /* The symbol should be a variable or a function return value.  */
8407   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8408       || (sym->attr.function && sym->result != sym))
8409     return;
8410
8411   /* Try to build the initializer expression.  If we can't initialize
8412      this symbol, then init will be NULL.  */
8413   init = build_default_init_expr (sym);
8414   if (init == NULL)
8415     return;
8416
8417   /* For saved variables, we don't want to add an initializer at 
8418      function entry, so we just add a static initializer.  */
8419   if (sym->attr.save || sym->ns->save_all)
8420     {
8421       /* Don't clobber an existing initializer!  */
8422       gcc_assert (sym->value == NULL);
8423       sym->value = init;
8424       return;
8425     }
8426
8427   build_init_assign (sym, init);
8428 }
8429
8430 /* Resolution of common features of flavors variable and procedure.  */
8431
8432 static gfc_try
8433 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
8434 {
8435   /* Constraints on deferred shape variable.  */
8436   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
8437     {
8438       if (sym->attr.allocatable)
8439         {
8440           if (sym->attr.dimension)
8441             {
8442               gfc_error ("Allocatable array '%s' at %L must have "
8443                          "a deferred shape", sym->name, &sym->declared_at);
8444               return FAILURE;
8445             }
8446           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
8447                                    "may not be ALLOCATABLE", sym->name,
8448                                    &sym->declared_at) == FAILURE)
8449             return FAILURE;
8450         }
8451
8452       if (sym->attr.pointer && sym->attr.dimension)
8453         {
8454           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
8455                      sym->name, &sym->declared_at);
8456           return FAILURE;
8457         }
8458
8459     }
8460   else
8461     {
8462       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
8463           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
8464         {
8465           gfc_error ("Array '%s' at %L cannot have a deferred shape",
8466                      sym->name, &sym->declared_at);
8467           return FAILURE;
8468          }
8469     }
8470   return SUCCESS;
8471 }
8472
8473
8474 /* Additional checks for symbols with flavor variable and derived
8475    type.  To be called from resolve_fl_variable.  */
8476
8477 static gfc_try
8478 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
8479 {
8480   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
8481
8482   /* Check to see if a derived type is blocked from being host
8483      associated by the presence of another class I symbol in the same
8484      namespace.  14.6.1.3 of the standard and the discussion on
8485      comp.lang.fortran.  */
8486   if (sym->ns != sym->ts.u.derived->ns
8487       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
8488     {
8489       gfc_symbol *s;
8490       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
8491       if (s && s->attr.flavor != FL_DERIVED)
8492         {
8493           gfc_error ("The type '%s' cannot be host associated at %L "
8494                      "because it is blocked by an incompatible object "
8495                      "of the same name declared at %L",
8496                      sym->ts.u.derived->name, &sym->declared_at,
8497                      &s->declared_at);
8498           return FAILURE;
8499         }
8500     }
8501
8502   /* 4th constraint in section 11.3: "If an object of a type for which
8503      component-initialization is specified (R429) appears in the
8504      specification-part of a module and does not have the ALLOCATABLE
8505      or POINTER attribute, the object shall have the SAVE attribute."
8506
8507      The check for initializers is performed with
8508      has_default_initializer because gfc_default_initializer generates
8509      a hidden default for allocatable components.  */
8510   if (!(sym->value || no_init_flag) && sym->ns->proc_name
8511       && sym->ns->proc_name->attr.flavor == FL_MODULE
8512       && !sym->ns->save_all && !sym->attr.save
8513       && !sym->attr.pointer && !sym->attr.allocatable
8514       && has_default_initializer (sym->ts.u.derived))
8515     {
8516       gfc_error("Object '%s' at %L must have the SAVE attribute for "
8517                 "default initialization of a component",
8518                 sym->name, &sym->declared_at);
8519       return FAILURE;
8520     }
8521
8522   if (sym->ts.type == BT_CLASS)
8523     {
8524       /* C502.  */
8525       if (!gfc_type_is_extensible (sym->ts.u.derived->components->ts.u.derived))
8526         {
8527           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
8528                      sym->ts.u.derived->name, sym->name, &sym->declared_at);
8529           return FAILURE;
8530         }
8531
8532       /* C509.  */
8533       if (!(sym->attr.dummy || sym->attr.allocatable || sym->attr.pointer
8534               || sym->ts.u.derived->components->attr.allocatable
8535               || sym->ts.u.derived->components->attr.pointer))
8536         {
8537           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
8538                      "or pointer", sym->name, &sym->declared_at);
8539           return FAILURE;
8540         }
8541     }
8542
8543   /* Assign default initializer.  */
8544   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
8545       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
8546     {
8547       sym->value = gfc_default_initializer (&sym->ts);
8548     }
8549
8550   return SUCCESS;
8551 }
8552
8553
8554 /* Resolve symbols with flavor variable.  */
8555
8556 static gfc_try
8557 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
8558 {
8559   int no_init_flag, automatic_flag;
8560   gfc_expr *e;
8561   const char *auto_save_msg;
8562
8563   auto_save_msg = "Automatic object '%s' at %L cannot have the "
8564                   "SAVE attribute";
8565
8566   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
8567     return FAILURE;
8568
8569   /* Set this flag to check that variables are parameters of all entries.
8570      This check is effected by the call to gfc_resolve_expr through
8571      is_non_constant_shape_array.  */
8572   specification_expr = 1;
8573
8574   if (sym->ns->proc_name
8575       && (sym->ns->proc_name->attr.flavor == FL_MODULE
8576           || sym->ns->proc_name->attr.is_main_program)
8577       && !sym->attr.use_assoc
8578       && !sym->attr.allocatable
8579       && !sym->attr.pointer
8580       && is_non_constant_shape_array (sym))
8581     {
8582       /* The shape of a main program or module array needs to be
8583          constant.  */
8584       gfc_error ("The module or main program array '%s' at %L must "
8585                  "have constant shape", sym->name, &sym->declared_at);
8586       specification_expr = 0;
8587       return FAILURE;
8588     }
8589
8590   if (sym->ts.type == BT_CHARACTER)
8591     {
8592       /* Make sure that character string variables with assumed length are
8593          dummy arguments.  */
8594       e = sym->ts.u.cl->length;
8595       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
8596         {
8597           gfc_error ("Entity with assumed character length at %L must be a "
8598                      "dummy argument or a PARAMETER", &sym->declared_at);
8599           return FAILURE;
8600         }
8601
8602       if (e && sym->attr.save && !gfc_is_constant_expr (e))
8603         {
8604           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
8605           return FAILURE;
8606         }
8607
8608       if (!gfc_is_constant_expr (e)
8609           && !(e->expr_type == EXPR_VARIABLE
8610                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
8611           && sym->ns->proc_name
8612           && (sym->ns->proc_name->attr.flavor == FL_MODULE
8613               || sym->ns->proc_name->attr.is_main_program)
8614           && !sym->attr.use_assoc)
8615         {
8616           gfc_error ("'%s' at %L must have constant character length "
8617                      "in this context", sym->name, &sym->declared_at);
8618           return FAILURE;
8619         }
8620     }
8621
8622   if (sym->value == NULL && sym->attr.referenced)
8623     apply_default_init_local (sym); /* Try to apply a default initialization.  */
8624
8625   /* Determine if the symbol may not have an initializer.  */
8626   no_init_flag = automatic_flag = 0;
8627   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
8628       || sym->attr.intrinsic || sym->attr.result)
8629     no_init_flag = 1;
8630   else if (sym->attr.dimension && !sym->attr.pointer
8631            && is_non_constant_shape_array (sym))
8632     {
8633       no_init_flag = automatic_flag = 1;
8634
8635       /* Also, they must not have the SAVE attribute.
8636          SAVE_IMPLICIT is checked below.  */
8637       if (sym->attr.save == SAVE_EXPLICIT)
8638         {
8639           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
8640           return FAILURE;
8641         }
8642     }
8643
8644   /* Ensure that any initializer is simplified.  */
8645   if (sym->value)
8646     gfc_simplify_expr (sym->value, 1);
8647
8648   /* Reject illegal initializers.  */
8649   if (!sym->mark && sym->value)
8650     {
8651       if (sym->attr.allocatable)
8652         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
8653                    sym->name, &sym->declared_at);
8654       else if (sym->attr.external)
8655         gfc_error ("External '%s' at %L cannot have an initializer",
8656                    sym->name, &sym->declared_at);
8657       else if (sym->attr.dummy
8658         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
8659         gfc_error ("Dummy '%s' at %L cannot have an initializer",
8660                    sym->name, &sym->declared_at);
8661       else if (sym->attr.intrinsic)
8662         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
8663                    sym->name, &sym->declared_at);
8664       else if (sym->attr.result)
8665         gfc_error ("Function result '%s' at %L cannot have an initializer",
8666                    sym->name, &sym->declared_at);
8667       else if (automatic_flag)
8668         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
8669                    sym->name, &sym->declared_at);
8670       else
8671         goto no_init_error;
8672       return FAILURE;
8673     }
8674
8675 no_init_error:
8676   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
8677     return resolve_fl_variable_derived (sym, no_init_flag);
8678
8679   return SUCCESS;
8680 }
8681
8682
8683 /* Resolve a procedure.  */
8684
8685 static gfc_try
8686 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
8687 {
8688   gfc_formal_arglist *arg;
8689
8690   if (sym->attr.ambiguous_interfaces && !sym->attr.referenced)
8691     gfc_warning ("Although not referenced, '%s' at %L has ambiguous "
8692                  "interfaces", sym->name, &sym->declared_at);
8693
8694   if (sym->attr.function
8695       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
8696     return FAILURE;
8697
8698   if (sym->ts.type == BT_CHARACTER)
8699     {
8700       gfc_charlen *cl = sym->ts.u.cl;
8701
8702       if (cl && cl->length && gfc_is_constant_expr (cl->length)
8703              && resolve_charlen (cl) == FAILURE)
8704         return FAILURE;
8705
8706       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
8707         {
8708           if (sym->attr.proc == PROC_ST_FUNCTION)
8709             {
8710               gfc_error ("Character-valued statement function '%s' at %L must "
8711                          "have constant length", sym->name, &sym->declared_at);
8712               return FAILURE;
8713             }
8714
8715           if (sym->attr.external && sym->formal == NULL
8716               && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
8717             {
8718               gfc_error ("Automatic character length function '%s' at %L must "
8719                          "have an explicit interface", sym->name,
8720                          &sym->declared_at);
8721               return FAILURE;
8722             }
8723         }
8724     }
8725
8726   /* Ensure that derived type for are not of a private type.  Internal
8727      module procedures are excluded by 2.2.3.3 - i.e., they are not
8728      externally accessible and can access all the objects accessible in
8729      the host.  */
8730   if (!(sym->ns->parent
8731         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
8732       && gfc_check_access(sym->attr.access, sym->ns->default_access))
8733     {
8734       gfc_interface *iface;
8735
8736       for (arg = sym->formal; arg; arg = arg->next)
8737         {
8738           if (arg->sym
8739               && arg->sym->ts.type == BT_DERIVED
8740               && !arg->sym->ts.u.derived->attr.use_assoc
8741               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
8742                                     arg->sym->ts.u.derived->ns->default_access)
8743               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
8744                                  "PRIVATE type and cannot be a dummy argument"
8745                                  " of '%s', which is PUBLIC at %L",
8746                                  arg->sym->name, sym->name, &sym->declared_at)
8747                  == FAILURE)
8748             {
8749               /* Stop this message from recurring.  */
8750               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
8751               return FAILURE;
8752             }
8753         }
8754
8755       /* PUBLIC interfaces may expose PRIVATE procedures that take types
8756          PRIVATE to the containing module.  */
8757       for (iface = sym->generic; iface; iface = iface->next)
8758         {
8759           for (arg = iface->sym->formal; arg; arg = arg->next)
8760             {
8761               if (arg->sym
8762                   && arg->sym->ts.type == BT_DERIVED
8763                   && !arg->sym->ts.u.derived->attr.use_assoc
8764                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
8765                                         arg->sym->ts.u.derived->ns->default_access)
8766                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
8767                                      "'%s' in PUBLIC interface '%s' at %L "
8768                                      "takes dummy arguments of '%s' which is "
8769                                      "PRIVATE", iface->sym->name, sym->name,
8770                                      &iface->sym->declared_at,
8771                                      gfc_typename (&arg->sym->ts)) == FAILURE)
8772                 {
8773                   /* Stop this message from recurring.  */
8774                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
8775                   return FAILURE;
8776                 }
8777              }
8778         }
8779
8780       /* PUBLIC interfaces may expose PRIVATE procedures that take types
8781          PRIVATE to the containing module.  */
8782       for (iface = sym->generic; iface; iface = iface->next)
8783         {
8784           for (arg = iface->sym->formal; arg; arg = arg->next)
8785             {
8786               if (arg->sym
8787                   && arg->sym->ts.type == BT_DERIVED
8788                   && !arg->sym->ts.u.derived->attr.use_assoc
8789                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
8790                                         arg->sym->ts.u.derived->ns->default_access)
8791                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
8792                                      "'%s' in PUBLIC interface '%s' at %L "
8793                                      "takes dummy arguments of '%s' which is "
8794                                      "PRIVATE", iface->sym->name, sym->name,
8795                                      &iface->sym->declared_at,
8796                                      gfc_typename (&arg->sym->ts)) == FAILURE)
8797                 {
8798                   /* Stop this message from recurring.  */
8799                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
8800                   return FAILURE;
8801                 }
8802              }
8803         }
8804     }
8805
8806   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
8807       && !sym->attr.proc_pointer)
8808     {
8809       gfc_error ("Function '%s' at %L cannot have an initializer",
8810                  sym->name, &sym->declared_at);
8811       return FAILURE;
8812     }
8813
8814   /* An external symbol may not have an initializer because it is taken to be
8815      a procedure. Exception: Procedure Pointers.  */
8816   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
8817     {
8818       gfc_error ("External object '%s' at %L may not have an initializer",
8819                  sym->name, &sym->declared_at);
8820       return FAILURE;
8821     }
8822
8823   /* An elemental function is required to return a scalar 12.7.1  */
8824   if (sym->attr.elemental && sym->attr.function && sym->as)
8825     {
8826       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
8827                  "result", sym->name, &sym->declared_at);
8828       /* Reset so that the error only occurs once.  */
8829       sym->attr.elemental = 0;
8830       return FAILURE;
8831     }
8832
8833   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
8834      char-len-param shall not be array-valued, pointer-valued, recursive
8835      or pure.  ....snip... A character value of * may only be used in the
8836      following ways: (i) Dummy arg of procedure - dummy associates with
8837      actual length; (ii) To declare a named constant; or (iii) External
8838      function - but length must be declared in calling scoping unit.  */
8839   if (sym->attr.function
8840       && sym->ts.type == BT_CHARACTER
8841       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
8842     {
8843       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
8844           || (sym->attr.recursive) || (sym->attr.pure))
8845         {
8846           if (sym->as && sym->as->rank)
8847             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8848                        "array-valued", sym->name, &sym->declared_at);
8849
8850           if (sym->attr.pointer)
8851             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8852                        "pointer-valued", sym->name, &sym->declared_at);
8853
8854           if (sym->attr.pure)
8855             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8856                        "pure", sym->name, &sym->declared_at);
8857
8858           if (sym->attr.recursive)
8859             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
8860                        "recursive", sym->name, &sym->declared_at);
8861
8862           return FAILURE;
8863         }
8864
8865       /* Appendix B.2 of the standard.  Contained functions give an
8866          error anyway.  Fixed-form is likely to be F77/legacy.  */
8867       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
8868         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
8869                         "CHARACTER(*) function '%s' at %L",
8870                         sym->name, &sym->declared_at);
8871     }
8872
8873   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
8874     {
8875       gfc_formal_arglist *curr_arg;
8876       int has_non_interop_arg = 0;
8877
8878       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
8879                              sym->common_block) == FAILURE)
8880         {
8881           /* Clear these to prevent looking at them again if there was an
8882              error.  */
8883           sym->attr.is_bind_c = 0;
8884           sym->attr.is_c_interop = 0;
8885           sym->ts.is_c_interop = 0;
8886         }
8887       else
8888         {
8889           /* So far, no errors have been found.  */
8890           sym->attr.is_c_interop = 1;
8891           sym->ts.is_c_interop = 1;
8892         }
8893       
8894       curr_arg = sym->formal;
8895       while (curr_arg != NULL)
8896         {
8897           /* Skip implicitly typed dummy args here.  */
8898           if (curr_arg->sym->attr.implicit_type == 0)
8899             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
8900               /* If something is found to fail, record the fact so we
8901                  can mark the symbol for the procedure as not being
8902                  BIND(C) to try and prevent multiple errors being
8903                  reported.  */
8904               has_non_interop_arg = 1;
8905           
8906           curr_arg = curr_arg->next;
8907         }
8908
8909       /* See if any of the arguments were not interoperable and if so, clear
8910          the procedure symbol to prevent duplicate error messages.  */
8911       if (has_non_interop_arg != 0)
8912         {
8913           sym->attr.is_c_interop = 0;
8914           sym->ts.is_c_interop = 0;
8915           sym->attr.is_bind_c = 0;
8916         }
8917     }
8918   
8919   if (!sym->attr.proc_pointer)
8920     {
8921       if (sym->attr.save == SAVE_EXPLICIT)
8922         {
8923           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
8924                      "in '%s' at %L", sym->name, &sym->declared_at);
8925           return FAILURE;
8926         }
8927       if (sym->attr.intent)
8928         {
8929           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
8930                      "in '%s' at %L", sym->name, &sym->declared_at);
8931           return FAILURE;
8932         }
8933       if (sym->attr.subroutine && sym->attr.result)
8934         {
8935           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
8936                      "in '%s' at %L", sym->name, &sym->declared_at);
8937           return FAILURE;
8938         }
8939       if (sym->attr.external && sym->attr.function
8940           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
8941               || sym->attr.contained))
8942         {
8943           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
8944                      "in '%s' at %L", sym->name, &sym->declared_at);
8945           return FAILURE;
8946         }
8947       if (strcmp ("ppr@", sym->name) == 0)
8948         {
8949           gfc_error ("Procedure pointer result '%s' at %L "
8950                      "is missing the pointer attribute",
8951                      sym->ns->proc_name->name, &sym->declared_at);
8952           return FAILURE;
8953         }
8954     }
8955
8956   return SUCCESS;
8957 }
8958
8959
8960 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
8961    been defined and we now know their defined arguments, check that they fulfill
8962    the requirements of the standard for procedures used as finalizers.  */
8963
8964 static gfc_try
8965 gfc_resolve_finalizers (gfc_symbol* derived)
8966 {
8967   gfc_finalizer* list;
8968   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
8969   gfc_try result = SUCCESS;
8970   bool seen_scalar = false;
8971
8972   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
8973     return SUCCESS;
8974
8975   /* Walk over the list of finalizer-procedures, check them, and if any one
8976      does not fit in with the standard's definition, print an error and remove
8977      it from the list.  */
8978   prev_link = &derived->f2k_derived->finalizers;
8979   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
8980     {
8981       gfc_symbol* arg;
8982       gfc_finalizer* i;
8983       int my_rank;
8984
8985       /* Skip this finalizer if we already resolved it.  */
8986       if (list->proc_tree)
8987         {
8988           prev_link = &(list->next);
8989           continue;
8990         }
8991
8992       /* Check this exists and is a SUBROUTINE.  */
8993       if (!list->proc_sym->attr.subroutine)
8994         {
8995           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
8996                      list->proc_sym->name, &list->where);
8997           goto error;
8998         }
8999
9000       /* We should have exactly one argument.  */
9001       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9002         {
9003           gfc_error ("FINAL procedure at %L must have exactly one argument",
9004                      &list->where);
9005           goto error;
9006         }
9007       arg = list->proc_sym->formal->sym;
9008
9009       /* This argument must be of our type.  */
9010       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9011         {
9012           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9013                      &arg->declared_at, derived->name);
9014           goto error;
9015         }
9016
9017       /* It must neither be a pointer nor allocatable nor optional.  */
9018       if (arg->attr.pointer)
9019         {
9020           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9021                      &arg->declared_at);
9022           goto error;
9023         }
9024       if (arg->attr.allocatable)
9025         {
9026           gfc_error ("Argument of FINAL procedure at %L must not be"
9027                      " ALLOCATABLE", &arg->declared_at);
9028           goto error;
9029         }
9030       if (arg->attr.optional)
9031         {
9032           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9033                      &arg->declared_at);
9034           goto error;
9035         }
9036
9037       /* It must not be INTENT(OUT).  */
9038       if (arg->attr.intent == INTENT_OUT)
9039         {
9040           gfc_error ("Argument of FINAL procedure at %L must not be"
9041                      " INTENT(OUT)", &arg->declared_at);
9042           goto error;
9043         }
9044
9045       /* Warn if the procedure is non-scalar and not assumed shape.  */
9046       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9047           && arg->as->type != AS_ASSUMED_SHAPE)
9048         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9049                      " shape argument", &arg->declared_at);
9050
9051       /* Check that it does not match in kind and rank with a FINAL procedure
9052          defined earlier.  To really loop over the *earlier* declarations,
9053          we need to walk the tail of the list as new ones were pushed at the
9054          front.  */
9055       /* TODO: Handle kind parameters once they are implemented.  */
9056       my_rank = (arg->as ? arg->as->rank : 0);
9057       for (i = list->next; i; i = i->next)
9058         {
9059           /* Argument list might be empty; that is an error signalled earlier,
9060              but we nevertheless continued resolving.  */
9061           if (i->proc_sym->formal)
9062             {
9063               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9064               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9065               if (i_rank == my_rank)
9066                 {
9067                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9068                              " rank (%d) as '%s'",
9069                              list->proc_sym->name, &list->where, my_rank, 
9070                              i->proc_sym->name);
9071                   goto error;
9072                 }
9073             }
9074         }
9075
9076         /* Is this the/a scalar finalizer procedure?  */
9077         if (!arg->as || arg->as->rank == 0)
9078           seen_scalar = true;
9079
9080         /* Find the symtree for this procedure.  */
9081         gcc_assert (!list->proc_tree);
9082         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9083
9084         prev_link = &list->next;
9085         continue;
9086
9087         /* Remove wrong nodes immediately from the list so we don't risk any
9088            troubles in the future when they might fail later expectations.  */
9089 error:
9090         result = FAILURE;
9091         i = list;
9092         *prev_link = list->next;
9093         gfc_free_finalizer (i);
9094     }
9095
9096   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9097      were nodes in the list, must have been for arrays.  It is surely a good
9098      idea to have a scalar version there if there's something to finalize.  */
9099   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9100     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9101                  " defined at %L, suggest also scalar one",
9102                  derived->name, &derived->declared_at);
9103
9104   /* TODO:  Remove this error when finalization is finished.  */
9105   gfc_error ("Finalization at %L is not yet implemented",
9106              &derived->declared_at);
9107
9108   return result;
9109 }
9110
9111
9112 /* Check that it is ok for the typebound procedure proc to override the
9113    procedure old.  */
9114
9115 static gfc_try
9116 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9117 {
9118   locus where;
9119   const gfc_symbol* proc_target;
9120   const gfc_symbol* old_target;
9121   unsigned proc_pass_arg, old_pass_arg, argpos;
9122   gfc_formal_arglist* proc_formal;
9123   gfc_formal_arglist* old_formal;
9124
9125   /* This procedure should only be called for non-GENERIC proc.  */
9126   gcc_assert (!proc->n.tb->is_generic);
9127
9128   /* If the overwritten procedure is GENERIC, this is an error.  */
9129   if (old->n.tb->is_generic)
9130     {
9131       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9132                  old->name, &proc->n.tb->where);
9133       return FAILURE;
9134     }
9135
9136   where = proc->n.tb->where;
9137   proc_target = proc->n.tb->u.specific->n.sym;
9138   old_target = old->n.tb->u.specific->n.sym;
9139
9140   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9141   if (old->n.tb->non_overridable)
9142     {
9143       gfc_error ("'%s' at %L overrides a procedure binding declared"
9144                  " NON_OVERRIDABLE", proc->name, &where);
9145       return FAILURE;
9146     }
9147
9148   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9149   if (!old->n.tb->deferred && proc->n.tb->deferred)
9150     {
9151       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9152                  " non-DEFERRED binding", proc->name, &where);
9153       return FAILURE;
9154     }
9155
9156   /* If the overridden binding is PURE, the overriding must be, too.  */
9157   if (old_target->attr.pure && !proc_target->attr.pure)
9158     {
9159       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9160                  proc->name, &where);
9161       return FAILURE;
9162     }
9163
9164   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9165      is not, the overriding must not be either.  */
9166   if (old_target->attr.elemental && !proc_target->attr.elemental)
9167     {
9168       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9169                  " ELEMENTAL", proc->name, &where);
9170       return FAILURE;
9171     }
9172   if (!old_target->attr.elemental && proc_target->attr.elemental)
9173     {
9174       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9175                  " be ELEMENTAL, either", proc->name, &where);
9176       return FAILURE;
9177     }
9178
9179   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9180      SUBROUTINE.  */
9181   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9182     {
9183       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9184                  " SUBROUTINE", proc->name, &where);
9185       return FAILURE;
9186     }
9187
9188   /* If the overridden binding is a FUNCTION, the overriding must also be a
9189      FUNCTION and have the same characteristics.  */
9190   if (old_target->attr.function)
9191     {
9192       if (!proc_target->attr.function)
9193         {
9194           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9195                      " FUNCTION", proc->name, &where);
9196           return FAILURE;
9197         }
9198
9199       /* FIXME:  Do more comprehensive checking (including, for instance, the
9200          rank and array-shape).  */
9201       gcc_assert (proc_target->result && old_target->result);
9202       if (!gfc_compare_types (&proc_target->result->ts,
9203                               &old_target->result->ts))
9204         {
9205           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9206                      " matching result types", proc->name, &where);
9207           return FAILURE;
9208         }
9209     }
9210
9211   /* If the overridden binding is PUBLIC, the overriding one must not be
9212      PRIVATE.  */
9213   if (old->n.tb->access == ACCESS_PUBLIC
9214       && proc->n.tb->access == ACCESS_PRIVATE)
9215     {
9216       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9217                  " PRIVATE", proc->name, &where);
9218       return FAILURE;
9219     }
9220
9221   /* Compare the formal argument lists of both procedures.  This is also abused
9222      to find the position of the passed-object dummy arguments of both
9223      bindings as at least the overridden one might not yet be resolved and we
9224      need those positions in the check below.  */
9225   proc_pass_arg = old_pass_arg = 0;
9226   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9227     proc_pass_arg = 1;
9228   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9229     old_pass_arg = 1;
9230   argpos = 1;
9231   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9232        proc_formal && old_formal;
9233        proc_formal = proc_formal->next, old_formal = old_formal->next)
9234     {
9235       if (proc->n.tb->pass_arg
9236           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9237         proc_pass_arg = argpos;
9238       if (old->n.tb->pass_arg
9239           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9240         old_pass_arg = argpos;
9241
9242       /* Check that the names correspond.  */
9243       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9244         {
9245           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9246                      " to match the corresponding argument of the overridden"
9247                      " procedure", proc_formal->sym->name, proc->name, &where,
9248                      old_formal->sym->name);
9249           return FAILURE;
9250         }
9251
9252       /* Check that the types correspond if neither is the passed-object
9253          argument.  */
9254       /* FIXME:  Do more comprehensive testing here.  */
9255       if (proc_pass_arg != argpos && old_pass_arg != argpos
9256           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
9257         {
9258           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L in"
9259                      " in respect to the overridden procedure",
9260                      proc_formal->sym->name, proc->name, &where);
9261           return FAILURE;
9262         }
9263
9264       ++argpos;
9265     }
9266   if (proc_formal || old_formal)
9267     {
9268       gfc_error ("'%s' at %L must have the same number of formal arguments as"
9269                  " the overridden procedure", proc->name, &where);
9270       return FAILURE;
9271     }
9272
9273   /* If the overridden binding is NOPASS, the overriding one must also be
9274      NOPASS.  */
9275   if (old->n.tb->nopass && !proc->n.tb->nopass)
9276     {
9277       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
9278                  " NOPASS", proc->name, &where);
9279       return FAILURE;
9280     }
9281
9282   /* If the overridden binding is PASS(x), the overriding one must also be
9283      PASS and the passed-object dummy arguments must correspond.  */
9284   if (!old->n.tb->nopass)
9285     {
9286       if (proc->n.tb->nopass)
9287         {
9288           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
9289                      " PASS", proc->name, &where);
9290           return FAILURE;
9291         }
9292
9293       if (proc_pass_arg != old_pass_arg)
9294         {
9295           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
9296                      " the same position as the passed-object dummy argument of"
9297                      " the overridden procedure", proc->name, &where);
9298           return FAILURE;
9299         }
9300     }
9301
9302   return SUCCESS;
9303 }
9304
9305
9306 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
9307
9308 static gfc_try
9309 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
9310                              const char* generic_name, locus where)
9311 {
9312   gfc_symbol* sym1;
9313   gfc_symbol* sym2;
9314
9315   gcc_assert (t1->specific && t2->specific);
9316   gcc_assert (!t1->specific->is_generic);
9317   gcc_assert (!t2->specific->is_generic);
9318
9319   sym1 = t1->specific->u.specific->n.sym;
9320   sym2 = t2->specific->u.specific->n.sym;
9321
9322   if (sym1 == sym2)
9323     return SUCCESS;
9324
9325   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
9326   if (sym1->attr.subroutine != sym2->attr.subroutine
9327       || sym1->attr.function != sym2->attr.function)
9328     {
9329       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
9330                  " GENERIC '%s' at %L",
9331                  sym1->name, sym2->name, generic_name, &where);
9332       return FAILURE;
9333     }
9334
9335   /* Compare the interfaces.  */
9336   if (gfc_compare_interfaces (sym1, sym2, NULL, 1, 0, NULL, 0))
9337     {
9338       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
9339                  sym1->name, sym2->name, generic_name, &where);
9340       return FAILURE;
9341     }
9342
9343   return SUCCESS;
9344 }
9345
9346
9347 /* Worker function for resolving a generic procedure binding; this is used to
9348    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
9349
9350    The difference between those cases is finding possible inherited bindings
9351    that are overridden, as one has to look for them in tb_sym_root,
9352    tb_uop_root or tb_op, respectively.  Thus the caller must already find
9353    the super-type and set p->overridden correctly.  */
9354
9355 static gfc_try
9356 resolve_tb_generic_targets (gfc_symbol* super_type,
9357                             gfc_typebound_proc* p, const char* name)
9358 {
9359   gfc_tbp_generic* target;
9360   gfc_symtree* first_target;
9361   gfc_symtree* inherited;
9362
9363   gcc_assert (p && p->is_generic);
9364
9365   /* Try to find the specific bindings for the symtrees in our target-list.  */
9366   gcc_assert (p->u.generic);
9367   for (target = p->u.generic; target; target = target->next)
9368     if (!target->specific)
9369       {
9370         gfc_typebound_proc* overridden_tbp;
9371         gfc_tbp_generic* g;
9372         const char* target_name;
9373
9374         target_name = target->specific_st->name;
9375
9376         /* Defined for this type directly.  */
9377         if (target->specific_st->n.tb)
9378           {
9379             target->specific = target->specific_st->n.tb;
9380             goto specific_found;
9381           }
9382
9383         /* Look for an inherited specific binding.  */
9384         if (super_type)
9385           {
9386             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
9387                                                  true, NULL);
9388
9389             if (inherited)
9390               {
9391                 gcc_assert (inherited->n.tb);
9392                 target->specific = inherited->n.tb;
9393                 goto specific_found;
9394               }
9395           }
9396
9397         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
9398                    " at %L", target_name, name, &p->where);
9399         return FAILURE;
9400
9401         /* Once we've found the specific binding, check it is not ambiguous with
9402            other specifics already found or inherited for the same GENERIC.  */
9403 specific_found:
9404         gcc_assert (target->specific);
9405
9406         /* This must really be a specific binding!  */
9407         if (target->specific->is_generic)
9408           {
9409             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
9410                        " '%s' is GENERIC, too", name, &p->where, target_name);
9411             return FAILURE;
9412           }
9413
9414         /* Check those already resolved on this type directly.  */
9415         for (g = p->u.generic; g; g = g->next)
9416           if (g != target && g->specific
9417               && check_generic_tbp_ambiguity (target, g, name, p->where)
9418                   == FAILURE)
9419             return FAILURE;
9420
9421         /* Check for ambiguity with inherited specific targets.  */
9422         for (overridden_tbp = p->overridden; overridden_tbp;
9423              overridden_tbp = overridden_tbp->overridden)
9424           if (overridden_tbp->is_generic)
9425             {
9426               for (g = overridden_tbp->u.generic; g; g = g->next)
9427                 {
9428                   gcc_assert (g->specific);
9429                   if (check_generic_tbp_ambiguity (target, g,
9430                                                    name, p->where) == FAILURE)
9431                     return FAILURE;
9432                 }
9433             }
9434       }
9435
9436   /* If we attempt to "overwrite" a specific binding, this is an error.  */
9437   if (p->overridden && !p->overridden->is_generic)
9438     {
9439       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
9440                  " the same name", name, &p->where);
9441       return FAILURE;
9442     }
9443
9444   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
9445      all must have the same attributes here.  */
9446   first_target = p->u.generic->specific->u.specific;
9447   gcc_assert (first_target);
9448   p->subroutine = first_target->n.sym->attr.subroutine;
9449   p->function = first_target->n.sym->attr.function;
9450
9451   return SUCCESS;
9452 }
9453
9454
9455 /* Resolve a GENERIC procedure binding for a derived type.  */
9456
9457 static gfc_try
9458 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
9459 {
9460   gfc_symbol* super_type;
9461
9462   /* Find the overridden binding if any.  */
9463   st->n.tb->overridden = NULL;
9464   super_type = gfc_get_derived_super_type (derived);
9465   if (super_type)
9466     {
9467       gfc_symtree* overridden;
9468       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
9469                                             true, NULL);
9470
9471       if (overridden && overridden->n.tb)
9472         st->n.tb->overridden = overridden->n.tb;
9473     }
9474
9475   /* Resolve using worker function.  */
9476   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
9477 }
9478
9479
9480 /* Retrieve the target-procedure of an operator binding and do some checks in
9481    common for intrinsic and user-defined type-bound operators.  */
9482
9483 static gfc_symbol*
9484 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
9485 {
9486   gfc_symbol* target_proc;
9487
9488   gcc_assert (target->specific && !target->specific->is_generic);
9489   target_proc = target->specific->u.specific->n.sym;
9490   gcc_assert (target_proc);
9491
9492   /* All operator bindings must have a passed-object dummy argument.  */
9493   if (target->specific->nopass)
9494     {
9495       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
9496       return NULL;
9497     }
9498
9499   return target_proc;
9500 }
9501
9502
9503 /* Resolve a type-bound intrinsic operator.  */
9504
9505 static gfc_try
9506 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
9507                                 gfc_typebound_proc* p)
9508 {
9509   gfc_symbol* super_type;
9510   gfc_tbp_generic* target;
9511   
9512   /* If there's already an error here, do nothing (but don't fail again).  */
9513   if (p->error)
9514     return SUCCESS;
9515
9516   /* Operators should always be GENERIC bindings.  */
9517   gcc_assert (p->is_generic);
9518
9519   /* Look for an overridden binding.  */
9520   super_type = gfc_get_derived_super_type (derived);
9521   if (super_type && super_type->f2k_derived)
9522     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
9523                                                      op, true, NULL);
9524   else
9525     p->overridden = NULL;
9526
9527   /* Resolve general GENERIC properties using worker function.  */
9528   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
9529     goto error;
9530
9531   /* Check the targets to be procedures of correct interface.  */
9532   for (target = p->u.generic; target; target = target->next)
9533     {
9534       gfc_symbol* target_proc;
9535
9536       target_proc = get_checked_tb_operator_target (target, p->where);
9537       if (!target_proc)
9538         goto error;
9539
9540       if (!gfc_check_operator_interface (target_proc, op, p->where))
9541         goto error;
9542     }
9543
9544   return SUCCESS;
9545
9546 error:
9547   p->error = 1;
9548   return FAILURE;
9549 }
9550
9551
9552 /* Resolve a type-bound user operator (tree-walker callback).  */
9553
9554 static gfc_symbol* resolve_bindings_derived;
9555 static gfc_try resolve_bindings_result;
9556
9557 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
9558
9559 static void
9560 resolve_typebound_user_op (gfc_symtree* stree)
9561 {
9562   gfc_symbol* super_type;
9563   gfc_tbp_generic* target;
9564
9565   gcc_assert (stree && stree->n.tb);
9566
9567   if (stree->n.tb->error)
9568     return;
9569
9570   /* Operators should always be GENERIC bindings.  */
9571   gcc_assert (stree->n.tb->is_generic);
9572
9573   /* Find overridden procedure, if any.  */
9574   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
9575   if (super_type && super_type->f2k_derived)
9576     {
9577       gfc_symtree* overridden;
9578       overridden = gfc_find_typebound_user_op (super_type, NULL,
9579                                                stree->name, true, NULL);
9580
9581       if (overridden && overridden->n.tb)
9582         stree->n.tb->overridden = overridden->n.tb;
9583     }
9584   else
9585     stree->n.tb->overridden = NULL;
9586
9587   /* Resolve basically using worker function.  */
9588   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
9589         == FAILURE)
9590     goto error;
9591
9592   /* Check the targets to be functions of correct interface.  */
9593   for (target = stree->n.tb->u.generic; target; target = target->next)
9594     {
9595       gfc_symbol* target_proc;
9596
9597       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
9598       if (!target_proc)
9599         goto error;
9600
9601       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
9602         goto error;
9603     }
9604
9605   return;
9606
9607 error:
9608   resolve_bindings_result = FAILURE;
9609   stree->n.tb->error = 1;
9610 }
9611
9612
9613 /* Resolve the type-bound procedures for a derived type.  */
9614
9615 static void
9616 resolve_typebound_procedure (gfc_symtree* stree)
9617 {
9618   gfc_symbol* proc;
9619   locus where;
9620   gfc_symbol* me_arg;
9621   gfc_symbol* super_type;
9622   gfc_component* comp;
9623
9624   gcc_assert (stree);
9625
9626   /* Undefined specific symbol from GENERIC target definition.  */
9627   if (!stree->n.tb)
9628     return;
9629
9630   if (stree->n.tb->error)
9631     return;
9632
9633   /* If this is a GENERIC binding, use that routine.  */
9634   if (stree->n.tb->is_generic)
9635     {
9636       if (resolve_typebound_generic (resolve_bindings_derived, stree)
9637             == FAILURE)
9638         goto error;
9639       return;
9640     }
9641
9642   /* Get the target-procedure to check it.  */
9643   gcc_assert (!stree->n.tb->is_generic);
9644   gcc_assert (stree->n.tb->u.specific);
9645   proc = stree->n.tb->u.specific->n.sym;
9646   where = stree->n.tb->where;
9647
9648   /* Default access should already be resolved from the parser.  */
9649   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
9650
9651   /* It should be a module procedure or an external procedure with explicit
9652      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
9653   if ((!proc->attr.subroutine && !proc->attr.function)
9654       || (proc->attr.proc != PROC_MODULE
9655           && proc->attr.if_source != IFSRC_IFBODY)
9656       || (proc->attr.abstract && !stree->n.tb->deferred))
9657     {
9658       gfc_error ("'%s' must be a module procedure or an external procedure with"
9659                  " an explicit interface at %L", proc->name, &where);
9660       goto error;
9661     }
9662   stree->n.tb->subroutine = proc->attr.subroutine;
9663   stree->n.tb->function = proc->attr.function;
9664
9665   /* Find the super-type of the current derived type.  We could do this once and
9666      store in a global if speed is needed, but as long as not I believe this is
9667      more readable and clearer.  */
9668   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
9669
9670   /* If PASS, resolve and check arguments if not already resolved / loaded
9671      from a .mod file.  */
9672   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
9673     {
9674       if (stree->n.tb->pass_arg)
9675         {
9676           gfc_formal_arglist* i;
9677
9678           /* If an explicit passing argument name is given, walk the arg-list
9679              and look for it.  */
9680
9681           me_arg = NULL;
9682           stree->n.tb->pass_arg_num = 1;
9683           for (i = proc->formal; i; i = i->next)
9684             {
9685               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
9686                 {
9687                   me_arg = i->sym;
9688                   break;
9689                 }
9690               ++stree->n.tb->pass_arg_num;
9691             }
9692
9693           if (!me_arg)
9694             {
9695               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
9696                          " argument '%s'",
9697                          proc->name, stree->n.tb->pass_arg, &where,
9698                          stree->n.tb->pass_arg);
9699               goto error;
9700             }
9701         }
9702       else
9703         {
9704           /* Otherwise, take the first one; there should in fact be at least
9705              one.  */
9706           stree->n.tb->pass_arg_num = 1;
9707           if (!proc->formal)
9708             {
9709               gfc_error ("Procedure '%s' with PASS at %L must have at"
9710                          " least one argument", proc->name, &where);
9711               goto error;
9712             }
9713           me_arg = proc->formal->sym;
9714         }
9715
9716       /* Now check that the argument-type matches.  */
9717       gcc_assert (me_arg);
9718       if (me_arg->ts.type != BT_CLASS)
9719         {
9720           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
9721                      " at %L", proc->name, &where);
9722           goto error;
9723         }
9724
9725       if (me_arg->ts.u.derived->components->ts.u.derived
9726           != resolve_bindings_derived)
9727         {
9728           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
9729                      " the derived-type '%s'", me_arg->name, proc->name,
9730                      me_arg->name, &where, resolve_bindings_derived->name);
9731           goto error;
9732         }
9733
9734     }
9735
9736   /* If we are extending some type, check that we don't override a procedure
9737      flagged NON_OVERRIDABLE.  */
9738   stree->n.tb->overridden = NULL;
9739   if (super_type)
9740     {
9741       gfc_symtree* overridden;
9742       overridden = gfc_find_typebound_proc (super_type, NULL,
9743                                             stree->name, true, NULL);
9744
9745       if (overridden && overridden->n.tb)
9746         stree->n.tb->overridden = overridden->n.tb;
9747
9748       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
9749         goto error;
9750     }
9751
9752   /* See if there's a name collision with a component directly in this type.  */
9753   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
9754     if (!strcmp (comp->name, stree->name))
9755       {
9756         gfc_error ("Procedure '%s' at %L has the same name as a component of"
9757                    " '%s'",
9758                    stree->name, &where, resolve_bindings_derived->name);
9759         goto error;
9760       }
9761
9762   /* Try to find a name collision with an inherited component.  */
9763   if (super_type && gfc_find_component (super_type, stree->name, true, true))
9764     {
9765       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
9766                  " component of '%s'",
9767                  stree->name, &where, resolve_bindings_derived->name);
9768       goto error;
9769     }
9770
9771   stree->n.tb->error = 0;
9772   return;
9773
9774 error:
9775   resolve_bindings_result = FAILURE;
9776   stree->n.tb->error = 1;
9777 }
9778
9779 static gfc_try
9780 resolve_typebound_procedures (gfc_symbol* derived)
9781 {
9782   int op;
9783
9784   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
9785     return SUCCESS;
9786
9787   resolve_bindings_derived = derived;
9788   resolve_bindings_result = SUCCESS;
9789
9790   if (derived->f2k_derived->tb_sym_root)
9791     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
9792                           &resolve_typebound_procedure);
9793
9794   if (derived->f2k_derived->tb_uop_root)
9795     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
9796                           &resolve_typebound_user_op);
9797
9798   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
9799     {
9800       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
9801       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
9802                                                p) == FAILURE)
9803         resolve_bindings_result = FAILURE;
9804     }
9805
9806   return resolve_bindings_result;
9807 }
9808
9809
9810 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
9811    to give all identical derived types the same backend_decl.  */
9812 static void
9813 add_dt_to_dt_list (gfc_symbol *derived)
9814 {
9815   gfc_dt_list *dt_list;
9816
9817   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
9818     if (derived == dt_list->derived)
9819       break;
9820
9821   if (dt_list == NULL)
9822     {
9823       dt_list = gfc_get_dt_list ();
9824       dt_list->next = gfc_derived_types;
9825       dt_list->derived = derived;
9826       gfc_derived_types = dt_list;
9827     }
9828 }
9829
9830
9831 /* Ensure that a derived-type is really not abstract, meaning that every
9832    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
9833
9834 static gfc_try
9835 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
9836 {
9837   if (!st)
9838     return SUCCESS;
9839
9840   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
9841     return FAILURE;
9842   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
9843     return FAILURE;
9844
9845   if (st->n.tb && st->n.tb->deferred)
9846     {
9847       gfc_symtree* overriding;
9848       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
9849       gcc_assert (overriding && overriding->n.tb);
9850       if (overriding->n.tb->deferred)
9851         {
9852           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
9853                      " '%s' is DEFERRED and not overridden",
9854                      sub->name, &sub->declared_at, st->name);
9855           return FAILURE;
9856         }
9857     }
9858
9859   return SUCCESS;
9860 }
9861
9862 static gfc_try
9863 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
9864 {
9865   /* The algorithm used here is to recursively travel up the ancestry of sub
9866      and for each ancestor-type, check all bindings.  If any of them is
9867      DEFERRED, look it up starting from sub and see if the found (overriding)
9868      binding is not DEFERRED.
9869      This is not the most efficient way to do this, but it should be ok and is
9870      clearer than something sophisticated.  */
9871
9872   gcc_assert (ancestor && ancestor->attr.abstract && !sub->attr.abstract);
9873
9874   /* Walk bindings of this ancestor.  */
9875   if (ancestor->f2k_derived)
9876     {
9877       gfc_try t;
9878       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
9879       if (t == FAILURE)
9880         return FAILURE;
9881     }
9882
9883   /* Find next ancestor type and recurse on it.  */
9884   ancestor = gfc_get_derived_super_type (ancestor);
9885   if (ancestor)
9886     return ensure_not_abstract (sub, ancestor);
9887
9888   return SUCCESS;
9889 }
9890
9891
9892 static void resolve_symbol (gfc_symbol *sym);
9893
9894
9895 /* Resolve the components of a derived type.  */
9896
9897 static gfc_try
9898 resolve_fl_derived (gfc_symbol *sym)
9899 {
9900   gfc_symbol* super_type;
9901   gfc_component *c;
9902   int i;
9903
9904   super_type = gfc_get_derived_super_type (sym);
9905
9906   /* Ensure the extended type gets resolved before we do.  */
9907   if (super_type && resolve_fl_derived (super_type) == FAILURE)
9908     return FAILURE;
9909
9910   /* An ABSTRACT type must be extensible.  */
9911   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
9912     {
9913       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
9914                  sym->name, &sym->declared_at);
9915       return FAILURE;
9916     }
9917
9918   for (c = sym->components; c != NULL; c = c->next)
9919     {
9920       if (c->attr.proc_pointer && c->ts.interface)
9921         {
9922           if (c->ts.interface->attr.procedure)
9923             gfc_error ("Interface '%s', used by procedure pointer component "
9924                        "'%s' at %L, is declared in a later PROCEDURE statement",
9925                        c->ts.interface->name, c->name, &c->loc);
9926
9927           /* Get the attributes from the interface (now resolved).  */
9928           if (c->ts.interface->attr.if_source
9929               || c->ts.interface->attr.intrinsic)
9930             {
9931               gfc_symbol *ifc = c->ts.interface;
9932
9933               if (ifc->formal && !ifc->formal_ns)
9934                 resolve_symbol (ifc);
9935
9936               if (ifc->attr.intrinsic)
9937                 resolve_intrinsic (ifc, &ifc->declared_at);
9938
9939               if (ifc->result)
9940                 {
9941                   c->ts = ifc->result->ts;
9942                   c->attr.allocatable = ifc->result->attr.allocatable;
9943                   c->attr.pointer = ifc->result->attr.pointer;
9944                   c->attr.dimension = ifc->result->attr.dimension;
9945                   c->as = gfc_copy_array_spec (ifc->result->as);
9946                 }
9947               else
9948                 {   
9949                   c->ts = ifc->ts;
9950                   c->attr.allocatable = ifc->attr.allocatable;
9951                   c->attr.pointer = ifc->attr.pointer;
9952                   c->attr.dimension = ifc->attr.dimension;
9953                   c->as = gfc_copy_array_spec (ifc->as);
9954                 }
9955               c->ts.interface = ifc;
9956               c->attr.function = ifc->attr.function;
9957               c->attr.subroutine = ifc->attr.subroutine;
9958               gfc_copy_formal_args_ppc (c, ifc);
9959
9960               c->attr.pure = ifc->attr.pure;
9961               c->attr.elemental = ifc->attr.elemental;
9962               c->attr.recursive = ifc->attr.recursive;
9963               c->attr.always_explicit = ifc->attr.always_explicit;
9964               c->attr.ext_attr |= ifc->attr.ext_attr;
9965               /* Replace symbols in array spec.  */
9966               if (c->as)
9967                 {
9968                   int i;
9969                   for (i = 0; i < c->as->rank; i++)
9970                     {
9971                       gfc_expr_replace_comp (c->as->lower[i], c);
9972                       gfc_expr_replace_comp (c->as->upper[i], c);
9973                     }
9974                 }
9975               /* Copy char length.  */
9976               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
9977                 {
9978                   c->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
9979                   gfc_expr_replace_comp (c->ts.u.cl->length, c);
9980                 }
9981             }
9982           else if (c->ts.interface->name[0] != '\0')
9983             {
9984               gfc_error ("Interface '%s' of procedure pointer component "
9985                          "'%s' at %L must be explicit", c->ts.interface->name,
9986                          c->name, &c->loc);
9987               return FAILURE;
9988             }
9989         }
9990       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
9991         {
9992           c->ts = *gfc_get_default_type (c->name, NULL);
9993           c->attr.implicit_type = 1;
9994         }
9995
9996       /* Procedure pointer components: Check PASS arg.  */
9997       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0)
9998         {
9999           gfc_symbol* me_arg;
10000
10001           if (c->tb->pass_arg)
10002             {
10003               gfc_formal_arglist* i;
10004
10005               /* If an explicit passing argument name is given, walk the arg-list
10006                 and look for it.  */
10007
10008               me_arg = NULL;
10009               c->tb->pass_arg_num = 1;
10010               for (i = c->formal; i; i = i->next)
10011                 {
10012                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10013                     {
10014                       me_arg = i->sym;
10015                       break;
10016                     }
10017                   c->tb->pass_arg_num++;
10018                 }
10019
10020               if (!me_arg)
10021                 {
10022                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10023                              "at %L has no argument '%s'", c->name,
10024                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10025                   c->tb->error = 1;
10026                   return FAILURE;
10027                 }
10028             }
10029           else
10030             {
10031               /* Otherwise, take the first one; there should in fact be at least
10032                 one.  */
10033               c->tb->pass_arg_num = 1;
10034               if (!c->formal)
10035                 {
10036                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10037                              "must have at least one argument",
10038                              c->name, &c->loc);
10039                   c->tb->error = 1;
10040                   return FAILURE;
10041                 }
10042               me_arg = c->formal->sym;
10043             }
10044
10045           /* Now check that the argument-type matches.  */
10046           gcc_assert (me_arg);
10047           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10048               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10049               || (me_arg->ts.type == BT_CLASS
10050                   && me_arg->ts.u.derived->components->ts.u.derived != sym))
10051             {
10052               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10053                          " the derived type '%s'", me_arg->name, c->name,
10054                          me_arg->name, &c->loc, sym->name);
10055               c->tb->error = 1;
10056               return FAILURE;
10057             }
10058
10059           /* Check for C453.  */
10060           if (me_arg->attr.dimension)
10061             {
10062               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10063                          "must be scalar", me_arg->name, c->name, me_arg->name,
10064                          &c->loc);
10065               c->tb->error = 1;
10066               return FAILURE;
10067             }
10068
10069           if (me_arg->attr.pointer)
10070             {
10071               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10072                          "may not have the POINTER attribute", me_arg->name,
10073                          c->name, me_arg->name, &c->loc);
10074               c->tb->error = 1;
10075               return FAILURE;
10076             }
10077
10078           if (me_arg->attr.allocatable)
10079             {
10080               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10081                          "may not be ALLOCATABLE", me_arg->name, c->name,
10082                          me_arg->name, &c->loc);
10083               c->tb->error = 1;
10084               return FAILURE;
10085             }
10086
10087           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10088             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10089                        " at %L", c->name, &c->loc);
10090
10091         }
10092
10093       /* Check type-spec if this is not the parent-type component.  */
10094       if ((!sym->attr.extension || c != sym->components)
10095           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10096         return FAILURE;
10097
10098       /* If this type is an extension, see if this component has the same name
10099          as an inherited type-bound procedure.  */
10100       if (super_type
10101           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10102         {
10103           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10104                      " inherited type-bound procedure",
10105                      c->name, sym->name, &c->loc);
10106           return FAILURE;
10107         }
10108
10109       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10110         {
10111          if (c->ts.u.cl->length == NULL
10112              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10113              || !gfc_is_constant_expr (c->ts.u.cl->length))
10114            {
10115              gfc_error ("Character length of component '%s' needs to "
10116                         "be a constant specification expression at %L",
10117                         c->name,
10118                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10119              return FAILURE;
10120            }
10121         }
10122
10123       if (c->ts.type == BT_DERIVED
10124           && sym->component_access != ACCESS_PRIVATE
10125           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10126           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10127           && !c->ts.u.derived->attr.use_assoc
10128           && !gfc_check_access (c->ts.u.derived->attr.access,
10129                                 c->ts.u.derived->ns->default_access)
10130           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10131                              "is a PRIVATE type and cannot be a component of "
10132                              "'%s', which is PUBLIC at %L", c->name,
10133                              sym->name, &sym->declared_at) == FAILURE)
10134         return FAILURE;
10135
10136       if (sym->attr.sequence)
10137         {
10138           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10139             {
10140               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10141                          "not have the SEQUENCE attribute",
10142                          c->ts.u.derived->name, &sym->declared_at);
10143               return FAILURE;
10144             }
10145         }
10146
10147       if (c->ts.type == BT_DERIVED && c->attr.pointer
10148           && c->ts.u.derived->components == NULL
10149           && !c->ts.u.derived->attr.zero_comp)
10150         {
10151           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10152                      "that has not been declared", c->name, sym->name,
10153                      &c->loc);
10154           return FAILURE;
10155         }
10156
10157       /* C437.  */
10158       if (c->ts.type == BT_CLASS
10159           && !(c->ts.u.derived->components->attr.pointer
10160                || c->ts.u.derived->components->attr.allocatable))
10161         {
10162           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10163                      "or pointer", c->name, &c->loc);
10164           return FAILURE;
10165         }
10166
10167       /* Ensure that all the derived type components are put on the
10168          derived type list; even in formal namespaces, where derived type
10169          pointer components might not have been declared.  */
10170       if (c->ts.type == BT_DERIVED
10171             && c->ts.u.derived
10172             && c->ts.u.derived->components
10173             && c->attr.pointer
10174             && sym != c->ts.u.derived)
10175         add_dt_to_dt_list (c->ts.u.derived);
10176
10177       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10178           || c->as == NULL)
10179         continue;
10180
10181       for (i = 0; i < c->as->rank; i++)
10182         {
10183           if (c->as->lower[i] == NULL
10184               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
10185               || !gfc_is_constant_expr (c->as->lower[i])
10186               || c->as->upper[i] == NULL
10187               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
10188               || !gfc_is_constant_expr (c->as->upper[i]))
10189             {
10190               gfc_error ("Component '%s' of '%s' at %L must have "
10191                          "constant array bounds",
10192                          c->name, sym->name, &c->loc);
10193               return FAILURE;
10194             }
10195         }
10196     }
10197
10198   /* Resolve the type-bound procedures.  */
10199   if (resolve_typebound_procedures (sym) == FAILURE)
10200     return FAILURE;
10201
10202   /* Resolve the finalizer procedures.  */
10203   if (gfc_resolve_finalizers (sym) == FAILURE)
10204     return FAILURE;
10205
10206   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
10207      all DEFERRED bindings are overridden.  */
10208   if (super_type && super_type->attr.abstract && !sym->attr.abstract
10209       && ensure_not_abstract (sym, super_type) == FAILURE)
10210     return FAILURE;
10211
10212   /* Add derived type to the derived type list.  */
10213   add_dt_to_dt_list (sym);
10214
10215   return SUCCESS;
10216 }
10217
10218
10219 static gfc_try
10220 resolve_fl_namelist (gfc_symbol *sym)
10221 {
10222   gfc_namelist *nl;
10223   gfc_symbol *nlsym;
10224
10225   /* Reject PRIVATE objects in a PUBLIC namelist.  */
10226   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
10227     {
10228       for (nl = sym->namelist; nl; nl = nl->next)
10229         {
10230           if (!nl->sym->attr.use_assoc
10231               && !is_sym_host_assoc (nl->sym, sym->ns)
10232               && !gfc_check_access(nl->sym->attr.access,
10233                                 nl->sym->ns->default_access))
10234             {
10235               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
10236                          "cannot be member of PUBLIC namelist '%s' at %L",
10237                          nl->sym->name, sym->name, &sym->declared_at);
10238               return FAILURE;
10239             }
10240
10241           /* Types with private components that came here by USE-association.  */
10242           if (nl->sym->ts.type == BT_DERIVED
10243               && derived_inaccessible (nl->sym->ts.u.derived))
10244             {
10245               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
10246                          "components and cannot be member of namelist '%s' at %L",
10247                          nl->sym->name, sym->name, &sym->declared_at);
10248               return FAILURE;
10249             }
10250
10251           /* Types with private components that are defined in the same module.  */
10252           if (nl->sym->ts.type == BT_DERIVED
10253               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
10254               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
10255                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
10256                                         nl->sym->ns->default_access))
10257             {
10258               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
10259                          "cannot be a member of PUBLIC namelist '%s' at %L",
10260                          nl->sym->name, sym->name, &sym->declared_at);
10261               return FAILURE;
10262             }
10263         }
10264     }
10265
10266   for (nl = sym->namelist; nl; nl = nl->next)
10267     {
10268       /* Reject namelist arrays of assumed shape.  */
10269       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
10270           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
10271                              "must not have assumed shape in namelist "
10272                              "'%s' at %L", nl->sym->name, sym->name,
10273                              &sym->declared_at) == FAILURE)
10274             return FAILURE;
10275
10276       /* Reject namelist arrays that are not constant shape.  */
10277       if (is_non_constant_shape_array (nl->sym))
10278         {
10279           gfc_error ("NAMELIST array object '%s' must have constant "
10280                      "shape in namelist '%s' at %L", nl->sym->name,
10281                      sym->name, &sym->declared_at);
10282           return FAILURE;
10283         }
10284
10285       /* Namelist objects cannot have allocatable or pointer components.  */
10286       if (nl->sym->ts.type != BT_DERIVED)
10287         continue;
10288
10289       if (nl->sym->ts.u.derived->attr.alloc_comp)
10290         {
10291           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10292                      "have ALLOCATABLE components",
10293                      nl->sym->name, sym->name, &sym->declared_at);
10294           return FAILURE;
10295         }
10296
10297       if (nl->sym->ts.u.derived->attr.pointer_comp)
10298         {
10299           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10300                      "have POINTER components", 
10301                      nl->sym->name, sym->name, &sym->declared_at);
10302           return FAILURE;
10303         }
10304     }
10305
10306
10307   /* 14.1.2 A module or internal procedure represent local entities
10308      of the same type as a namelist member and so are not allowed.  */
10309   for (nl = sym->namelist; nl; nl = nl->next)
10310     {
10311       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
10312         continue;
10313
10314       if (nl->sym->attr.function && nl->sym == nl->sym->result)
10315         if ((nl->sym == sym->ns->proc_name)
10316                ||
10317             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
10318           continue;
10319
10320       nlsym = NULL;
10321       if (nl->sym && nl->sym->name)
10322         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
10323       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
10324         {
10325           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
10326                      "attribute in '%s' at %L", nlsym->name,
10327                      &sym->declared_at);
10328           return FAILURE;
10329         }
10330     }
10331
10332   return SUCCESS;
10333 }
10334
10335
10336 static gfc_try
10337 resolve_fl_parameter (gfc_symbol *sym)
10338 {
10339   /* A parameter array's shape needs to be constant.  */
10340   if (sym->as != NULL 
10341       && (sym->as->type == AS_DEFERRED
10342           || is_non_constant_shape_array (sym)))
10343     {
10344       gfc_error ("Parameter array '%s' at %L cannot be automatic "
10345                  "or of deferred shape", sym->name, &sym->declared_at);
10346       return FAILURE;
10347     }
10348
10349   /* Make sure a parameter that has been implicitly typed still
10350      matches the implicit type, since PARAMETER statements can precede
10351      IMPLICIT statements.  */
10352   if (sym->attr.implicit_type
10353       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
10354                                                              sym->ns)))
10355     {
10356       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
10357                  "later IMPLICIT type", sym->name, &sym->declared_at);
10358       return FAILURE;
10359     }
10360
10361   /* Make sure the types of derived parameters are consistent.  This
10362      type checking is deferred until resolution because the type may
10363      refer to a derived type from the host.  */
10364   if (sym->ts.type == BT_DERIVED
10365       && !gfc_compare_types (&sym->ts, &sym->value->ts))
10366     {
10367       gfc_error ("Incompatible derived type in PARAMETER at %L",
10368                  &sym->value->where);
10369       return FAILURE;
10370     }
10371   return SUCCESS;
10372 }
10373
10374
10375 /* Do anything necessary to resolve a symbol.  Right now, we just
10376    assume that an otherwise unknown symbol is a variable.  This sort
10377    of thing commonly happens for symbols in module.  */
10378
10379 static void
10380 resolve_symbol (gfc_symbol *sym)
10381 {
10382   int check_constant, mp_flag;
10383   gfc_symtree *symtree;
10384   gfc_symtree *this_symtree;
10385   gfc_namespace *ns;
10386   gfc_component *c;
10387
10388   if (sym->attr.flavor == FL_UNKNOWN)
10389     {
10390
10391     /* If we find that a flavorless symbol is an interface in one of the
10392        parent namespaces, find its symtree in this namespace, free the
10393        symbol and set the symtree to point to the interface symbol.  */
10394       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
10395         {
10396           symtree = gfc_find_symtree (ns->sym_root, sym->name);
10397           if (symtree && symtree->n.sym->generic)
10398             {
10399               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
10400                                                sym->name);
10401               sym->refs--;
10402               if (!sym->refs)
10403                 gfc_free_symbol (sym);
10404               symtree->n.sym->refs++;
10405               this_symtree->n.sym = symtree->n.sym;
10406               return;
10407             }
10408         }
10409
10410       /* Otherwise give it a flavor according to such attributes as
10411          it has.  */
10412       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
10413         sym->attr.flavor = FL_VARIABLE;
10414       else
10415         {
10416           sym->attr.flavor = FL_PROCEDURE;
10417           if (sym->attr.dimension)
10418             sym->attr.function = 1;
10419         }
10420     }
10421
10422   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
10423     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
10424
10425   if (sym->attr.procedure && sym->ts.interface
10426       && sym->attr.if_source != IFSRC_DECL)
10427     {
10428       if (sym->ts.interface == sym)
10429         {
10430           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
10431                      "interface", sym->name, &sym->declared_at);
10432           return;
10433         }
10434       if (sym->ts.interface->attr.procedure)
10435         {
10436           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
10437                      " in a later PROCEDURE statement", sym->ts.interface->name,
10438                      sym->name,&sym->declared_at);
10439           return;
10440         }
10441
10442       /* Get the attributes from the interface (now resolved).  */
10443       if (sym->ts.interface->attr.if_source
10444           || sym->ts.interface->attr.intrinsic)
10445         {
10446           gfc_symbol *ifc = sym->ts.interface;
10447           resolve_symbol (ifc);
10448
10449           if (ifc->attr.intrinsic)
10450             resolve_intrinsic (ifc, &ifc->declared_at);
10451
10452           if (ifc->result)
10453             sym->ts = ifc->result->ts;
10454           else   
10455             sym->ts = ifc->ts;
10456           sym->ts.interface = ifc;
10457           sym->attr.function = ifc->attr.function;
10458           sym->attr.subroutine = ifc->attr.subroutine;
10459           gfc_copy_formal_args (sym, ifc);
10460
10461           sym->attr.allocatable = ifc->attr.allocatable;
10462           sym->attr.pointer = ifc->attr.pointer;
10463           sym->attr.pure = ifc->attr.pure;
10464           sym->attr.elemental = ifc->attr.elemental;
10465           sym->attr.dimension = ifc->attr.dimension;
10466           sym->attr.recursive = ifc->attr.recursive;
10467           sym->attr.always_explicit = ifc->attr.always_explicit;
10468           sym->attr.ext_attr |= ifc->attr.ext_attr;
10469           /* Copy array spec.  */
10470           sym->as = gfc_copy_array_spec (ifc->as);
10471           if (sym->as)
10472             {
10473               int i;
10474               for (i = 0; i < sym->as->rank; i++)
10475                 {
10476                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
10477                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
10478                 }
10479             }
10480           /* Copy char length.  */
10481           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10482             {
10483               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10484               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
10485             }
10486         }
10487       else if (sym->ts.interface->name[0] != '\0')
10488         {
10489           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
10490                     sym->ts.interface->name, sym->name, &sym->declared_at);
10491           return;
10492         }
10493     }
10494
10495   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
10496     return;
10497
10498   /* Symbols that are module procedures with results (functions) have
10499      the types and array specification copied for type checking in
10500      procedures that call them, as well as for saving to a module
10501      file.  These symbols can't stand the scrutiny that their results
10502      can.  */
10503   mp_flag = (sym->result != NULL && sym->result != sym);
10504
10505
10506   /* Make sure that the intrinsic is consistent with its internal 
10507      representation. This needs to be done before assigning a default 
10508      type to avoid spurious warnings.  */
10509   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
10510       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
10511     return;
10512
10513   /* Assign default type to symbols that need one and don't have one.  */
10514   if (sym->ts.type == BT_UNKNOWN)
10515     {
10516       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
10517         gfc_set_default_type (sym, 1, NULL);
10518
10519       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
10520           && !sym->attr.function && !sym->attr.subroutine
10521           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
10522         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
10523
10524       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
10525         {
10526           /* The specific case of an external procedure should emit an error
10527              in the case that there is no implicit type.  */
10528           if (!mp_flag)
10529             gfc_set_default_type (sym, sym->attr.external, NULL);
10530           else
10531             {
10532               /* Result may be in another namespace.  */
10533               resolve_symbol (sym->result);
10534
10535               if (!sym->result->attr.proc_pointer)
10536                 {
10537                   sym->ts = sym->result->ts;
10538                   sym->as = gfc_copy_array_spec (sym->result->as);
10539                   sym->attr.dimension = sym->result->attr.dimension;
10540                   sym->attr.pointer = sym->result->attr.pointer;
10541                   sym->attr.allocatable = sym->result->attr.allocatable;
10542                 }
10543             }
10544         }
10545     }
10546
10547   /* Assumed size arrays and assumed shape arrays must be dummy
10548      arguments.  */
10549
10550   if (sym->as != NULL
10551       && (sym->as->type == AS_ASSUMED_SIZE
10552           || sym->as->type == AS_ASSUMED_SHAPE)
10553       && sym->attr.dummy == 0)
10554     {
10555       if (sym->as->type == AS_ASSUMED_SIZE)
10556         gfc_error ("Assumed size array at %L must be a dummy argument",
10557                    &sym->declared_at);
10558       else
10559         gfc_error ("Assumed shape array at %L must be a dummy argument",
10560                    &sym->declared_at);
10561       return;
10562     }
10563
10564   /* Make sure symbols with known intent or optional are really dummy
10565      variable.  Because of ENTRY statement, this has to be deferred
10566      until resolution time.  */
10567
10568   if (!sym->attr.dummy
10569       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
10570     {
10571       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
10572       return;
10573     }
10574
10575   if (sym->attr.value && !sym->attr.dummy)
10576     {
10577       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
10578                  "it is not a dummy argument", sym->name, &sym->declared_at);
10579       return;
10580     }
10581
10582   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
10583     {
10584       gfc_charlen *cl = sym->ts.u.cl;
10585       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10586         {
10587           gfc_error ("Character dummy variable '%s' at %L with VALUE "
10588                      "attribute must have constant length",
10589                      sym->name, &sym->declared_at);
10590           return;
10591         }
10592
10593       if (sym->ts.is_c_interop
10594           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
10595         {
10596           gfc_error ("C interoperable character dummy variable '%s' at %L "
10597                      "with VALUE attribute must have length one",
10598                      sym->name, &sym->declared_at);
10599           return;
10600         }
10601     }
10602
10603   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
10604      do this for something that was implicitly typed because that is handled
10605      in gfc_set_default_type.  Handle dummy arguments and procedure
10606      definitions separately.  Also, anything that is use associated is not
10607      handled here but instead is handled in the module it is declared in.
10608      Finally, derived type definitions are allowed to be BIND(C) since that
10609      only implies that they're interoperable, and they are checked fully for
10610      interoperability when a variable is declared of that type.  */
10611   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
10612       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
10613       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
10614     {
10615       gfc_try t = SUCCESS;
10616       
10617       /* First, make sure the variable is declared at the
10618          module-level scope (J3/04-007, Section 15.3).  */
10619       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
10620           sym->attr.in_common == 0)
10621         {
10622           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
10623                      "is neither a COMMON block nor declared at the "
10624                      "module level scope", sym->name, &(sym->declared_at));
10625           t = FAILURE;
10626         }
10627       else if (sym->common_head != NULL)
10628         {
10629           t = verify_com_block_vars_c_interop (sym->common_head);
10630         }
10631       else
10632         {
10633           /* If type() declaration, we need to verify that the components
10634              of the given type are all C interoperable, etc.  */
10635           if (sym->ts.type == BT_DERIVED &&
10636               sym->ts.u.derived->attr.is_c_interop != 1)
10637             {
10638               /* Make sure the user marked the derived type as BIND(C).  If
10639                  not, call the verify routine.  This could print an error
10640                  for the derived type more than once if multiple variables
10641                  of that type are declared.  */
10642               if (sym->ts.u.derived->attr.is_bind_c != 1)
10643                 verify_bind_c_derived_type (sym->ts.u.derived);
10644               t = FAILURE;
10645             }
10646           
10647           /* Verify the variable itself as C interoperable if it
10648              is BIND(C).  It is not possible for this to succeed if
10649              the verify_bind_c_derived_type failed, so don't have to handle
10650              any error returned by verify_bind_c_derived_type.  */
10651           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10652                                  sym->common_block);
10653         }
10654
10655       if (t == FAILURE)
10656         {
10657           /* clear the is_bind_c flag to prevent reporting errors more than
10658              once if something failed.  */
10659           sym->attr.is_bind_c = 0;
10660           return;
10661         }
10662     }
10663
10664   /* If a derived type symbol has reached this point, without its
10665      type being declared, we have an error.  Notice that most
10666      conditions that produce undefined derived types have already
10667      been dealt with.  However, the likes of:
10668      implicit type(t) (t) ..... call foo (t) will get us here if
10669      the type is not declared in the scope of the implicit
10670      statement. Change the type to BT_UNKNOWN, both because it is so
10671      and to prevent an ICE.  */
10672   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
10673       && !sym->ts.u.derived->attr.zero_comp)
10674     {
10675       gfc_error ("The derived type '%s' at %L is of type '%s', "
10676                  "which has not been defined", sym->name,
10677                   &sym->declared_at, sym->ts.u.derived->name);
10678       sym->ts.type = BT_UNKNOWN;
10679       return;
10680     }
10681
10682   /* Make sure that the derived type has been resolved and that the
10683      derived type is visible in the symbol's namespace, if it is a
10684      module function and is not PRIVATE.  */
10685   if (sym->ts.type == BT_DERIVED
10686         && sym->ts.u.derived->attr.use_assoc
10687         && sym->ns->proc_name
10688         && sym->ns->proc_name->attr.flavor == FL_MODULE)
10689     {
10690       gfc_symbol *ds;
10691
10692       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
10693         return;
10694
10695       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
10696       if (!ds && sym->attr.function
10697             && gfc_check_access (sym->attr.access, sym->ns->default_access))
10698         {
10699           symtree = gfc_new_symtree (&sym->ns->sym_root,
10700                                      sym->ts.u.derived->name);
10701           symtree->n.sym = sym->ts.u.derived;
10702           sym->ts.u.derived->refs++;
10703         }
10704     }
10705
10706   /* Unless the derived-type declaration is use associated, Fortran 95
10707      does not allow public entries of private derived types.
10708      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
10709      161 in 95-006r3.  */
10710   if (sym->ts.type == BT_DERIVED
10711       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
10712       && !sym->ts.u.derived->attr.use_assoc
10713       && gfc_check_access (sym->attr.access, sym->ns->default_access)
10714       && !gfc_check_access (sym->ts.u.derived->attr.access,
10715                             sym->ts.u.derived->ns->default_access)
10716       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
10717                          "of PRIVATE derived type '%s'",
10718                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
10719                          : "variable", sym->name, &sym->declared_at,
10720                          sym->ts.u.derived->name) == FAILURE)
10721     return;
10722
10723   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
10724      default initialization is defined (5.1.2.4.4).  */
10725   if (sym->ts.type == BT_DERIVED
10726       && sym->attr.dummy
10727       && sym->attr.intent == INTENT_OUT
10728       && sym->as
10729       && sym->as->type == AS_ASSUMED_SIZE)
10730     {
10731       for (c = sym->ts.u.derived->components; c; c = c->next)
10732         {
10733           if (c->initializer)
10734             {
10735               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
10736                          "ASSUMED SIZE and so cannot have a default initializer",
10737                          sym->name, &sym->declared_at);
10738               return;
10739             }
10740         }
10741     }
10742
10743   switch (sym->attr.flavor)
10744     {
10745     case FL_VARIABLE:
10746       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
10747         return;
10748       break;
10749
10750     case FL_PROCEDURE:
10751       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
10752         return;
10753       break;
10754
10755     case FL_NAMELIST:
10756       if (resolve_fl_namelist (sym) == FAILURE)
10757         return;
10758       break;
10759
10760     case FL_PARAMETER:
10761       if (resolve_fl_parameter (sym) == FAILURE)
10762         return;
10763       break;
10764
10765     default:
10766       break;
10767     }
10768
10769   /* Resolve array specifier. Check as well some constraints
10770      on COMMON blocks.  */
10771
10772   check_constant = sym->attr.in_common && !sym->attr.pointer;
10773
10774   /* Set the formal_arg_flag so that check_conflict will not throw
10775      an error for host associated variables in the specification
10776      expression for an array_valued function.  */
10777   if (sym->attr.function && sym->as)
10778     formal_arg_flag = 1;
10779
10780   gfc_resolve_array_spec (sym->as, check_constant);
10781
10782   formal_arg_flag = 0;
10783
10784   /* Resolve formal namespaces.  */
10785   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
10786       && !sym->attr.contained && !sym->attr.intrinsic)
10787     gfc_resolve (sym->formal_ns);
10788
10789   /* Make sure the formal namespace is present.  */
10790   if (sym->formal && !sym->formal_ns)
10791     {
10792       gfc_formal_arglist *formal = sym->formal;
10793       while (formal && !formal->sym)
10794         formal = formal->next;
10795
10796       if (formal)
10797         {
10798           sym->formal_ns = formal->sym->ns;
10799           sym->formal_ns->refs++;
10800         }
10801     }
10802
10803   /* Check threadprivate restrictions.  */
10804   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
10805       && (!sym->attr.in_common
10806           && sym->module == NULL
10807           && (sym->ns->proc_name == NULL
10808               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
10809     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
10810
10811   /* If we have come this far we can apply default-initializers, as
10812      described in 14.7.5, to those variables that have not already
10813      been assigned one.  */
10814   if (sym->ts.type == BT_DERIVED
10815       && sym->attr.referenced
10816       && sym->ns == gfc_current_ns
10817       && !sym->value
10818       && !sym->attr.allocatable
10819       && !sym->attr.alloc_comp)
10820     {
10821       symbol_attribute *a = &sym->attr;
10822
10823       if ((!a->save && !a->dummy && !a->pointer
10824            && !a->in_common && !a->use_assoc
10825            && !(a->function && sym != sym->result))
10826           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
10827         apply_default_init (sym);
10828     }
10829
10830   /* If this symbol has a type-spec, check it.  */
10831   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
10832       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
10833     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
10834           == FAILURE)
10835       return;
10836 }
10837
10838
10839 /************* Resolve DATA statements *************/
10840
10841 static struct
10842 {
10843   gfc_data_value *vnode;
10844   mpz_t left;
10845 }
10846 values;
10847
10848
10849 /* Advance the values structure to point to the next value in the data list.  */
10850
10851 static gfc_try
10852 next_data_value (void)
10853 {
10854   while (mpz_cmp_ui (values.left, 0) == 0)
10855     {
10856       if (!gfc_is_constant_expr (values.vnode->expr))
10857         gfc_error ("non-constant DATA value at %L",
10858                    &values.vnode->expr->where);
10859
10860       if (values.vnode->next == NULL)
10861         return FAILURE;
10862
10863       values.vnode = values.vnode->next;
10864       mpz_set (values.left, values.vnode->repeat);
10865     }
10866
10867   return SUCCESS;
10868 }
10869
10870
10871 static gfc_try
10872 check_data_variable (gfc_data_variable *var, locus *where)
10873 {
10874   gfc_expr *e;
10875   mpz_t size;
10876   mpz_t offset;
10877   gfc_try t;
10878   ar_type mark = AR_UNKNOWN;
10879   int i;
10880   mpz_t section_index[GFC_MAX_DIMENSIONS];
10881   gfc_ref *ref;
10882   gfc_array_ref *ar;
10883   gfc_symbol *sym;
10884   int has_pointer;
10885
10886   if (gfc_resolve_expr (var->expr) == FAILURE)
10887     return FAILURE;
10888
10889   ar = NULL;
10890   mpz_init_set_si (offset, 0);
10891   e = var->expr;
10892
10893   if (e->expr_type != EXPR_VARIABLE)
10894     gfc_internal_error ("check_data_variable(): Bad expression");
10895
10896   sym = e->symtree->n.sym;
10897
10898   if (sym->ns->is_block_data && !sym->attr.in_common)
10899     {
10900       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
10901                  sym->name, &sym->declared_at);
10902     }
10903
10904   if (e->ref == NULL && sym->as)
10905     {
10906       gfc_error ("DATA array '%s' at %L must be specified in a previous"
10907                  " declaration", sym->name, where);
10908       return FAILURE;
10909     }
10910
10911   has_pointer = sym->attr.pointer;
10912
10913   for (ref = e->ref; ref; ref = ref->next)
10914     {
10915       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
10916         has_pointer = 1;
10917
10918       if (has_pointer
10919             && ref->type == REF_ARRAY
10920             && ref->u.ar.type != AR_FULL)
10921           {
10922             gfc_error ("DATA element '%s' at %L is a pointer and so must "
10923                         "be a full array", sym->name, where);
10924             return FAILURE;
10925           }
10926     }
10927
10928   if (e->rank == 0 || has_pointer)
10929     {
10930       mpz_init_set_ui (size, 1);
10931       ref = NULL;
10932     }
10933   else
10934     {
10935       ref = e->ref;
10936
10937       /* Find the array section reference.  */
10938       for (ref = e->ref; ref; ref = ref->next)
10939         {
10940           if (ref->type != REF_ARRAY)
10941             continue;
10942           if (ref->u.ar.type == AR_ELEMENT)
10943             continue;
10944           break;
10945         }
10946       gcc_assert (ref);
10947
10948       /* Set marks according to the reference pattern.  */
10949       switch (ref->u.ar.type)
10950         {
10951         case AR_FULL:
10952           mark = AR_FULL;
10953           break;
10954
10955         case AR_SECTION:
10956           ar = &ref->u.ar;
10957           /* Get the start position of array section.  */
10958           gfc_get_section_index (ar, section_index, &offset);
10959           mark = AR_SECTION;
10960           break;
10961
10962         default:
10963           gcc_unreachable ();
10964         }
10965
10966       if (gfc_array_size (e, &size) == FAILURE)
10967         {
10968           gfc_error ("Nonconstant array section at %L in DATA statement",
10969                      &e->where);
10970           mpz_clear (offset);
10971           return FAILURE;
10972         }
10973     }
10974
10975   t = SUCCESS;
10976
10977   while (mpz_cmp_ui (size, 0) > 0)
10978     {
10979       if (next_data_value () == FAILURE)
10980         {
10981           gfc_error ("DATA statement at %L has more variables than values",
10982                      where);
10983           t = FAILURE;
10984           break;
10985         }
10986
10987       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
10988       if (t == FAILURE)
10989         break;
10990
10991       /* If we have more than one element left in the repeat count,
10992          and we have more than one element left in the target variable,
10993          then create a range assignment.  */
10994       /* FIXME: Only done for full arrays for now, since array sections
10995          seem tricky.  */
10996       if (mark == AR_FULL && ref && ref->next == NULL
10997           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
10998         {
10999           mpz_t range;
11000
11001           if (mpz_cmp (size, values.left) >= 0)
11002             {
11003               mpz_init_set (range, values.left);
11004               mpz_sub (size, size, values.left);
11005               mpz_set_ui (values.left, 0);
11006             }
11007           else
11008             {
11009               mpz_init_set (range, size);
11010               mpz_sub (values.left, values.left, size);
11011               mpz_set_ui (size, 0);
11012             }
11013
11014           gfc_assign_data_value_range (var->expr, values.vnode->expr,
11015                                        offset, range);
11016
11017           mpz_add (offset, offset, range);
11018           mpz_clear (range);
11019         }
11020
11021       /* Assign initial value to symbol.  */
11022       else
11023         {
11024           mpz_sub_ui (values.left, values.left, 1);
11025           mpz_sub_ui (size, size, 1);
11026
11027           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11028           if (t == FAILURE)
11029             break;
11030
11031           if (mark == AR_FULL)
11032             mpz_add_ui (offset, offset, 1);
11033
11034           /* Modify the array section indexes and recalculate the offset
11035              for next element.  */
11036           else if (mark == AR_SECTION)
11037             gfc_advance_section (section_index, ar, &offset);
11038         }
11039     }
11040
11041   if (mark == AR_SECTION)
11042     {
11043       for (i = 0; i < ar->dimen; i++)
11044         mpz_clear (section_index[i]);
11045     }
11046
11047   mpz_clear (size);
11048   mpz_clear (offset);
11049
11050   return t;
11051 }
11052
11053
11054 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11055
11056 /* Iterate over a list of elements in a DATA statement.  */
11057
11058 static gfc_try
11059 traverse_data_list (gfc_data_variable *var, locus *where)
11060 {
11061   mpz_t trip;
11062   iterator_stack frame;
11063   gfc_expr *e, *start, *end, *step;
11064   gfc_try retval = SUCCESS;
11065
11066   mpz_init (frame.value);
11067
11068   start = gfc_copy_expr (var->iter.start);
11069   end = gfc_copy_expr (var->iter.end);
11070   step = gfc_copy_expr (var->iter.step);
11071
11072   if (gfc_simplify_expr (start, 1) == FAILURE
11073       || start->expr_type != EXPR_CONSTANT)
11074     {
11075       gfc_error ("iterator start at %L does not simplify", &start->where);
11076       retval = FAILURE;
11077       goto cleanup;
11078     }
11079   if (gfc_simplify_expr (end, 1) == FAILURE
11080       || end->expr_type != EXPR_CONSTANT)
11081     {
11082       gfc_error ("iterator end at %L does not simplify", &end->where);
11083       retval = FAILURE;
11084       goto cleanup;
11085     }
11086   if (gfc_simplify_expr (step, 1) == FAILURE
11087       || step->expr_type != EXPR_CONSTANT)
11088     {
11089       gfc_error ("iterator step at %L does not simplify", &step->where);
11090       retval = FAILURE;
11091       goto cleanup;
11092     }
11093
11094   mpz_init_set (trip, end->value.integer);
11095   mpz_sub (trip, trip, start->value.integer);
11096   mpz_add (trip, trip, step->value.integer);
11097
11098   mpz_div (trip, trip, step->value.integer);
11099
11100   mpz_set (frame.value, start->value.integer);
11101
11102   frame.prev = iter_stack;
11103   frame.variable = var->iter.var->symtree;
11104   iter_stack = &frame;
11105
11106   while (mpz_cmp_ui (trip, 0) > 0)
11107     {
11108       if (traverse_data_var (var->list, where) == FAILURE)
11109         {
11110           mpz_clear (trip);
11111           retval = FAILURE;
11112           goto cleanup;
11113         }
11114
11115       e = gfc_copy_expr (var->expr);
11116       if (gfc_simplify_expr (e, 1) == FAILURE)
11117         {
11118           gfc_free_expr (e);
11119           mpz_clear (trip);
11120           retval = FAILURE;
11121           goto cleanup;
11122         }
11123
11124       mpz_add (frame.value, frame.value, step->value.integer);
11125
11126       mpz_sub_ui (trip, trip, 1);
11127     }
11128
11129   mpz_clear (trip);
11130 cleanup:
11131   mpz_clear (frame.value);
11132
11133   gfc_free_expr (start);
11134   gfc_free_expr (end);
11135   gfc_free_expr (step);
11136
11137   iter_stack = frame.prev;
11138   return retval;
11139 }
11140
11141
11142 /* Type resolve variables in the variable list of a DATA statement.  */
11143
11144 static gfc_try
11145 traverse_data_var (gfc_data_variable *var, locus *where)
11146 {
11147   gfc_try t;
11148
11149   for (; var; var = var->next)
11150     {
11151       if (var->expr == NULL)
11152         t = traverse_data_list (var, where);
11153       else
11154         t = check_data_variable (var, where);
11155
11156       if (t == FAILURE)
11157         return FAILURE;
11158     }
11159
11160   return SUCCESS;
11161 }
11162
11163
11164 /* Resolve the expressions and iterators associated with a data statement.
11165    This is separate from the assignment checking because data lists should
11166    only be resolved once.  */
11167
11168 static gfc_try
11169 resolve_data_variables (gfc_data_variable *d)
11170 {
11171   for (; d; d = d->next)
11172     {
11173       if (d->list == NULL)
11174         {
11175           if (gfc_resolve_expr (d->expr) == FAILURE)
11176             return FAILURE;
11177         }
11178       else
11179         {
11180           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
11181             return FAILURE;
11182
11183           if (resolve_data_variables (d->list) == FAILURE)
11184             return FAILURE;
11185         }
11186     }
11187
11188   return SUCCESS;
11189 }
11190
11191
11192 /* Resolve a single DATA statement.  We implement this by storing a pointer to
11193    the value list into static variables, and then recursively traversing the
11194    variables list, expanding iterators and such.  */
11195
11196 static void
11197 resolve_data (gfc_data *d)
11198 {
11199
11200   if (resolve_data_variables (d->var) == FAILURE)
11201     return;
11202
11203   values.vnode = d->value;
11204   if (d->value == NULL)
11205     mpz_set_ui (values.left, 0);
11206   else
11207     mpz_set (values.left, d->value->repeat);
11208
11209   if (traverse_data_var (d->var, &d->where) == FAILURE)
11210     return;
11211
11212   /* At this point, we better not have any values left.  */
11213
11214   if (next_data_value () == SUCCESS)
11215     gfc_error ("DATA statement at %L has more values than variables",
11216                &d->where);
11217 }
11218
11219
11220 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
11221    accessed by host or use association, is a dummy argument to a pure function,
11222    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
11223    is storage associated with any such variable, shall not be used in the
11224    following contexts: (clients of this function).  */
11225
11226 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
11227    procedure.  Returns zero if assignment is OK, nonzero if there is a
11228    problem.  */
11229 int
11230 gfc_impure_variable (gfc_symbol *sym)
11231 {
11232   gfc_symbol *proc;
11233
11234   if (sym->attr.use_assoc || sym->attr.in_common)
11235     return 1;
11236
11237   if (sym->ns != gfc_current_ns)
11238     return !sym->attr.function;
11239
11240   proc = sym->ns->proc_name;
11241   if (sym->attr.dummy && gfc_pure (proc)
11242         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
11243                 ||
11244              proc->attr.function))
11245     return 1;
11246
11247   /* TODO: Sort out what can be storage associated, if anything, and include
11248      it here.  In principle equivalences should be scanned but it does not
11249      seem to be possible to storage associate an impure variable this way.  */
11250   return 0;
11251 }
11252
11253
11254 /* Test whether a symbol is pure or not.  For a NULL pointer, checks the
11255    symbol of the current procedure.  */
11256
11257 int
11258 gfc_pure (gfc_symbol *sym)
11259 {
11260   symbol_attribute attr;
11261
11262   if (sym == NULL)
11263     sym = gfc_current_ns->proc_name;
11264   if (sym == NULL)
11265     return 0;
11266
11267   attr = sym->attr;
11268
11269   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
11270 }
11271
11272
11273 /* Test whether the current procedure is elemental or not.  */
11274
11275 int
11276 gfc_elemental (gfc_symbol *sym)
11277 {
11278   symbol_attribute attr;
11279
11280   if (sym == NULL)
11281     sym = gfc_current_ns->proc_name;
11282   if (sym == NULL)
11283     return 0;
11284   attr = sym->attr;
11285
11286   return attr.flavor == FL_PROCEDURE && attr.elemental;
11287 }
11288
11289
11290 /* Warn about unused labels.  */
11291
11292 static void
11293 warn_unused_fortran_label (gfc_st_label *label)
11294 {
11295   if (label == NULL)
11296     return;
11297
11298   warn_unused_fortran_label (label->left);
11299
11300   if (label->defined == ST_LABEL_UNKNOWN)
11301     return;
11302
11303   switch (label->referenced)
11304     {
11305     case ST_LABEL_UNKNOWN:
11306       gfc_warning ("Label %d at %L defined but not used", label->value,
11307                    &label->where);
11308       break;
11309
11310     case ST_LABEL_BAD_TARGET:
11311       gfc_warning ("Label %d at %L defined but cannot be used",
11312                    label->value, &label->where);
11313       break;
11314
11315     default:
11316       break;
11317     }
11318
11319   warn_unused_fortran_label (label->right);
11320 }
11321
11322
11323 /* Returns the sequence type of a symbol or sequence.  */
11324
11325 static seq_type
11326 sequence_type (gfc_typespec ts)
11327 {
11328   seq_type result;
11329   gfc_component *c;
11330
11331   switch (ts.type)
11332   {
11333     case BT_DERIVED:
11334
11335       if (ts.u.derived->components == NULL)
11336         return SEQ_NONDEFAULT;
11337
11338       result = sequence_type (ts.u.derived->components->ts);
11339       for (c = ts.u.derived->components->next; c; c = c->next)
11340         if (sequence_type (c->ts) != result)
11341           return SEQ_MIXED;
11342
11343       return result;
11344
11345     case BT_CHARACTER:
11346       if (ts.kind != gfc_default_character_kind)
11347           return SEQ_NONDEFAULT;
11348
11349       return SEQ_CHARACTER;
11350
11351     case BT_INTEGER:
11352       if (ts.kind != gfc_default_integer_kind)
11353           return SEQ_NONDEFAULT;
11354
11355       return SEQ_NUMERIC;
11356
11357     case BT_REAL:
11358       if (!(ts.kind == gfc_default_real_kind
11359             || ts.kind == gfc_default_double_kind))
11360           return SEQ_NONDEFAULT;
11361
11362       return SEQ_NUMERIC;
11363
11364     case BT_COMPLEX:
11365       if (ts.kind != gfc_default_complex_kind)
11366           return SEQ_NONDEFAULT;
11367
11368       return SEQ_NUMERIC;
11369
11370     case BT_LOGICAL:
11371       if (ts.kind != gfc_default_logical_kind)
11372           return SEQ_NONDEFAULT;
11373
11374       return SEQ_NUMERIC;
11375
11376     default:
11377       return SEQ_NONDEFAULT;
11378   }
11379 }
11380
11381
11382 /* Resolve derived type EQUIVALENCE object.  */
11383
11384 static gfc_try
11385 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
11386 {
11387   gfc_component *c = derived->components;
11388
11389   if (!derived)
11390     return SUCCESS;
11391
11392   /* Shall not be an object of nonsequence derived type.  */
11393   if (!derived->attr.sequence)
11394     {
11395       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
11396                  "attribute to be an EQUIVALENCE object", sym->name,
11397                  &e->where);
11398       return FAILURE;
11399     }
11400
11401   /* Shall not have allocatable components.  */
11402   if (derived->attr.alloc_comp)
11403     {
11404       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
11405                  "components to be an EQUIVALENCE object",sym->name,
11406                  &e->where);
11407       return FAILURE;
11408     }
11409
11410   if (sym->attr.in_common && has_default_initializer (sym->ts.u.derived))
11411     {
11412       gfc_error ("Derived type variable '%s' at %L with default "
11413                  "initialization cannot be in EQUIVALENCE with a variable "
11414                  "in COMMON", sym->name, &e->where);
11415       return FAILURE;
11416     }
11417
11418   for (; c ; c = c->next)
11419     {
11420       if (c->ts.type == BT_DERIVED
11421           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
11422         return FAILURE;
11423
11424       /* Shall not be an object of sequence derived type containing a pointer
11425          in the structure.  */
11426       if (c->attr.pointer)
11427         {
11428           gfc_error ("Derived type variable '%s' at %L with pointer "
11429                      "component(s) cannot be an EQUIVALENCE object",
11430                      sym->name, &e->where);
11431           return FAILURE;
11432         }
11433     }
11434   return SUCCESS;
11435 }
11436
11437
11438 /* Resolve equivalence object. 
11439    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
11440    an allocatable array, an object of nonsequence derived type, an object of
11441    sequence derived type containing a pointer at any level of component
11442    selection, an automatic object, a function name, an entry name, a result
11443    name, a named constant, a structure component, or a subobject of any of
11444    the preceding objects.  A substring shall not have length zero.  A
11445    derived type shall not have components with default initialization nor
11446    shall two objects of an equivalence group be initialized.
11447    Either all or none of the objects shall have an protected attribute.
11448    The simple constraints are done in symbol.c(check_conflict) and the rest
11449    are implemented here.  */
11450
11451 static void
11452 resolve_equivalence (gfc_equiv *eq)
11453 {
11454   gfc_symbol *sym;
11455   gfc_symbol *first_sym;
11456   gfc_expr *e;
11457   gfc_ref *r;
11458   locus *last_where = NULL;
11459   seq_type eq_type, last_eq_type;
11460   gfc_typespec *last_ts;
11461   int object, cnt_protected;
11462   const char *value_name;
11463   const char *msg;
11464
11465   value_name = NULL;
11466   last_ts = &eq->expr->symtree->n.sym->ts;
11467
11468   first_sym = eq->expr->symtree->n.sym;
11469
11470   cnt_protected = 0;
11471
11472   for (object = 1; eq; eq = eq->eq, object++)
11473     {
11474       e = eq->expr;
11475
11476       e->ts = e->symtree->n.sym->ts;
11477       /* match_varspec might not know yet if it is seeing
11478          array reference or substring reference, as it doesn't
11479          know the types.  */
11480       if (e->ref && e->ref->type == REF_ARRAY)
11481         {
11482           gfc_ref *ref = e->ref;
11483           sym = e->symtree->n.sym;
11484
11485           if (sym->attr.dimension)
11486             {
11487               ref->u.ar.as = sym->as;
11488               ref = ref->next;
11489             }
11490
11491           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
11492           if (e->ts.type == BT_CHARACTER
11493               && ref
11494               && ref->type == REF_ARRAY
11495               && ref->u.ar.dimen == 1
11496               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
11497               && ref->u.ar.stride[0] == NULL)
11498             {
11499               gfc_expr *start = ref->u.ar.start[0];
11500               gfc_expr *end = ref->u.ar.end[0];
11501               void *mem = NULL;
11502
11503               /* Optimize away the (:) reference.  */
11504               if (start == NULL && end == NULL)
11505                 {
11506                   if (e->ref == ref)
11507                     e->ref = ref->next;
11508                   else
11509                     e->ref->next = ref->next;
11510                   mem = ref;
11511                 }
11512               else
11513                 {
11514                   ref->type = REF_SUBSTRING;
11515                   if (start == NULL)
11516                     start = gfc_int_expr (1);
11517                   ref->u.ss.start = start;
11518                   if (end == NULL && e->ts.u.cl)
11519                     end = gfc_copy_expr (e->ts.u.cl->length);
11520                   ref->u.ss.end = end;
11521                   ref->u.ss.length = e->ts.u.cl;
11522                   e->ts.u.cl = NULL;
11523                 }
11524               ref = ref->next;
11525               gfc_free (mem);
11526             }
11527
11528           /* Any further ref is an error.  */
11529           if (ref)
11530             {
11531               gcc_assert (ref->type == REF_ARRAY);
11532               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
11533                          &ref->u.ar.where);
11534               continue;
11535             }
11536         }
11537
11538       if (gfc_resolve_expr (e) == FAILURE)
11539         continue;
11540
11541       sym = e->symtree->n.sym;
11542
11543       if (sym->attr.is_protected)
11544         cnt_protected++;
11545       if (cnt_protected > 0 && cnt_protected != object)
11546         {
11547               gfc_error ("Either all or none of the objects in the "
11548                          "EQUIVALENCE set at %L shall have the "
11549                          "PROTECTED attribute",
11550                          &e->where);
11551               break;
11552         }
11553
11554       /* Shall not equivalence common block variables in a PURE procedure.  */
11555       if (sym->ns->proc_name
11556           && sym->ns->proc_name->attr.pure
11557           && sym->attr.in_common)
11558         {
11559           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
11560                      "object in the pure procedure '%s'",
11561                      sym->name, &e->where, sym->ns->proc_name->name);
11562           break;
11563         }
11564
11565       /* Shall not be a named constant.  */
11566       if (e->expr_type == EXPR_CONSTANT)
11567         {
11568           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
11569                      "object", sym->name, &e->where);
11570           continue;
11571         }
11572
11573       if (e->ts.type == BT_DERIVED
11574           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
11575         continue;
11576
11577       /* Check that the types correspond correctly:
11578          Note 5.28:
11579          A numeric sequence structure may be equivalenced to another sequence
11580          structure, an object of default integer type, default real type, double
11581          precision real type, default logical type such that components of the
11582          structure ultimately only become associated to objects of the same
11583          kind. A character sequence structure may be equivalenced to an object
11584          of default character kind or another character sequence structure.
11585          Other objects may be equivalenced only to objects of the same type and
11586          kind parameters.  */
11587
11588       /* Identical types are unconditionally OK.  */
11589       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
11590         goto identical_types;
11591
11592       last_eq_type = sequence_type (*last_ts);
11593       eq_type = sequence_type (sym->ts);
11594
11595       /* Since the pair of objects is not of the same type, mixed or
11596          non-default sequences can be rejected.  */
11597
11598       msg = "Sequence %s with mixed components in EQUIVALENCE "
11599             "statement at %L with different type objects";
11600       if ((object ==2
11601            && last_eq_type == SEQ_MIXED
11602            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
11603               == FAILURE)
11604           || (eq_type == SEQ_MIXED
11605               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11606                                  &e->where) == FAILURE))
11607         continue;
11608
11609       msg = "Non-default type object or sequence %s in EQUIVALENCE "
11610             "statement at %L with objects of different type";
11611       if ((object ==2
11612            && last_eq_type == SEQ_NONDEFAULT
11613            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
11614                               last_where) == FAILURE)
11615           || (eq_type == SEQ_NONDEFAULT
11616               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11617                                  &e->where) == FAILURE))
11618         continue;
11619
11620       msg ="Non-CHARACTER object '%s' in default CHARACTER "
11621            "EQUIVALENCE statement at %L";
11622       if (last_eq_type == SEQ_CHARACTER
11623           && eq_type != SEQ_CHARACTER
11624           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11625                              &e->where) == FAILURE)
11626                 continue;
11627
11628       msg ="Non-NUMERIC object '%s' in default NUMERIC "
11629            "EQUIVALENCE statement at %L";
11630       if (last_eq_type == SEQ_NUMERIC
11631           && eq_type != SEQ_NUMERIC
11632           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
11633                              &e->where) == FAILURE)
11634                 continue;
11635
11636   identical_types:
11637       last_ts =&sym->ts;
11638       last_where = &e->where;
11639
11640       if (!e->ref)
11641         continue;
11642
11643       /* Shall not be an automatic array.  */
11644       if (e->ref->type == REF_ARRAY
11645           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
11646         {
11647           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
11648                      "an EQUIVALENCE object", sym->name, &e->where);
11649           continue;
11650         }
11651
11652       r = e->ref;
11653       while (r)
11654         {
11655           /* Shall not be a structure component.  */
11656           if (r->type == REF_COMPONENT)
11657             {
11658               gfc_error ("Structure component '%s' at %L cannot be an "
11659                          "EQUIVALENCE object",
11660                          r->u.c.component->name, &e->where);
11661               break;
11662             }
11663
11664           /* A substring shall not have length zero.  */
11665           if (r->type == REF_SUBSTRING)
11666             {
11667               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
11668                 {
11669                   gfc_error ("Substring at %L has length zero",
11670                              &r->u.ss.start->where);
11671                   break;
11672                 }
11673             }
11674           r = r->next;
11675         }
11676     }
11677 }
11678
11679
11680 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
11681
11682 static void
11683 resolve_fntype (gfc_namespace *ns)
11684 {
11685   gfc_entry_list *el;
11686   gfc_symbol *sym;
11687
11688   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
11689     return;
11690
11691   /* If there are any entries, ns->proc_name is the entry master
11692      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
11693   if (ns->entries)
11694     sym = ns->entries->sym;
11695   else
11696     sym = ns->proc_name;
11697   if (sym->result == sym
11698       && sym->ts.type == BT_UNKNOWN
11699       && gfc_set_default_type (sym, 0, NULL) == FAILURE
11700       && !sym->attr.untyped)
11701     {
11702       gfc_error ("Function '%s' at %L has no IMPLICIT type",
11703                  sym->name, &sym->declared_at);
11704       sym->attr.untyped = 1;
11705     }
11706
11707   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
11708       && !sym->attr.contained
11709       && !gfc_check_access (sym->ts.u.derived->attr.access,
11710                             sym->ts.u.derived->ns->default_access)
11711       && gfc_check_access (sym->attr.access, sym->ns->default_access))
11712     {
11713       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
11714                       "%L of PRIVATE type '%s'", sym->name,
11715                       &sym->declared_at, sym->ts.u.derived->name);
11716     }
11717
11718     if (ns->entries)
11719     for (el = ns->entries->next; el; el = el->next)
11720       {
11721         if (el->sym->result == el->sym
11722             && el->sym->ts.type == BT_UNKNOWN
11723             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
11724             && !el->sym->attr.untyped)
11725           {
11726             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
11727                        el->sym->name, &el->sym->declared_at);
11728             el->sym->attr.untyped = 1;
11729           }
11730       }
11731 }
11732
11733
11734 /* 12.3.2.1.1 Defined operators.  */
11735
11736 static gfc_try
11737 check_uop_procedure (gfc_symbol *sym, locus where)
11738 {
11739   gfc_formal_arglist *formal;
11740
11741   if (!sym->attr.function)
11742     {
11743       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
11744                  sym->name, &where);
11745       return FAILURE;
11746     }
11747
11748   if (sym->ts.type == BT_CHARACTER
11749       && !(sym->ts.u.cl && sym->ts.u.cl->length)
11750       && !(sym->result && sym->result->ts.u.cl
11751            && sym->result->ts.u.cl->length))
11752     {
11753       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
11754                  "character length", sym->name, &where);
11755       return FAILURE;
11756     }
11757
11758   formal = sym->formal;
11759   if (!formal || !formal->sym)
11760     {
11761       gfc_error ("User operator procedure '%s' at %L must have at least "
11762                  "one argument", sym->name, &where);
11763       return FAILURE;
11764     }
11765
11766   if (formal->sym->attr.intent != INTENT_IN)
11767     {
11768       gfc_error ("First argument of operator interface at %L must be "
11769                  "INTENT(IN)", &where);
11770       return FAILURE;
11771     }
11772
11773   if (formal->sym->attr.optional)
11774     {
11775       gfc_error ("First argument of operator interface at %L cannot be "
11776                  "optional", &where);
11777       return FAILURE;
11778     }
11779
11780   formal = formal->next;
11781   if (!formal || !formal->sym)
11782     return SUCCESS;
11783
11784   if (formal->sym->attr.intent != INTENT_IN)
11785     {
11786       gfc_error ("Second argument of operator interface at %L must be "
11787                  "INTENT(IN)", &where);
11788       return FAILURE;
11789     }
11790
11791   if (formal->sym->attr.optional)
11792     {
11793       gfc_error ("Second argument of operator interface at %L cannot be "
11794                  "optional", &where);
11795       return FAILURE;
11796     }
11797
11798   if (formal->next)
11799     {
11800       gfc_error ("Operator interface at %L must have, at most, two "
11801                  "arguments", &where);
11802       return FAILURE;
11803     }
11804
11805   return SUCCESS;
11806 }
11807
11808 static void
11809 gfc_resolve_uops (gfc_symtree *symtree)
11810 {
11811   gfc_interface *itr;
11812
11813   if (symtree == NULL)
11814     return;
11815
11816   gfc_resolve_uops (symtree->left);
11817   gfc_resolve_uops (symtree->right);
11818
11819   for (itr = symtree->n.uop->op; itr; itr = itr->next)
11820     check_uop_procedure (itr->sym, itr->sym->declared_at);
11821 }
11822
11823
11824 /* Examine all of the expressions associated with a program unit,
11825    assign types to all intermediate expressions, make sure that all
11826    assignments are to compatible types and figure out which names
11827    refer to which functions or subroutines.  It doesn't check code
11828    block, which is handled by resolve_code.  */
11829
11830 static void
11831 resolve_types (gfc_namespace *ns)
11832 {
11833   gfc_namespace *n;
11834   gfc_charlen *cl;
11835   gfc_data *d;
11836   gfc_equiv *eq;
11837   gfc_namespace* old_ns = gfc_current_ns;
11838
11839   /* Check that all IMPLICIT types are ok.  */
11840   if (!ns->seen_implicit_none)
11841     {
11842       unsigned letter;
11843       for (letter = 0; letter != GFC_LETTERS; ++letter)
11844         if (ns->set_flag[letter]
11845             && resolve_typespec_used (&ns->default_type[letter],
11846                                       &ns->implicit_loc[letter],
11847                                       NULL) == FAILURE)
11848           return;
11849     }
11850
11851   gfc_current_ns = ns;
11852
11853   resolve_entries (ns);
11854
11855   resolve_common_vars (ns->blank_common.head, false);
11856   resolve_common_blocks (ns->common_root);
11857
11858   resolve_contained_functions (ns);
11859
11860   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
11861
11862   for (cl = ns->cl_list; cl; cl = cl->next)
11863     resolve_charlen (cl);
11864
11865   gfc_traverse_ns (ns, resolve_symbol);
11866
11867   resolve_fntype (ns);
11868
11869   for (n = ns->contained; n; n = n->sibling)
11870     {
11871       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
11872         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
11873                    "also be PURE", n->proc_name->name,
11874                    &n->proc_name->declared_at);
11875
11876       resolve_types (n);
11877     }
11878
11879   forall_flag = 0;
11880   gfc_check_interfaces (ns);
11881
11882   gfc_traverse_ns (ns, resolve_values);
11883
11884   if (ns->save_all)
11885     gfc_save_all (ns);
11886
11887   iter_stack = NULL;
11888   for (d = ns->data; d; d = d->next)
11889     resolve_data (d);
11890
11891   iter_stack = NULL;
11892   gfc_traverse_ns (ns, gfc_formalize_init_value);
11893
11894   gfc_traverse_ns (ns, gfc_verify_binding_labels);
11895
11896   if (ns->common_root != NULL)
11897     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
11898
11899   for (eq = ns->equiv; eq; eq = eq->next)
11900     resolve_equivalence (eq);
11901
11902   /* Warn about unused labels.  */
11903   if (warn_unused_label)
11904     warn_unused_fortran_label (ns->st_labels);
11905
11906   gfc_resolve_uops (ns->uop_root);
11907
11908   gfc_current_ns = old_ns;
11909 }
11910
11911
11912 /* Call resolve_code recursively.  */
11913
11914 static void
11915 resolve_codes (gfc_namespace *ns)
11916 {
11917   gfc_namespace *n;
11918   bitmap_obstack old_obstack;
11919
11920   for (n = ns->contained; n; n = n->sibling)
11921     resolve_codes (n);
11922
11923   gfc_current_ns = ns;
11924   cs_base = NULL;
11925   /* Set to an out of range value.  */
11926   current_entry_id = -1;
11927
11928   old_obstack = labels_obstack;
11929   bitmap_obstack_initialize (&labels_obstack);
11930
11931   resolve_code (ns->code, ns);
11932
11933   bitmap_obstack_release (&labels_obstack);
11934   labels_obstack = old_obstack;
11935 }
11936
11937
11938 /* This function is called after a complete program unit has been compiled.
11939    Its purpose is to examine all of the expressions associated with a program
11940    unit, assign types to all intermediate expressions, make sure that all
11941    assignments are to compatible types and figure out which names refer to
11942    which functions or subroutines.  */
11943
11944 void
11945 gfc_resolve (gfc_namespace *ns)
11946 {
11947   gfc_namespace *old_ns;
11948   code_stack *old_cs_base;
11949
11950   if (ns->resolved)
11951     return;
11952
11953   ns->resolved = -1;
11954   old_ns = gfc_current_ns;
11955   old_cs_base = cs_base;
11956
11957   resolve_types (ns);
11958   resolve_codes (ns);
11959
11960   gfc_current_ns = old_ns;
11961   cs_base = old_cs_base;
11962   ns->resolved = 1;
11963 }