OSDN Git Service

gcc/fortran/:
[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, 2010
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 #include "constructor.h"
33
34 /* Types used in equivalence statements.  */
35
36 typedef enum seq_type
37 {
38   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
39 }
40 seq_type;
41
42 /* Stack to keep track of the nesting of blocks as we move through the
43    code.  See resolve_branch() and resolve_code().  */
44
45 typedef struct code_stack
46 {
47   struct gfc_code *head, *current;
48   struct code_stack *prev;
49
50   /* This bitmap keeps track of the targets valid for a branch from
51      inside this block except for END {IF|SELECT}s of enclosing
52      blocks.  */
53   bitmap reachable_labels;
54 }
55 code_stack;
56
57 static code_stack *cs_base = NULL;
58
59
60 /* Nonzero if we're inside a FORALL block.  */
61
62 static int forall_flag;
63
64 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
65
66 static int omp_workshare_flag;
67
68 /* Nonzero if we are processing a formal arglist. The corresponding function
69    resets the flag each time that it is read.  */
70 static int formal_arg_flag = 0;
71
72 /* True if we are resolving a specification expression.  */
73 static int specification_expr = 0;
74
75 /* The id of the last entry seen.  */
76 static int current_entry_id;
77
78 /* We use bitmaps to determine if a branch target is valid.  */
79 static bitmap_obstack labels_obstack;
80
81 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
82 static bool inquiry_argument = false;
83
84 int
85 gfc_is_formal_arg (void)
86 {
87   return formal_arg_flag;
88 }
89
90 /* Is the symbol host associated?  */
91 static bool
92 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
93 {
94   for (ns = ns->parent; ns; ns = ns->parent)
95     {      
96       if (sym->ns == ns)
97         return true;
98     }
99
100   return false;
101 }
102
103 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
104    an ABSTRACT derived-type.  If where is not NULL, an error message with that
105    locus is printed, optionally using name.  */
106
107 static gfc_try
108 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
109 {
110   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
111     {
112       if (where)
113         {
114           if (name)
115             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
116                        name, where, ts->u.derived->name);
117           else
118             gfc_error ("ABSTRACT type '%s' used at %L",
119                        ts->u.derived->name, where);
120         }
121
122       return FAILURE;
123     }
124
125   return SUCCESS;
126 }
127
128
129 /* Resolve types of formal argument lists.  These have to be done early so that
130    the formal argument lists of module procedures can be copied to the
131    containing module before the individual procedures are resolved
132    individually.  We also resolve argument lists of procedures in interface
133    blocks because they are self-contained scoping units.
134
135    Since a dummy argument cannot be a non-dummy procedure, the only
136    resort left for untyped names are the IMPLICIT types.  */
137
138 static void
139 resolve_formal_arglist (gfc_symbol *proc)
140 {
141   gfc_formal_arglist *f;
142   gfc_symbol *sym;
143   int i;
144
145   if (proc->result != NULL)
146     sym = proc->result;
147   else
148     sym = proc;
149
150   if (gfc_elemental (proc)
151       || sym->attr.pointer || sym->attr.allocatable
152       || (sym->as && sym->as->rank > 0))
153     {
154       proc->attr.always_explicit = 1;
155       sym->attr.always_explicit = 1;
156     }
157
158   formal_arg_flag = 1;
159
160   for (f = proc->formal; f; f = f->next)
161     {
162       sym = f->sym;
163
164       if (sym == NULL)
165         {
166           /* Alternate return placeholder.  */
167           if (gfc_elemental (proc))
168             gfc_error ("Alternate return specifier in elemental subroutine "
169                        "'%s' at %L is not allowed", proc->name,
170                        &proc->declared_at);
171           if (proc->attr.function)
172             gfc_error ("Alternate return specifier in function "
173                        "'%s' at %L is not allowed", proc->name,
174                        &proc->declared_at);
175           continue;
176         }
177
178       if (sym->attr.if_source != IFSRC_UNKNOWN)
179         resolve_formal_arglist (sym);
180
181       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
182         {
183           if (gfc_pure (proc) && !gfc_pure (sym))
184             {
185               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
186                          "also be PURE", sym->name, &sym->declared_at);
187               continue;
188             }
189
190           if (gfc_elemental (proc))
191             {
192               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
193                          "procedure", &sym->declared_at);
194               continue;
195             }
196
197           if (sym->attr.function
198                 && sym->ts.type == BT_UNKNOWN
199                 && sym->attr.intrinsic)
200             {
201               gfc_intrinsic_sym *isym;
202               isym = gfc_find_function (sym->name);
203               if (isym == NULL || !isym->specific)
204                 {
205                   gfc_error ("Unable to find a specific INTRINSIC procedure "
206                              "for the reference '%s' at %L", sym->name,
207                              &sym->declared_at);
208                 }
209               sym->ts = isym->ts;
210             }
211
212           continue;
213         }
214
215       if (sym->ts.type == BT_UNKNOWN)
216         {
217           if (!sym->attr.function || sym->result == sym)
218             gfc_set_default_type (sym, 1, sym->ns);
219         }
220
221       gfc_resolve_array_spec (sym->as, 0);
222
223       /* We can't tell if an array with dimension (:) is assumed or deferred
224          shape until we know if it has the pointer or allocatable attributes.
225       */
226       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
227           && !(sym->attr.pointer || sym->attr.allocatable))
228         {
229           sym->as->type = AS_ASSUMED_SHAPE;
230           for (i = 0; i < sym->as->rank; i++)
231             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
232                                                   NULL, 1);
233         }
234
235       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
236           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
237           || sym->attr.optional)
238         {
239           proc->attr.always_explicit = 1;
240           if (proc->result)
241             proc->result->attr.always_explicit = 1;
242         }
243
244       /* If the flavor is unknown at this point, it has to be a variable.
245          A procedure specification would have already set the type.  */
246
247       if (sym->attr.flavor == FL_UNKNOWN)
248         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
249
250       if (gfc_pure (proc) && !sym->attr.pointer
251           && sym->attr.flavor != FL_PROCEDURE)
252         {
253           if (proc->attr.function && sym->attr.intent != INTENT_IN)
254             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
255                        "INTENT(IN)", sym->name, proc->name,
256                        &sym->declared_at);
257
258           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
259             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
260                        "have its INTENT specified", sym->name, proc->name,
261                        &sym->declared_at);
262         }
263
264       if (gfc_elemental (proc))
265         {
266           /* F2008, C1289.  */
267           if (sym->attr.codimension)
268             {
269               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
270                          "procedure", sym->name, &sym->declared_at);
271               continue;
272             }
273
274           if (sym->as != NULL)
275             {
276               gfc_error ("Argument '%s' of elemental procedure at %L must "
277                          "be scalar", sym->name, &sym->declared_at);
278               continue;
279             }
280
281           if (sym->attr.pointer)
282             {
283               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
284                          "have the POINTER attribute", sym->name,
285                          &sym->declared_at);
286               continue;
287             }
288
289           if (sym->attr.flavor == FL_PROCEDURE)
290             {
291               gfc_error ("Dummy procedure '%s' not allowed in elemental "
292                          "procedure '%s' at %L", sym->name, proc->name,
293                          &sym->declared_at);
294               continue;
295             }
296         }
297
298       /* Each dummy shall be specified to be scalar.  */
299       if (proc->attr.proc == PROC_ST_FUNCTION)
300         {
301           if (sym->as != NULL)
302             {
303               gfc_error ("Argument '%s' of statement function at %L must "
304                          "be scalar", sym->name, &sym->declared_at);
305               continue;
306             }
307
308           if (sym->ts.type == BT_CHARACTER)
309             {
310               gfc_charlen *cl = sym->ts.u.cl;
311               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
312                 {
313                   gfc_error ("Character-valued argument '%s' of statement "
314                              "function at %L must have constant length",
315                              sym->name, &sym->declared_at);
316                   continue;
317                 }
318             }
319         }
320     }
321   formal_arg_flag = 0;
322 }
323
324
325 /* Work function called when searching for symbols that have argument lists
326    associated with them.  */
327
328 static void
329 find_arglists (gfc_symbol *sym)
330 {
331   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
332     return;
333
334   resolve_formal_arglist (sym);
335 }
336
337
338 /* Given a namespace, resolve all formal argument lists within the namespace.
339  */
340
341 static void
342 resolve_formal_arglists (gfc_namespace *ns)
343 {
344   if (ns == NULL)
345     return;
346
347   gfc_traverse_ns (ns, find_arglists);
348 }
349
350
351 static void
352 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
353 {
354   gfc_try t;
355
356   /* If this namespace is not a function or an entry master function,
357      ignore it.  */
358   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
359       || sym->attr.entry_master)
360     return;
361
362   /* Try to find out of what the return type is.  */
363   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
364     {
365       t = gfc_set_default_type (sym->result, 0, ns);
366
367       if (t == FAILURE && !sym->result->attr.untyped)
368         {
369           if (sym->result == sym)
370             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
371                        sym->name, &sym->declared_at);
372           else if (!sym->result->attr.proc_pointer)
373             gfc_error ("Result '%s' of contained function '%s' at %L has "
374                        "no IMPLICIT type", sym->result->name, sym->name,
375                        &sym->result->declared_at);
376           sym->result->attr.untyped = 1;
377         }
378     }
379
380   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
381      type, lists the only ways a character length value of * can be used:
382      dummy arguments of procedures, named constants, and function results
383      in external functions.  Internal function results and results of module
384      procedures are not on this list, ergo, not permitted.  */
385
386   if (sym->result->ts.type == BT_CHARACTER)
387     {
388       gfc_charlen *cl = sym->result->ts.u.cl;
389       if (!cl || !cl->length)
390         {
391           /* See if this is a module-procedure and adapt error message
392              accordingly.  */
393           bool module_proc;
394           gcc_assert (ns->parent && ns->parent->proc_name);
395           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
396
397           gfc_error ("Character-valued %s '%s' at %L must not be"
398                      " assumed length",
399                      module_proc ? _("module procedure")
400                                  : _("internal function"),
401                      sym->name, &sym->declared_at);
402         }
403     }
404 }
405
406
407 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
408    introduce duplicates.  */
409
410 static void
411 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
412 {
413   gfc_formal_arglist *f, *new_arglist;
414   gfc_symbol *new_sym;
415
416   for (; new_args != NULL; new_args = new_args->next)
417     {
418       new_sym = new_args->sym;
419       /* See if this arg is already in the formal argument list.  */
420       for (f = proc->formal; f; f = f->next)
421         {
422           if (new_sym == f->sym)
423             break;
424         }
425
426       if (f)
427         continue;
428
429       /* Add a new argument.  Argument order is not important.  */
430       new_arglist = gfc_get_formal_arglist ();
431       new_arglist->sym = new_sym;
432       new_arglist->next = proc->formal;
433       proc->formal  = new_arglist;
434     }
435 }
436
437
438 /* Flag the arguments that are not present in all entries.  */
439
440 static void
441 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
442 {
443   gfc_formal_arglist *f, *head;
444   head = new_args;
445
446   for (f = proc->formal; f; f = f->next)
447     {
448       if (f->sym == NULL)
449         continue;
450
451       for (new_args = head; new_args; new_args = new_args->next)
452         {
453           if (new_args->sym == f->sym)
454             break;
455         }
456
457       if (new_args)
458         continue;
459
460       f->sym->attr.not_always_present = 1;
461     }
462 }
463
464
465 /* Resolve alternate entry points.  If a symbol has multiple entry points we
466    create a new master symbol for the main routine, and turn the existing
467    symbol into an entry point.  */
468
469 static void
470 resolve_entries (gfc_namespace *ns)
471 {
472   gfc_namespace *old_ns;
473   gfc_code *c;
474   gfc_symbol *proc;
475   gfc_entry_list *el;
476   char name[GFC_MAX_SYMBOL_LEN + 1];
477   static int master_count = 0;
478
479   if (ns->proc_name == NULL)
480     return;
481
482   /* No need to do anything if this procedure doesn't have alternate entry
483      points.  */
484   if (!ns->entries)
485     return;
486
487   /* We may already have resolved alternate entry points.  */
488   if (ns->proc_name->attr.entry_master)
489     return;
490
491   /* If this isn't a procedure something has gone horribly wrong.  */
492   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
493
494   /* Remember the current namespace.  */
495   old_ns = gfc_current_ns;
496
497   gfc_current_ns = ns;
498
499   /* Add the main entry point to the list of entry points.  */
500   el = gfc_get_entry_list ();
501   el->sym = ns->proc_name;
502   el->id = 0;
503   el->next = ns->entries;
504   ns->entries = el;
505   ns->proc_name->attr.entry = 1;
506
507   /* If it is a module function, it needs to be in the right namespace
508      so that gfc_get_fake_result_decl can gather up the results. The
509      need for this arose in get_proc_name, where these beasts were
510      left in their own namespace, to keep prior references linked to
511      the entry declaration.*/
512   if (ns->proc_name->attr.function
513       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
514     el->sym->ns = ns;
515
516   /* Do the same for entries where the master is not a module
517      procedure.  These are retained in the module namespace because
518      of the module procedure declaration.  */
519   for (el = el->next; el; el = el->next)
520     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
521           && el->sym->attr.mod_proc)
522       el->sym->ns = ns;
523   el = ns->entries;
524
525   /* Add an entry statement for it.  */
526   c = gfc_get_code ();
527   c->op = EXEC_ENTRY;
528   c->ext.entry = el;
529   c->next = ns->code;
530   ns->code = c;
531
532   /* Create a new symbol for the master function.  */
533   /* Give the internal function a unique name (within this file).
534      Also include the function name so the user has some hope of figuring
535      out what is going on.  */
536   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
537             master_count++, ns->proc_name->name);
538   gfc_get_ha_symbol (name, &proc);
539   gcc_assert (proc != NULL);
540
541   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
542   if (ns->proc_name->attr.subroutine)
543     gfc_add_subroutine (&proc->attr, proc->name, NULL);
544   else
545     {
546       gfc_symbol *sym;
547       gfc_typespec *ts, *fts;
548       gfc_array_spec *as, *fas;
549       gfc_add_function (&proc->attr, proc->name, NULL);
550       proc->result = proc;
551       fas = ns->entries->sym->as;
552       fas = fas ? fas : ns->entries->sym->result->as;
553       fts = &ns->entries->sym->result->ts;
554       if (fts->type == BT_UNKNOWN)
555         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
556       for (el = ns->entries->next; el; el = el->next)
557         {
558           ts = &el->sym->result->ts;
559           as = el->sym->as;
560           as = as ? as : el->sym->result->as;
561           if (ts->type == BT_UNKNOWN)
562             ts = gfc_get_default_type (el->sym->result->name, NULL);
563
564           if (! gfc_compare_types (ts, fts)
565               || (el->sym->result->attr.dimension
566                   != ns->entries->sym->result->attr.dimension)
567               || (el->sym->result->attr.pointer
568                   != ns->entries->sym->result->attr.pointer))
569             break;
570           else if (as && fas && ns->entries->sym->result != el->sym->result
571                       && gfc_compare_array_spec (as, fas) == 0)
572             gfc_error ("Function %s at %L has entries with mismatched "
573                        "array specifications", ns->entries->sym->name,
574                        &ns->entries->sym->declared_at);
575           /* The characteristics need to match and thus both need to have
576              the same string length, i.e. both len=*, or both len=4.
577              Having both len=<variable> is also possible, but difficult to
578              check at compile time.  */
579           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
580                    && (((ts->u.cl->length && !fts->u.cl->length)
581                         ||(!ts->u.cl->length && fts->u.cl->length))
582                        || (ts->u.cl->length
583                            && ts->u.cl->length->expr_type
584                               != fts->u.cl->length->expr_type)
585                        || (ts->u.cl->length
586                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
587                            && mpz_cmp (ts->u.cl->length->value.integer,
588                                        fts->u.cl->length->value.integer) != 0)))
589             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
590                             "entries returning variables of different "
591                             "string lengths", ns->entries->sym->name,
592                             &ns->entries->sym->declared_at);
593         }
594
595       if (el == NULL)
596         {
597           sym = ns->entries->sym->result;
598           /* All result types the same.  */
599           proc->ts = *fts;
600           if (sym->attr.dimension)
601             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
602           if (sym->attr.pointer)
603             gfc_add_pointer (&proc->attr, NULL);
604         }
605       else
606         {
607           /* Otherwise the result will be passed through a union by
608              reference.  */
609           proc->attr.mixed_entry_master = 1;
610           for (el = ns->entries; el; el = el->next)
611             {
612               sym = el->sym->result;
613               if (sym->attr.dimension)
614                 {
615                   if (el == ns->entries)
616                     gfc_error ("FUNCTION result %s can't be an array in "
617                                "FUNCTION %s at %L", sym->name,
618                                ns->entries->sym->name, &sym->declared_at);
619                   else
620                     gfc_error ("ENTRY result %s can't be an array in "
621                                "FUNCTION %s at %L", sym->name,
622                                ns->entries->sym->name, &sym->declared_at);
623                 }
624               else if (sym->attr.pointer)
625                 {
626                   if (el == ns->entries)
627                     gfc_error ("FUNCTION result %s can't be a POINTER in "
628                                "FUNCTION %s at %L", sym->name,
629                                ns->entries->sym->name, &sym->declared_at);
630                   else
631                     gfc_error ("ENTRY result %s can't be a POINTER in "
632                                "FUNCTION %s at %L", sym->name,
633                                ns->entries->sym->name, &sym->declared_at);
634                 }
635               else
636                 {
637                   ts = &sym->ts;
638                   if (ts->type == BT_UNKNOWN)
639                     ts = gfc_get_default_type (sym->name, NULL);
640                   switch (ts->type)
641                     {
642                     case BT_INTEGER:
643                       if (ts->kind == gfc_default_integer_kind)
644                         sym = NULL;
645                       break;
646                     case BT_REAL:
647                       if (ts->kind == gfc_default_real_kind
648                           || ts->kind == gfc_default_double_kind)
649                         sym = NULL;
650                       break;
651                     case BT_COMPLEX:
652                       if (ts->kind == gfc_default_complex_kind)
653                         sym = NULL;
654                       break;
655                     case BT_LOGICAL:
656                       if (ts->kind == gfc_default_logical_kind)
657                         sym = NULL;
658                       break;
659                     case BT_UNKNOWN:
660                       /* We will issue error elsewhere.  */
661                       sym = NULL;
662                       break;
663                     default:
664                       break;
665                     }
666                   if (sym)
667                     {
668                       if (el == ns->entries)
669                         gfc_error ("FUNCTION result %s can't be of type %s "
670                                    "in FUNCTION %s at %L", sym->name,
671                                    gfc_typename (ts), ns->entries->sym->name,
672                                    &sym->declared_at);
673                       else
674                         gfc_error ("ENTRY result %s can't be of type %s "
675                                    "in FUNCTION %s at %L", sym->name,
676                                    gfc_typename (ts), ns->entries->sym->name,
677                                    &sym->declared_at);
678                     }
679                 }
680             }
681         }
682     }
683   proc->attr.access = ACCESS_PRIVATE;
684   proc->attr.entry_master = 1;
685
686   /* Merge all the entry point arguments.  */
687   for (el = ns->entries; el; el = el->next)
688     merge_argument_lists (proc, el->sym->formal);
689
690   /* Check the master formal arguments for any that are not
691      present in all entry points.  */
692   for (el = ns->entries; el; el = el->next)
693     check_argument_lists (proc, el->sym->formal);
694
695   /* Use the master function for the function body.  */
696   ns->proc_name = proc;
697
698   /* Finalize the new symbols.  */
699   gfc_commit_symbols ();
700
701   /* Restore the original namespace.  */
702   gfc_current_ns = old_ns;
703 }
704
705
706 static bool
707 has_default_initializer (gfc_symbol *der)
708 {
709   gfc_component *c;
710
711   gcc_assert (der->attr.flavor == FL_DERIVED);
712   for (c = der->components; c; c = c->next)
713     if ((c->ts.type != BT_DERIVED && c->initializer)
714         || (c->ts.type == BT_DERIVED
715             && (!c->attr.pointer && has_default_initializer (c->ts.u.derived))))
716       break;
717
718   return c != NULL;
719 }
720
721 /* Resolve common variables.  */
722 static void
723 resolve_common_vars (gfc_symbol *sym, bool named_common)
724 {
725   gfc_symbol *csym = sym;
726
727   for (; csym; csym = csym->common_next)
728     {
729       if (csym->value || csym->attr.data)
730         {
731           if (!csym->ns->is_block_data)
732             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
733                             "but only in BLOCK DATA initialization is "
734                             "allowed", csym->name, &csym->declared_at);
735           else if (!named_common)
736             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
737                             "in a blank COMMON but initialization is only "
738                             "allowed in named common blocks", csym->name,
739                             &csym->declared_at);
740         }
741
742       if (csym->ts.type != BT_DERIVED)
743         continue;
744
745       if (!(csym->ts.u.derived->attr.sequence
746             || csym->ts.u.derived->attr.is_bind_c))
747         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
748                        "has neither the SEQUENCE nor the BIND(C) "
749                        "attribute", csym->name, &csym->declared_at);
750       if (csym->ts.u.derived->attr.alloc_comp)
751         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
752                        "has an ultimate component that is "
753                        "allocatable", csym->name, &csym->declared_at);
754       if (has_default_initializer (csym->ts.u.derived))
755         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
756                        "may not have default initializer", csym->name,
757                        &csym->declared_at);
758
759       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
760         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
761     }
762 }
763
764 /* Resolve common blocks.  */
765 static void
766 resolve_common_blocks (gfc_symtree *common_root)
767 {
768   gfc_symbol *sym;
769
770   if (common_root == NULL)
771     return;
772
773   if (common_root->left)
774     resolve_common_blocks (common_root->left);
775   if (common_root->right)
776     resolve_common_blocks (common_root->right);
777
778   resolve_common_vars (common_root->n.common->head, true);
779
780   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
781   if (sym == NULL)
782     return;
783
784   if (sym->attr.flavor == FL_PARAMETER)
785     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
786                sym->name, &common_root->n.common->where, &sym->declared_at);
787
788   if (sym->attr.intrinsic)
789     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
790                sym->name, &common_root->n.common->where);
791   else if (sym->attr.result
792            || gfc_is_function_return_value (sym, gfc_current_ns))
793     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
794                     "that is also a function result", sym->name,
795                     &common_root->n.common->where);
796   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
797            && sym->attr.proc != PROC_ST_FUNCTION)
798     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
799                     "that is also a global procedure", sym->name,
800                     &common_root->n.common->where);
801 }
802
803
804 /* Resolve contained function types.  Because contained functions can call one
805    another, they have to be worked out before any of the contained procedures
806    can be resolved.
807
808    The good news is that if a function doesn't already have a type, the only
809    way it can get one is through an IMPLICIT type or a RESULT variable, because
810    by definition contained functions are contained namespace they're contained
811    in, not in a sibling or parent namespace.  */
812
813 static void
814 resolve_contained_functions (gfc_namespace *ns)
815 {
816   gfc_namespace *child;
817   gfc_entry_list *el;
818
819   resolve_formal_arglists (ns);
820
821   for (child = ns->contained; child; child = child->sibling)
822     {
823       /* Resolve alternate entry points first.  */
824       resolve_entries (child);
825
826       /* Then check function return types.  */
827       resolve_contained_fntype (child->proc_name, child);
828       for (el = child->entries; el; el = el->next)
829         resolve_contained_fntype (el->sym, child);
830     }
831 }
832
833
834 /* Resolve all of the elements of a structure constructor and make sure that
835    the types are correct.  */
836
837 static gfc_try
838 resolve_structure_cons (gfc_expr *expr)
839 {
840   gfc_constructor *cons;
841   gfc_component *comp;
842   gfc_try t;
843   symbol_attribute a;
844
845   t = SUCCESS;
846   cons = gfc_constructor_first (expr->value.constructor);
847   /* A constructor may have references if it is the result of substituting a
848      parameter variable.  In this case we just pull out the component we
849      want.  */
850   if (expr->ref)
851     comp = expr->ref->u.c.sym->components;
852   else
853     comp = expr->ts.u.derived->components;
854
855   /* See if the user is trying to invoke a structure constructor for one of
856      the iso_c_binding derived types.  */
857   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
858       && expr->ts.u.derived->ts.is_iso_c && cons
859       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
860     {
861       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
862                  expr->ts.u.derived->name, &(expr->where));
863       return FAILURE;
864     }
865
866   /* Return if structure constructor is c_null_(fun)prt.  */
867   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
868       && expr->ts.u.derived->ts.is_iso_c && cons
869       && cons->expr && cons->expr->expr_type == EXPR_NULL)
870     return SUCCESS;
871
872   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
873     {
874       int rank;
875
876       if (!cons->expr)
877         continue;
878
879       if (gfc_resolve_expr (cons->expr) == FAILURE)
880         {
881           t = FAILURE;
882           continue;
883         }
884
885       rank = comp->as ? comp->as->rank : 0;
886       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
887           && (comp->attr.allocatable || cons->expr->rank))
888         {
889           gfc_error ("The rank of the element in the derived type "
890                      "constructor at %L does not match that of the "
891                      "component (%d/%d)", &cons->expr->where,
892                      cons->expr->rank, rank);
893           t = FAILURE;
894         }
895
896       /* If we don't have the right type, try to convert it.  */
897
898       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
899         {
900           t = FAILURE;
901           if (strcmp (comp->name, "$extends") == 0)
902             {
903               /* Can afford to be brutal with the $extends initializer.
904                  The derived type can get lost because it is PRIVATE
905                  but it is not usage constrained by the standard.  */
906               cons->expr->ts = comp->ts;
907               t = SUCCESS;
908             }
909           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
910             gfc_error ("The element in the derived type constructor at %L, "
911                        "for pointer component '%s', is %s but should be %s",
912                        &cons->expr->where, comp->name,
913                        gfc_basic_typename (cons->expr->ts.type),
914                        gfc_basic_typename (comp->ts.type));
915           else
916             t = gfc_convert_type (cons->expr, &comp->ts, 1);
917         }
918
919       if (cons->expr->expr_type == EXPR_NULL
920           && !(comp->attr.pointer || comp->attr.allocatable
921                || comp->attr.proc_pointer
922                || (comp->ts.type == BT_CLASS
923                    && (comp->ts.u.derived->components->attr.pointer
924                        || comp->ts.u.derived->components->attr.allocatable))))
925         {
926           t = FAILURE;
927           gfc_error ("The NULL in the derived type constructor at %L is "
928                      "being applied to component '%s', which is neither "
929                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
930                      comp->name);
931         }
932
933       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
934         continue;
935
936       a = gfc_expr_attr (cons->expr);
937
938       if (!a.pointer && !a.target)
939         {
940           t = FAILURE;
941           gfc_error ("The element in the derived type constructor at %L, "
942                      "for pointer component '%s' should be a POINTER or "
943                      "a TARGET", &cons->expr->where, comp->name);
944         }
945
946       /* F2003, C1272 (3).  */
947       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
948           && (gfc_impure_variable (cons->expr->symtree->n.sym)
949               || gfc_is_coindexed (cons->expr)))
950         {
951           t = FAILURE;
952           gfc_error ("Invalid expression in the derived type constructor for "
953                      "pointer component '%s' at %L in PURE procedure",
954                      comp->name, &cons->expr->where);
955         }
956     }
957
958   return t;
959 }
960
961
962 /****************** Expression name resolution ******************/
963
964 /* Returns 0 if a symbol was not declared with a type or
965    attribute declaration statement, nonzero otherwise.  */
966
967 static int
968 was_declared (gfc_symbol *sym)
969 {
970   symbol_attribute a;
971
972   a = sym->attr;
973
974   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
975     return 1;
976
977   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
978       || a.optional || a.pointer || a.save || a.target || a.volatile_
979       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
980       || a.asynchronous || a.codimension)
981     return 1;
982
983   return 0;
984 }
985
986
987 /* Determine if a symbol is generic or not.  */
988
989 static int
990 generic_sym (gfc_symbol *sym)
991 {
992   gfc_symbol *s;
993
994   if (sym->attr.generic ||
995       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
996     return 1;
997
998   if (was_declared (sym) || sym->ns->parent == NULL)
999     return 0;
1000
1001   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1002   
1003   if (s != NULL)
1004     {
1005       if (s == sym)
1006         return 0;
1007       else
1008         return generic_sym (s);
1009     }
1010
1011   return 0;
1012 }
1013
1014
1015 /* Determine if a symbol is specific or not.  */
1016
1017 static int
1018 specific_sym (gfc_symbol *sym)
1019 {
1020   gfc_symbol *s;
1021
1022   if (sym->attr.if_source == IFSRC_IFBODY
1023       || sym->attr.proc == PROC_MODULE
1024       || sym->attr.proc == PROC_INTERNAL
1025       || sym->attr.proc == PROC_ST_FUNCTION
1026       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1027       || sym->attr.external)
1028     return 1;
1029
1030   if (was_declared (sym) || sym->ns->parent == NULL)
1031     return 0;
1032
1033   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1034
1035   return (s == NULL) ? 0 : specific_sym (s);
1036 }
1037
1038
1039 /* Figure out if the procedure is specific, generic or unknown.  */
1040
1041 typedef enum
1042 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1043 proc_type;
1044
1045 static proc_type
1046 procedure_kind (gfc_symbol *sym)
1047 {
1048   if (generic_sym (sym))
1049     return PTYPE_GENERIC;
1050
1051   if (specific_sym (sym))
1052     return PTYPE_SPECIFIC;
1053
1054   return PTYPE_UNKNOWN;
1055 }
1056
1057 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1058    is nonzero when matching actual arguments.  */
1059
1060 static int need_full_assumed_size = 0;
1061
1062 static bool
1063 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1064 {
1065   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1066       return false;
1067
1068   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1069      What should it be?  */
1070   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1071           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1072                && (e->ref->u.ar.type == AR_FULL))
1073     {
1074       gfc_error ("The upper bound in the last dimension must "
1075                  "appear in the reference to the assumed size "
1076                  "array '%s' at %L", sym->name, &e->where);
1077       return true;
1078     }
1079   return false;
1080 }
1081
1082
1083 /* Look for bad assumed size array references in argument expressions
1084   of elemental and array valued intrinsic procedures.  Since this is
1085   called from procedure resolution functions, it only recurses at
1086   operators.  */
1087
1088 static bool
1089 resolve_assumed_size_actual (gfc_expr *e)
1090 {
1091   if (e == NULL)
1092    return false;
1093
1094   switch (e->expr_type)
1095     {
1096     case EXPR_VARIABLE:
1097       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1098         return true;
1099       break;
1100
1101     case EXPR_OP:
1102       if (resolve_assumed_size_actual (e->value.op.op1)
1103           || resolve_assumed_size_actual (e->value.op.op2))
1104         return true;
1105       break;
1106
1107     default:
1108       break;
1109     }
1110   return false;
1111 }
1112
1113
1114 /* Check a generic procedure, passed as an actual argument, to see if
1115    there is a matching specific name.  If none, it is an error, and if
1116    more than one, the reference is ambiguous.  */
1117 static int
1118 count_specific_procs (gfc_expr *e)
1119 {
1120   int n;
1121   gfc_interface *p;
1122   gfc_symbol *sym;
1123         
1124   n = 0;
1125   sym = e->symtree->n.sym;
1126
1127   for (p = sym->generic; p; p = p->next)
1128     if (strcmp (sym->name, p->sym->name) == 0)
1129       {
1130         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1131                                        sym->name);
1132         n++;
1133       }
1134
1135   if (n > 1)
1136     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1137                &e->where);
1138
1139   if (n == 0)
1140     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1141                "argument at %L", sym->name, &e->where);
1142
1143   return n;
1144 }
1145
1146
1147 /* See if a call to sym could possibly be a not allowed RECURSION because of
1148    a missing RECURIVE declaration.  This means that either sym is the current
1149    context itself, or sym is the parent of a contained procedure calling its
1150    non-RECURSIVE containing procedure.
1151    This also works if sym is an ENTRY.  */
1152
1153 static bool
1154 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1155 {
1156   gfc_symbol* proc_sym;
1157   gfc_symbol* context_proc;
1158   gfc_namespace* real_context;
1159
1160   if (sym->attr.flavor == FL_PROGRAM)
1161     return false;
1162
1163   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1164
1165   /* If we've got an ENTRY, find real procedure.  */
1166   if (sym->attr.entry && sym->ns->entries)
1167     proc_sym = sym->ns->entries->sym;
1168   else
1169     proc_sym = sym;
1170
1171   /* If sym is RECURSIVE, all is well of course.  */
1172   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1173     return false;
1174
1175   /* Find the context procedure's "real" symbol if it has entries.
1176      We look for a procedure symbol, so recurse on the parents if we don't
1177      find one (like in case of a BLOCK construct).  */
1178   for (real_context = context; ; real_context = real_context->parent)
1179     {
1180       /* We should find something, eventually!  */
1181       gcc_assert (real_context);
1182
1183       context_proc = (real_context->entries ? real_context->entries->sym
1184                                             : real_context->proc_name);
1185
1186       /* In some special cases, there may not be a proc_name, like for this
1187          invalid code:
1188          real(bad_kind()) function foo () ...
1189          when checking the call to bad_kind ().
1190          In these cases, we simply return here and assume that the
1191          call is ok.  */
1192       if (!context_proc)
1193         return false;
1194
1195       if (context_proc->attr.flavor != FL_LABEL)
1196         break;
1197     }
1198
1199   /* A call from sym's body to itself is recursion, of course.  */
1200   if (context_proc == proc_sym)
1201     return true;
1202
1203   /* The same is true if context is a contained procedure and sym the
1204      containing one.  */
1205   if (context_proc->attr.contained)
1206     {
1207       gfc_symbol* parent_proc;
1208
1209       gcc_assert (context->parent);
1210       parent_proc = (context->parent->entries ? context->parent->entries->sym
1211                                               : context->parent->proc_name);
1212
1213       if (parent_proc == proc_sym)
1214         return true;
1215     }
1216
1217   return false;
1218 }
1219
1220
1221 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1222    its typespec and formal argument list.  */
1223
1224 static gfc_try
1225 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1226 {
1227   gfc_intrinsic_sym* isym;
1228   const char* symstd;
1229
1230   if (sym->formal)
1231     return SUCCESS;
1232
1233   /* We already know this one is an intrinsic, so we don't call
1234      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1235      gfc_find_subroutine directly to check whether it is a function or
1236      subroutine.  */
1237
1238   if ((isym = gfc_find_function (sym->name)))
1239     {
1240       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1241           && !sym->attr.implicit_type)
1242         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1243                       " ignored", sym->name, &sym->declared_at);
1244
1245       if (!sym->attr.function &&
1246           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1247         return FAILURE;
1248
1249       sym->ts = isym->ts;
1250     }
1251   else if ((isym = gfc_find_subroutine (sym->name)))
1252     {
1253       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1254         {
1255           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1256                       " specifier", sym->name, &sym->declared_at);
1257           return FAILURE;
1258         }
1259
1260       if (!sym->attr.subroutine &&
1261           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1262         return FAILURE;
1263     }
1264   else
1265     {
1266       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1267                  &sym->declared_at);
1268       return FAILURE;
1269     }
1270
1271   gfc_copy_formal_args_intr (sym, isym);
1272
1273   /* Check it is actually available in the standard settings.  */
1274   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1275       == FAILURE)
1276     {
1277       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1278                  " available in the current standard settings but %s.  Use"
1279                  " an appropriate -std=* option or enable -fall-intrinsics"
1280                  " in order to use it.",
1281                  sym->name, &sym->declared_at, symstd);
1282       return FAILURE;
1283     }
1284
1285   return SUCCESS;
1286 }
1287
1288
1289 /* Resolve a procedure expression, like passing it to a called procedure or as
1290    RHS for a procedure pointer assignment.  */
1291
1292 static gfc_try
1293 resolve_procedure_expression (gfc_expr* expr)
1294 {
1295   gfc_symbol* sym;
1296
1297   if (expr->expr_type != EXPR_VARIABLE)
1298     return SUCCESS;
1299   gcc_assert (expr->symtree);
1300
1301   sym = expr->symtree->n.sym;
1302
1303   if (sym->attr.intrinsic)
1304     resolve_intrinsic (sym, &expr->where);
1305
1306   if (sym->attr.flavor != FL_PROCEDURE
1307       || (sym->attr.function && sym->result == sym))
1308     return SUCCESS;
1309
1310   /* A non-RECURSIVE procedure that is used as procedure expression within its
1311      own body is in danger of being called recursively.  */
1312   if (is_illegal_recursion (sym, gfc_current_ns))
1313     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1314                  " itself recursively.  Declare it RECURSIVE or use"
1315                  " -frecursive", sym->name, &expr->where);
1316   
1317   return SUCCESS;
1318 }
1319
1320
1321 /* Resolve an actual argument list.  Most of the time, this is just
1322    resolving the expressions in the list.
1323    The exception is that we sometimes have to decide whether arguments
1324    that look like procedure arguments are really simple variable
1325    references.  */
1326
1327 static gfc_try
1328 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1329                         bool no_formal_args)
1330 {
1331   gfc_symbol *sym;
1332   gfc_symtree *parent_st;
1333   gfc_expr *e;
1334   int save_need_full_assumed_size;
1335   gfc_component *comp;
1336
1337   for (; arg; arg = arg->next)
1338     {
1339       e = arg->expr;
1340       if (e == NULL)
1341         {
1342           /* Check the label is a valid branching target.  */
1343           if (arg->label)
1344             {
1345               if (arg->label->defined == ST_LABEL_UNKNOWN)
1346                 {
1347                   gfc_error ("Label %d referenced at %L is never defined",
1348                              arg->label->value, &arg->label->where);
1349                   return FAILURE;
1350                 }
1351             }
1352           continue;
1353         }
1354
1355       if (gfc_is_proc_ptr_comp (e, &comp))
1356         {
1357           e->ts = comp->ts;
1358           if (e->expr_type == EXPR_PPC)
1359             {
1360               if (comp->as != NULL)
1361                 e->rank = comp->as->rank;
1362               e->expr_type = EXPR_FUNCTION;
1363             }
1364           if (gfc_resolve_expr (e) == FAILURE)                          
1365             return FAILURE; 
1366           goto argument_list;
1367         }
1368
1369       if (e->expr_type == EXPR_VARIABLE
1370             && e->symtree->n.sym->attr.generic
1371             && no_formal_args
1372             && count_specific_procs (e) != 1)
1373         return FAILURE;
1374
1375       if (e->ts.type != BT_PROCEDURE)
1376         {
1377           save_need_full_assumed_size = need_full_assumed_size;
1378           if (e->expr_type != EXPR_VARIABLE)
1379             need_full_assumed_size = 0;
1380           if (gfc_resolve_expr (e) != SUCCESS)
1381             return FAILURE;
1382           need_full_assumed_size = save_need_full_assumed_size;
1383           goto argument_list;
1384         }
1385
1386       /* See if the expression node should really be a variable reference.  */
1387
1388       sym = e->symtree->n.sym;
1389
1390       if (sym->attr.flavor == FL_PROCEDURE
1391           || sym->attr.intrinsic
1392           || sym->attr.external)
1393         {
1394           int actual_ok;
1395
1396           /* If a procedure is not already determined to be something else
1397              check if it is intrinsic.  */
1398           if (!sym->attr.intrinsic
1399               && !(sym->attr.external || sym->attr.use_assoc
1400                    || sym->attr.if_source == IFSRC_IFBODY)
1401               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1402             sym->attr.intrinsic = 1;
1403
1404           if (sym->attr.proc == PROC_ST_FUNCTION)
1405             {
1406               gfc_error ("Statement function '%s' at %L is not allowed as an "
1407                          "actual argument", sym->name, &e->where);
1408             }
1409
1410           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1411                                                sym->attr.subroutine);
1412           if (sym->attr.intrinsic && actual_ok == 0)
1413             {
1414               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1415                          "actual argument", sym->name, &e->where);
1416             }
1417
1418           if (sym->attr.contained && !sym->attr.use_assoc
1419               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1420             {
1421               gfc_error ("Internal procedure '%s' is not allowed as an "
1422                          "actual argument at %L", sym->name, &e->where);
1423             }
1424
1425           if (sym->attr.elemental && !sym->attr.intrinsic)
1426             {
1427               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1428                          "allowed as an actual argument at %L", sym->name,
1429                          &e->where);
1430             }
1431
1432           /* Check if a generic interface has a specific procedure
1433             with the same name before emitting an error.  */
1434           if (sym->attr.generic && count_specific_procs (e) != 1)
1435             return FAILURE;
1436           
1437           /* Just in case a specific was found for the expression.  */
1438           sym = e->symtree->n.sym;
1439
1440           /* If the symbol is the function that names the current (or
1441              parent) scope, then we really have a variable reference.  */
1442
1443           if (gfc_is_function_return_value (sym, sym->ns))
1444             goto got_variable;
1445
1446           /* If all else fails, see if we have a specific intrinsic.  */
1447           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1448             {
1449               gfc_intrinsic_sym *isym;
1450
1451               isym = gfc_find_function (sym->name);
1452               if (isym == NULL || !isym->specific)
1453                 {
1454                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1455                              "for the reference '%s' at %L", sym->name,
1456                              &e->where);
1457                   return FAILURE;
1458                 }
1459               sym->ts = isym->ts;
1460               sym->attr.intrinsic = 1;
1461               sym->attr.function = 1;
1462             }
1463
1464           if (gfc_resolve_expr (e) == FAILURE)
1465             return FAILURE;
1466           goto argument_list;
1467         }
1468
1469       /* See if the name is a module procedure in a parent unit.  */
1470
1471       if (was_declared (sym) || sym->ns->parent == NULL)
1472         goto got_variable;
1473
1474       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1475         {
1476           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1477           return FAILURE;
1478         }
1479
1480       if (parent_st == NULL)
1481         goto got_variable;
1482
1483       sym = parent_st->n.sym;
1484       e->symtree = parent_st;           /* Point to the right thing.  */
1485
1486       if (sym->attr.flavor == FL_PROCEDURE
1487           || sym->attr.intrinsic
1488           || sym->attr.external)
1489         {
1490           if (gfc_resolve_expr (e) == FAILURE)
1491             return FAILURE;
1492           goto argument_list;
1493         }
1494
1495     got_variable:
1496       e->expr_type = EXPR_VARIABLE;
1497       e->ts = sym->ts;
1498       if (sym->as != NULL)
1499         {
1500           e->rank = sym->as->rank;
1501           e->ref = gfc_get_ref ();
1502           e->ref->type = REF_ARRAY;
1503           e->ref->u.ar.type = AR_FULL;
1504           e->ref->u.ar.as = sym->as;
1505         }
1506
1507       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1508          primary.c (match_actual_arg). If above code determines that it
1509          is a  variable instead, it needs to be resolved as it was not
1510          done at the beginning of this function.  */
1511       save_need_full_assumed_size = need_full_assumed_size;
1512       if (e->expr_type != EXPR_VARIABLE)
1513         need_full_assumed_size = 0;
1514       if (gfc_resolve_expr (e) != SUCCESS)
1515         return FAILURE;
1516       need_full_assumed_size = save_need_full_assumed_size;
1517
1518     argument_list:
1519       /* Check argument list functions %VAL, %LOC and %REF.  There is
1520          nothing to do for %REF.  */
1521       if (arg->name && arg->name[0] == '%')
1522         {
1523           if (strncmp ("%VAL", arg->name, 4) == 0)
1524             {
1525               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1526                 {
1527                   gfc_error ("By-value argument at %L is not of numeric "
1528                              "type", &e->where);
1529                   return FAILURE;
1530                 }
1531
1532               if (e->rank)
1533                 {
1534                   gfc_error ("By-value argument at %L cannot be an array or "
1535                              "an array section", &e->where);
1536                 return FAILURE;
1537                 }
1538
1539               /* Intrinsics are still PROC_UNKNOWN here.  However,
1540                  since same file external procedures are not resolvable
1541                  in gfortran, it is a good deal easier to leave them to
1542                  intrinsic.c.  */
1543               if (ptype != PROC_UNKNOWN
1544                   && ptype != PROC_DUMMY
1545                   && ptype != PROC_EXTERNAL
1546                   && ptype != PROC_MODULE)
1547                 {
1548                   gfc_error ("By-value argument at %L is not allowed "
1549                              "in this context", &e->where);
1550                   return FAILURE;
1551                 }
1552             }
1553
1554           /* Statement functions have already been excluded above.  */
1555           else if (strncmp ("%LOC", arg->name, 4) == 0
1556                    && e->ts.type == BT_PROCEDURE)
1557             {
1558               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1559                 {
1560                   gfc_error ("Passing internal procedure at %L by location "
1561                              "not allowed", &e->where);
1562                   return FAILURE;
1563                 }
1564             }
1565         }
1566
1567       /* Fortran 2008, C1237.  */
1568       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1569           && gfc_has_ultimate_pointer (e))
1570         {
1571           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1572                      "component", &e->where);
1573           return FAILURE;
1574         }
1575     }
1576
1577   return SUCCESS;
1578 }
1579
1580
1581 /* Do the checks of the actual argument list that are specific to elemental
1582    procedures.  If called with c == NULL, we have a function, otherwise if
1583    expr == NULL, we have a subroutine.  */
1584
1585 static gfc_try
1586 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1587 {
1588   gfc_actual_arglist *arg0;
1589   gfc_actual_arglist *arg;
1590   gfc_symbol *esym = NULL;
1591   gfc_intrinsic_sym *isym = NULL;
1592   gfc_expr *e = NULL;
1593   gfc_intrinsic_arg *iformal = NULL;
1594   gfc_formal_arglist *eformal = NULL;
1595   bool formal_optional = false;
1596   bool set_by_optional = false;
1597   int i;
1598   int rank = 0;
1599
1600   /* Is this an elemental procedure?  */
1601   if (expr && expr->value.function.actual != NULL)
1602     {
1603       if (expr->value.function.esym != NULL
1604           && expr->value.function.esym->attr.elemental)
1605         {
1606           arg0 = expr->value.function.actual;
1607           esym = expr->value.function.esym;
1608         }
1609       else if (expr->value.function.isym != NULL
1610                && expr->value.function.isym->elemental)
1611         {
1612           arg0 = expr->value.function.actual;
1613           isym = expr->value.function.isym;
1614         }
1615       else
1616         return SUCCESS;
1617     }
1618   else if (c && c->ext.actual != NULL)
1619     {
1620       arg0 = c->ext.actual;
1621       
1622       if (c->resolved_sym)
1623         esym = c->resolved_sym;
1624       else
1625         esym = c->symtree->n.sym;
1626       gcc_assert (esym);
1627
1628       if (!esym->attr.elemental)
1629         return SUCCESS;
1630     }
1631   else
1632     return SUCCESS;
1633
1634   /* The rank of an elemental is the rank of its array argument(s).  */
1635   for (arg = arg0; arg; arg = arg->next)
1636     {
1637       if (arg->expr != NULL && arg->expr->rank > 0)
1638         {
1639           rank = arg->expr->rank;
1640           if (arg->expr->expr_type == EXPR_VARIABLE
1641               && arg->expr->symtree->n.sym->attr.optional)
1642             set_by_optional = true;
1643
1644           /* Function specific; set the result rank and shape.  */
1645           if (expr)
1646             {
1647               expr->rank = rank;
1648               if (!expr->shape && arg->expr->shape)
1649                 {
1650                   expr->shape = gfc_get_shape (rank);
1651                   for (i = 0; i < rank; i++)
1652                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1653                 }
1654             }
1655           break;
1656         }
1657     }
1658
1659   /* If it is an array, it shall not be supplied as an actual argument
1660      to an elemental procedure unless an array of the same rank is supplied
1661      as an actual argument corresponding to a nonoptional dummy argument of
1662      that elemental procedure(12.4.1.5).  */
1663   formal_optional = false;
1664   if (isym)
1665     iformal = isym->formal;
1666   else
1667     eformal = esym->formal;
1668
1669   for (arg = arg0; arg; arg = arg->next)
1670     {
1671       if (eformal)
1672         {
1673           if (eformal->sym && eformal->sym->attr.optional)
1674             formal_optional = true;
1675           eformal = eformal->next;
1676         }
1677       else if (isym && iformal)
1678         {
1679           if (iformal->optional)
1680             formal_optional = true;
1681           iformal = iformal->next;
1682         }
1683       else if (isym)
1684         formal_optional = true;
1685
1686       if (pedantic && arg->expr != NULL
1687           && arg->expr->expr_type == EXPR_VARIABLE
1688           && arg->expr->symtree->n.sym->attr.optional
1689           && formal_optional
1690           && arg->expr->rank
1691           && (set_by_optional || arg->expr->rank != rank)
1692           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1693         {
1694           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1695                        "MISSING, it cannot be the actual argument of an "
1696                        "ELEMENTAL procedure unless there is a non-optional "
1697                        "argument with the same rank (12.4.1.5)",
1698                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1699           return FAILURE;
1700         }
1701     }
1702
1703   for (arg = arg0; arg; arg = arg->next)
1704     {
1705       if (arg->expr == NULL || arg->expr->rank == 0)
1706         continue;
1707
1708       /* Being elemental, the last upper bound of an assumed size array
1709          argument must be present.  */
1710       if (resolve_assumed_size_actual (arg->expr))
1711         return FAILURE;
1712
1713       /* Elemental procedure's array actual arguments must conform.  */
1714       if (e != NULL)
1715         {
1716           if (gfc_check_conformance (arg->expr, e,
1717                                      "elemental procedure") == FAILURE)
1718             return FAILURE;
1719         }
1720       else
1721         e = arg->expr;
1722     }
1723
1724   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1725      is an array, the intent inout/out variable needs to be also an array.  */
1726   if (rank > 0 && esym && expr == NULL)
1727     for (eformal = esym->formal, arg = arg0; arg && eformal;
1728          arg = arg->next, eformal = eformal->next)
1729       if ((eformal->sym->attr.intent == INTENT_OUT
1730            || eformal->sym->attr.intent == INTENT_INOUT)
1731           && arg->expr && arg->expr->rank == 0)
1732         {
1733           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1734                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1735                      "actual argument is an array", &arg->expr->where,
1736                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1737                      : "INOUT", eformal->sym->name, esym->name);
1738           return FAILURE;
1739         }
1740   return SUCCESS;
1741 }
1742
1743
1744 /* Go through each actual argument in ACTUAL and see if it can be
1745    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1746    function being called, or NULL if not known.  */
1747
1748 static void
1749 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1750 {
1751   gfc_actual_arglist *ap;
1752   gfc_expr *expr;
1753
1754   for (ap = actual; ap; ap = ap->next)
1755     if (ap->expr
1756         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1757         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1758                                          NOT_ELEMENTAL))
1759       ap->expr->inline_noncopying_intrinsic = 1;
1760 }
1761
1762
1763 /* This function does the checking of references to global procedures
1764    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1765    77 and 95 standards.  It checks for a gsymbol for the name, making
1766    one if it does not already exist.  If it already exists, then the
1767    reference being resolved must correspond to the type of gsymbol.
1768    Otherwise, the new symbol is equipped with the attributes of the
1769    reference.  The corresponding code that is called in creating
1770    global entities is parse.c.
1771
1772    In addition, for all but -std=legacy, the gsymbols are used to
1773    check the interfaces of external procedures from the same file.
1774    The namespace of the gsymbol is resolved and then, once this is
1775    done the interface is checked.  */
1776
1777
1778 static bool
1779 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1780 {
1781   if (!gsym_ns->proc_name->attr.recursive)
1782     return true;
1783
1784   if (sym->ns == gsym_ns)
1785     return false;
1786
1787   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1788     return false;
1789
1790   return true;
1791 }
1792
1793 static bool
1794 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1795 {
1796   if (gsym_ns->entries)
1797     {
1798       gfc_entry_list *entry = gsym_ns->entries;
1799
1800       for (; entry; entry = entry->next)
1801         {
1802           if (strcmp (sym->name, entry->sym->name) == 0)
1803             {
1804               if (strcmp (gsym_ns->proc_name->name,
1805                           sym->ns->proc_name->name) == 0)
1806                 return false;
1807
1808               if (sym->ns->parent
1809                   && strcmp (gsym_ns->proc_name->name,
1810                              sym->ns->parent->proc_name->name) == 0)
1811                 return false;
1812             }
1813         }
1814     }
1815   return true;
1816 }
1817
1818 static void
1819 resolve_global_procedure (gfc_symbol *sym, locus *where,
1820                           gfc_actual_arglist **actual, int sub)
1821 {
1822   gfc_gsymbol * gsym;
1823   gfc_namespace *ns;
1824   enum gfc_symbol_type type;
1825
1826   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1827
1828   gsym = gfc_get_gsymbol (sym->name);
1829
1830   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1831     gfc_global_used (gsym, where);
1832
1833   if (gfc_option.flag_whole_file
1834         && sym->attr.if_source == IFSRC_UNKNOWN
1835         && gsym->type != GSYM_UNKNOWN
1836         && gsym->ns
1837         && gsym->ns->resolved != -1
1838         && gsym->ns->proc_name
1839         && not_in_recursive (sym, gsym->ns)
1840         && not_entry_self_reference (sym, gsym->ns))
1841     {
1842       /* Make sure that translation for the gsymbol occurs before
1843          the procedure currently being resolved.  */
1844       ns = gsym->ns->resolved ? NULL : gfc_global_ns_list;
1845       for (; ns && ns != gsym->ns; ns = ns->sibling)
1846         {
1847           if (ns->sibling == gsym->ns)
1848             {
1849               ns->sibling = gsym->ns->sibling;
1850               gsym->ns->sibling = gfc_global_ns_list;
1851               gfc_global_ns_list = gsym->ns;
1852               break;
1853             }
1854         }
1855
1856       if (!gsym->ns->resolved)
1857         {
1858           gfc_dt_list *old_dt_list;
1859
1860           /* Stash away derived types so that the backend_decls do not
1861              get mixed up.  */
1862           old_dt_list = gfc_derived_types;
1863           gfc_derived_types = NULL;
1864
1865           gfc_resolve (gsym->ns);
1866
1867           /* Store the new derived types with the global namespace.  */
1868           if (gfc_derived_types)
1869             gsym->ns->derived_types = gfc_derived_types;
1870
1871           /* Restore the derived types of this namespace.  */
1872           gfc_derived_types = old_dt_list;
1873         }
1874
1875       if (gsym->ns->proc_name->attr.function
1876             && gsym->ns->proc_name->as
1877             && gsym->ns->proc_name->as->rank
1878             && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1879         gfc_error ("The reference to function '%s' at %L either needs an "
1880                    "explicit INTERFACE or the rank is incorrect", sym->name,
1881                    where);
1882      
1883       /* Non-assumed length character functions.  */
1884       if (sym->attr.function && sym->ts.type == BT_CHARACTER
1885           && gsym->ns->proc_name->ts.u.cl->length != NULL)
1886         {
1887           gfc_charlen *cl = sym->ts.u.cl;
1888
1889           if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1890               && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1891             {
1892               gfc_error ("Nonconstant character-length function '%s' at %L "
1893                          "must have an explicit interface", sym->name,
1894                          &sym->declared_at);
1895             }
1896         }
1897
1898       if (gfc_option.flag_whole_file == 1
1899             || ((gfc_option.warn_std & GFC_STD_LEGACY)
1900                   &&
1901                !(gfc_option.warn_std & GFC_STD_GNU)))
1902         gfc_errors_to_warnings (1);
1903
1904       gfc_procedure_use (gsym->ns->proc_name, actual, where);
1905
1906       gfc_errors_to_warnings (0);
1907     }
1908
1909   if (gsym->type == GSYM_UNKNOWN)
1910     {
1911       gsym->type = type;
1912       gsym->where = *where;
1913     }
1914
1915   gsym->used = 1;
1916 }
1917
1918
1919 /************* Function resolution *************/
1920
1921 /* Resolve a function call known to be generic.
1922    Section 14.1.2.4.1.  */
1923
1924 static match
1925 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1926 {
1927   gfc_symbol *s;
1928
1929   if (sym->attr.generic)
1930     {
1931       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1932       if (s != NULL)
1933         {
1934           expr->value.function.name = s->name;
1935           expr->value.function.esym = s;
1936
1937           if (s->ts.type != BT_UNKNOWN)
1938             expr->ts = s->ts;
1939           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1940             expr->ts = s->result->ts;
1941
1942           if (s->as != NULL)
1943             expr->rank = s->as->rank;
1944           else if (s->result != NULL && s->result->as != NULL)
1945             expr->rank = s->result->as->rank;
1946
1947           gfc_set_sym_referenced (expr->value.function.esym);
1948
1949           return MATCH_YES;
1950         }
1951
1952       /* TODO: Need to search for elemental references in generic
1953          interface.  */
1954     }
1955
1956   if (sym->attr.intrinsic)
1957     return gfc_intrinsic_func_interface (expr, 0);
1958
1959   return MATCH_NO;
1960 }
1961
1962
1963 static gfc_try
1964 resolve_generic_f (gfc_expr *expr)
1965 {
1966   gfc_symbol *sym;
1967   match m;
1968
1969   sym = expr->symtree->n.sym;
1970
1971   for (;;)
1972     {
1973       m = resolve_generic_f0 (expr, sym);
1974       if (m == MATCH_YES)
1975         return SUCCESS;
1976       else if (m == MATCH_ERROR)
1977         return FAILURE;
1978
1979 generic:
1980       if (sym->ns->parent == NULL)
1981         break;
1982       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1983
1984       if (sym == NULL)
1985         break;
1986       if (!generic_sym (sym))
1987         goto generic;
1988     }
1989
1990   /* Last ditch attempt.  See if the reference is to an intrinsic
1991      that possesses a matching interface.  14.1.2.4  */
1992   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
1993     {
1994       gfc_error ("There is no specific function for the generic '%s' at %L",
1995                  expr->symtree->n.sym->name, &expr->where);
1996       return FAILURE;
1997     }
1998
1999   m = gfc_intrinsic_func_interface (expr, 0);
2000   if (m == MATCH_YES)
2001     return SUCCESS;
2002   if (m == MATCH_NO)
2003     gfc_error ("Generic function '%s' at %L is not consistent with a "
2004                "specific intrinsic interface", expr->symtree->n.sym->name,
2005                &expr->where);
2006
2007   return FAILURE;
2008 }
2009
2010
2011 /* Resolve a function call known to be specific.  */
2012
2013 static match
2014 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2015 {
2016   match m;
2017
2018   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2019     {
2020       if (sym->attr.dummy)
2021         {
2022           sym->attr.proc = PROC_DUMMY;
2023           goto found;
2024         }
2025
2026       sym->attr.proc = PROC_EXTERNAL;
2027       goto found;
2028     }
2029
2030   if (sym->attr.proc == PROC_MODULE
2031       || sym->attr.proc == PROC_ST_FUNCTION
2032       || sym->attr.proc == PROC_INTERNAL)
2033     goto found;
2034
2035   if (sym->attr.intrinsic)
2036     {
2037       m = gfc_intrinsic_func_interface (expr, 1);
2038       if (m == MATCH_YES)
2039         return MATCH_YES;
2040       if (m == MATCH_NO)
2041         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2042                    "with an intrinsic", sym->name, &expr->where);
2043
2044       return MATCH_ERROR;
2045     }
2046
2047   return MATCH_NO;
2048
2049 found:
2050   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2051
2052   if (sym->result)
2053     expr->ts = sym->result->ts;
2054   else
2055     expr->ts = sym->ts;
2056   expr->value.function.name = sym->name;
2057   expr->value.function.esym = sym;
2058   if (sym->as != NULL)
2059     expr->rank = sym->as->rank;
2060
2061   return MATCH_YES;
2062 }
2063
2064
2065 static gfc_try
2066 resolve_specific_f (gfc_expr *expr)
2067 {
2068   gfc_symbol *sym;
2069   match m;
2070
2071   sym = expr->symtree->n.sym;
2072
2073   for (;;)
2074     {
2075       m = resolve_specific_f0 (sym, expr);
2076       if (m == MATCH_YES)
2077         return SUCCESS;
2078       if (m == MATCH_ERROR)
2079         return FAILURE;
2080
2081       if (sym->ns->parent == NULL)
2082         break;
2083
2084       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2085
2086       if (sym == NULL)
2087         break;
2088     }
2089
2090   gfc_error ("Unable to resolve the specific function '%s' at %L",
2091              expr->symtree->n.sym->name, &expr->where);
2092
2093   return SUCCESS;
2094 }
2095
2096
2097 /* Resolve a procedure call not known to be generic nor specific.  */
2098
2099 static gfc_try
2100 resolve_unknown_f (gfc_expr *expr)
2101 {
2102   gfc_symbol *sym;
2103   gfc_typespec *ts;
2104
2105   sym = expr->symtree->n.sym;
2106
2107   if (sym->attr.dummy)
2108     {
2109       sym->attr.proc = PROC_DUMMY;
2110       expr->value.function.name = sym->name;
2111       goto set_type;
2112     }
2113
2114   /* See if we have an intrinsic function reference.  */
2115
2116   if (gfc_is_intrinsic (sym, 0, expr->where))
2117     {
2118       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2119         return SUCCESS;
2120       return FAILURE;
2121     }
2122
2123   /* The reference is to an external name.  */
2124
2125   sym->attr.proc = PROC_EXTERNAL;
2126   expr->value.function.name = sym->name;
2127   expr->value.function.esym = expr->symtree->n.sym;
2128
2129   if (sym->as != NULL)
2130     expr->rank = sym->as->rank;
2131
2132   /* Type of the expression is either the type of the symbol or the
2133      default type of the symbol.  */
2134
2135 set_type:
2136   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2137
2138   if (sym->ts.type != BT_UNKNOWN)
2139     expr->ts = sym->ts;
2140   else
2141     {
2142       ts = gfc_get_default_type (sym->name, sym->ns);
2143
2144       if (ts->type == BT_UNKNOWN)
2145         {
2146           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2147                      sym->name, &expr->where);
2148           return FAILURE;
2149         }
2150       else
2151         expr->ts = *ts;
2152     }
2153
2154   return SUCCESS;
2155 }
2156
2157
2158 /* Return true, if the symbol is an external procedure.  */
2159 static bool
2160 is_external_proc (gfc_symbol *sym)
2161 {
2162   if (!sym->attr.dummy && !sym->attr.contained
2163         && !(sym->attr.intrinsic
2164               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2165         && sym->attr.proc != PROC_ST_FUNCTION
2166         && !sym->attr.use_assoc
2167         && sym->name)
2168     return true;
2169
2170   return false;
2171 }
2172
2173
2174 /* Figure out if a function reference is pure or not.  Also set the name
2175    of the function for a potential error message.  Return nonzero if the
2176    function is PURE, zero if not.  */
2177 static int
2178 pure_stmt_function (gfc_expr *, gfc_symbol *);
2179
2180 static int
2181 pure_function (gfc_expr *e, const char **name)
2182 {
2183   int pure;
2184
2185   *name = NULL;
2186
2187   if (e->symtree != NULL
2188         && e->symtree->n.sym != NULL
2189         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2190     return pure_stmt_function (e, e->symtree->n.sym);
2191
2192   if (e->value.function.esym)
2193     {
2194       pure = gfc_pure (e->value.function.esym);
2195       *name = e->value.function.esym->name;
2196     }
2197   else if (e->value.function.isym)
2198     {
2199       pure = e->value.function.isym->pure
2200              || e->value.function.isym->elemental;
2201       *name = e->value.function.isym->name;
2202     }
2203   else
2204     {
2205       /* Implicit functions are not pure.  */
2206       pure = 0;
2207       *name = e->value.function.name;
2208     }
2209
2210   return pure;
2211 }
2212
2213
2214 static bool
2215 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2216                  int *f ATTRIBUTE_UNUSED)
2217 {
2218   const char *name;
2219
2220   /* Don't bother recursing into other statement functions
2221      since they will be checked individually for purity.  */
2222   if (e->expr_type != EXPR_FUNCTION
2223         || !e->symtree
2224         || e->symtree->n.sym == sym
2225         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2226     return false;
2227
2228   return pure_function (e, &name) ? false : true;
2229 }
2230
2231
2232 static int
2233 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2234 {
2235   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2236 }
2237
2238
2239 static gfc_try
2240 is_scalar_expr_ptr (gfc_expr *expr)
2241 {
2242   gfc_try retval = SUCCESS;
2243   gfc_ref *ref;
2244   int start;
2245   int end;
2246
2247   /* See if we have a gfc_ref, which means we have a substring, array
2248      reference, or a component.  */
2249   if (expr->ref != NULL)
2250     {
2251       ref = expr->ref;
2252       while (ref->next != NULL)
2253         ref = ref->next;
2254
2255       switch (ref->type)
2256         {
2257         case REF_SUBSTRING:
2258           if (ref->u.ss.length != NULL 
2259               && ref->u.ss.length->length != NULL
2260               && ref->u.ss.start
2261               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2262               && ref->u.ss.end
2263               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2264             {
2265               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2266               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2267               if (end - start + 1 != 1)
2268                 retval = FAILURE;
2269             }
2270           else
2271             retval = FAILURE;
2272           break;
2273         case REF_ARRAY:
2274           if (ref->u.ar.type == AR_ELEMENT)
2275             retval = SUCCESS;
2276           else if (ref->u.ar.type == AR_FULL)
2277             {
2278               /* The user can give a full array if the array is of size 1.  */
2279               if (ref->u.ar.as != NULL
2280                   && ref->u.ar.as->rank == 1
2281                   && ref->u.ar.as->type == AS_EXPLICIT
2282                   && ref->u.ar.as->lower[0] != NULL
2283                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2284                   && ref->u.ar.as->upper[0] != NULL
2285                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2286                 {
2287                   /* If we have a character string, we need to check if
2288                      its length is one.  */
2289                   if (expr->ts.type == BT_CHARACTER)
2290                     {
2291                       if (expr->ts.u.cl == NULL
2292                           || expr->ts.u.cl->length == NULL
2293                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2294                           != 0)
2295                         retval = FAILURE;
2296                     }
2297                   else
2298                     {
2299                       /* We have constant lower and upper bounds.  If the
2300                          difference between is 1, it can be considered a
2301                          scalar.  */
2302                       start = (int) mpz_get_si
2303                                 (ref->u.ar.as->lower[0]->value.integer);
2304                       end = (int) mpz_get_si
2305                                 (ref->u.ar.as->upper[0]->value.integer);
2306                       if (end - start + 1 != 1)
2307                         retval = FAILURE;
2308                    }
2309                 }
2310               else
2311                 retval = FAILURE;
2312             }
2313           else
2314             retval = FAILURE;
2315           break;
2316         default:
2317           retval = SUCCESS;
2318           break;
2319         }
2320     }
2321   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2322     {
2323       /* Character string.  Make sure it's of length 1.  */
2324       if (expr->ts.u.cl == NULL
2325           || expr->ts.u.cl->length == NULL
2326           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2327         retval = FAILURE;
2328     }
2329   else if (expr->rank != 0)
2330     retval = FAILURE;
2331
2332   return retval;
2333 }
2334
2335
2336 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2337    and, in the case of c_associated, set the binding label based on
2338    the arguments.  */
2339
2340 static gfc_try
2341 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2342                           gfc_symbol **new_sym)
2343 {
2344   char name[GFC_MAX_SYMBOL_LEN + 1];
2345   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2346   int optional_arg = 0, is_pointer = 0;
2347   gfc_try retval = SUCCESS;
2348   gfc_symbol *args_sym;
2349   gfc_typespec *arg_ts;
2350
2351   if (args->expr->expr_type == EXPR_CONSTANT
2352       || args->expr->expr_type == EXPR_OP
2353       || args->expr->expr_type == EXPR_NULL)
2354     {
2355       gfc_error ("Argument to '%s' at %L is not a variable",
2356                  sym->name, &(args->expr->where));
2357       return FAILURE;
2358     }
2359
2360   args_sym = args->expr->symtree->n.sym;
2361
2362   /* The typespec for the actual arg should be that stored in the expr
2363      and not necessarily that of the expr symbol (args_sym), because
2364      the actual expression could be a part-ref of the expr symbol.  */
2365   arg_ts = &(args->expr->ts);
2366
2367   is_pointer = gfc_is_data_pointer (args->expr);
2368     
2369   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2370     {
2371       /* If the user gave two args then they are providing something for
2372          the optional arg (the second cptr).  Therefore, set the name and
2373          binding label to the c_associated for two cptrs.  Otherwise,
2374          set c_associated to expect one cptr.  */
2375       if (args->next)
2376         {
2377           /* two args.  */
2378           sprintf (name, "%s_2", sym->name);
2379           sprintf (binding_label, "%s_2", sym->binding_label);
2380           optional_arg = 1;
2381         }
2382       else
2383         {
2384           /* one arg.  */
2385           sprintf (name, "%s_1", sym->name);
2386           sprintf (binding_label, "%s_1", sym->binding_label);
2387           optional_arg = 0;
2388         }
2389
2390       /* Get a new symbol for the version of c_associated that
2391          will get called.  */
2392       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2393     }
2394   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2395            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2396     {
2397       sprintf (name, "%s", sym->name);
2398       sprintf (binding_label, "%s", sym->binding_label);
2399
2400       /* Error check the call.  */
2401       if (args->next != NULL)
2402         {
2403           gfc_error_now ("More actual than formal arguments in '%s' "
2404                          "call at %L", name, &(args->expr->where));
2405           retval = FAILURE;
2406         }
2407       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2408         {
2409           /* Make sure we have either the target or pointer attribute.  */
2410           if (!args_sym->attr.target && !is_pointer)
2411             {
2412               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2413                              "a TARGET or an associated pointer",
2414                              args_sym->name,
2415                              sym->name, &(args->expr->where));
2416               retval = FAILURE;
2417             }
2418
2419           /* See if we have interoperable type and type param.  */
2420           if (verify_c_interop (arg_ts) == SUCCESS
2421               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2422             {
2423               if (args_sym->attr.target == 1)
2424                 {
2425                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2426                      has the target attribute and is interoperable.  */
2427                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2428                      allocatable variable that has the TARGET attribute and
2429                      is not an array of zero size.  */
2430                   if (args_sym->attr.allocatable == 1)
2431                     {
2432                       if (args_sym->attr.dimension != 0 
2433                           && (args_sym->as && args_sym->as->rank == 0))
2434                         {
2435                           gfc_error_now ("Allocatable variable '%s' used as a "
2436                                          "parameter to '%s' at %L must not be "
2437                                          "an array of zero size",
2438                                          args_sym->name, sym->name,
2439                                          &(args->expr->where));
2440                           retval = FAILURE;
2441                         }
2442                     }
2443                   else
2444                     {
2445                       /* A non-allocatable target variable with C
2446                          interoperable type and type parameters must be
2447                          interoperable.  */
2448                       if (args_sym && args_sym->attr.dimension)
2449                         {
2450                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2451                             {
2452                               gfc_error ("Assumed-shape array '%s' at %L "
2453                                          "cannot be an argument to the "
2454                                          "procedure '%s' because "
2455                                          "it is not C interoperable",
2456                                          args_sym->name,
2457                                          &(args->expr->where), sym->name);
2458                               retval = FAILURE;
2459                             }
2460                           else if (args_sym->as->type == AS_DEFERRED)
2461                             {
2462                               gfc_error ("Deferred-shape array '%s' at %L "
2463                                          "cannot be an argument to the "
2464                                          "procedure '%s' because "
2465                                          "it is not C interoperable",
2466                                          args_sym->name,
2467                                          &(args->expr->where), sym->name);
2468                               retval = FAILURE;
2469                             }
2470                         }
2471                               
2472                       /* Make sure it's not a character string.  Arrays of
2473                          any type should be ok if the variable is of a C
2474                          interoperable type.  */
2475                       if (arg_ts->type == BT_CHARACTER)
2476                         if (arg_ts->u.cl != NULL
2477                             && (arg_ts->u.cl->length == NULL
2478                                 || arg_ts->u.cl->length->expr_type
2479                                    != EXPR_CONSTANT
2480                                 || mpz_cmp_si
2481                                     (arg_ts->u.cl->length->value.integer, 1)
2482                                    != 0)
2483                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2484                           {
2485                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2486                                            "at %L must have a length of 1",
2487                                            args_sym->name, sym->name,
2488                                            &(args->expr->where));
2489                             retval = FAILURE;
2490                           }
2491                     }
2492                 }
2493               else if (is_pointer
2494                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2495                 {
2496                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2497                      scalar pointer.  */
2498                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2499                                  "associated scalar POINTER", args_sym->name,
2500                                  sym->name, &(args->expr->where));
2501                   retval = FAILURE;
2502                 }
2503             }
2504           else
2505             {
2506               /* The parameter is not required to be C interoperable.  If it
2507                  is not C interoperable, it must be a nonpolymorphic scalar
2508                  with no length type parameters.  It still must have either
2509                  the pointer or target attribute, and it can be
2510                  allocatable (but must be allocated when c_loc is called).  */
2511               if (args->expr->rank != 0 
2512                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2513                 {
2514                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2515                                  "scalar", args_sym->name, sym->name,
2516                                  &(args->expr->where));
2517                   retval = FAILURE;
2518                 }
2519               else if (arg_ts->type == BT_CHARACTER 
2520                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2521                 {
2522                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2523                                  "%L must have a length of 1",
2524                                  args_sym->name, sym->name,
2525                                  &(args->expr->where));
2526                   retval = FAILURE;
2527                 }
2528             }
2529         }
2530       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2531         {
2532           if (args_sym->attr.flavor != FL_PROCEDURE)
2533             {
2534               /* TODO: Update this error message to allow for procedure
2535                  pointers once they are implemented.  */
2536               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2537                              "procedure",
2538                              args_sym->name, sym->name,
2539                              &(args->expr->where));
2540               retval = FAILURE;
2541             }
2542           else if (args_sym->attr.is_bind_c != 1)
2543             {
2544               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2545                              "BIND(C)",
2546                              args_sym->name, sym->name,
2547                              &(args->expr->where));
2548               retval = FAILURE;
2549             }
2550         }
2551       
2552       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2553       *new_sym = sym;
2554     }
2555   else
2556     {
2557       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2558                           "iso_c_binding function: '%s'!\n", sym->name);
2559     }
2560
2561   return retval;
2562 }
2563
2564
2565 /* Resolve a function call, which means resolving the arguments, then figuring
2566    out which entity the name refers to.  */
2567 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2568    to INTENT(OUT) or INTENT(INOUT).  */
2569
2570 static gfc_try
2571 resolve_function (gfc_expr *expr)
2572 {
2573   gfc_actual_arglist *arg;
2574   gfc_symbol *sym;
2575   const char *name;
2576   gfc_try t;
2577   int temp;
2578   procedure_type p = PROC_INTRINSIC;
2579   bool no_formal_args;
2580
2581   sym = NULL;
2582   if (expr->symtree)
2583     sym = expr->symtree->n.sym;
2584
2585   /* If this is a procedure pointer component, it has already been resolved.  */
2586   if (gfc_is_proc_ptr_comp (expr, NULL))
2587     return SUCCESS;
2588   
2589   if (sym && sym->attr.intrinsic
2590       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2591     return FAILURE;
2592
2593   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2594     {
2595       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2596       return FAILURE;
2597     }
2598
2599   /* If this ia a deferred TBP with an abstract interface (which may
2600      of course be referenced), expr->value.function.esym will be set.  */
2601   if (sym && sym->attr.abstract && !expr->value.function.esym)
2602     {
2603       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2604                  sym->name, &expr->where);
2605       return FAILURE;
2606     }
2607
2608   /* Switch off assumed size checking and do this again for certain kinds
2609      of procedure, once the procedure itself is resolved.  */
2610   need_full_assumed_size++;
2611
2612   if (expr->symtree && expr->symtree->n.sym)
2613     p = expr->symtree->n.sym->attr.proc;
2614
2615   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2616     inquiry_argument = true;
2617   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2618
2619   if (resolve_actual_arglist (expr->value.function.actual,
2620                               p, no_formal_args) == FAILURE)
2621     {
2622       inquiry_argument = false;
2623       return FAILURE;
2624     }
2625
2626   inquiry_argument = false;
2627  
2628   /* Need to setup the call to the correct c_associated, depending on
2629      the number of cptrs to user gives to compare.  */
2630   if (sym && sym->attr.is_iso_c == 1)
2631     {
2632       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2633           == FAILURE)
2634         return FAILURE;
2635       
2636       /* Get the symtree for the new symbol (resolved func).
2637          the old one will be freed later, when it's no longer used.  */
2638       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2639     }
2640   
2641   /* Resume assumed_size checking.  */
2642   need_full_assumed_size--;
2643
2644   /* If the procedure is external, check for usage.  */
2645   if (sym && is_external_proc (sym))
2646     resolve_global_procedure (sym, &expr->where,
2647                               &expr->value.function.actual, 0);
2648
2649   if (sym && sym->ts.type == BT_CHARACTER
2650       && sym->ts.u.cl
2651       && sym->ts.u.cl->length == NULL
2652       && !sym->attr.dummy
2653       && expr->value.function.esym == NULL
2654       && !sym->attr.contained)
2655     {
2656       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2657       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2658                  "be used at %L since it is not a dummy argument",
2659                  sym->name, &expr->where);
2660       return FAILURE;
2661     }
2662
2663   /* See if function is already resolved.  */
2664
2665   if (expr->value.function.name != NULL)
2666     {
2667       if (expr->ts.type == BT_UNKNOWN)
2668         expr->ts = sym->ts;
2669       t = SUCCESS;
2670     }
2671   else
2672     {
2673       /* Apply the rules of section 14.1.2.  */
2674
2675       switch (procedure_kind (sym))
2676         {
2677         case PTYPE_GENERIC:
2678           t = resolve_generic_f (expr);
2679           break;
2680
2681         case PTYPE_SPECIFIC:
2682           t = resolve_specific_f (expr);
2683           break;
2684
2685         case PTYPE_UNKNOWN:
2686           t = resolve_unknown_f (expr);
2687           break;
2688
2689         default:
2690           gfc_internal_error ("resolve_function(): bad function type");
2691         }
2692     }
2693
2694   /* If the expression is still a function (it might have simplified),
2695      then we check to see if we are calling an elemental function.  */
2696
2697   if (expr->expr_type != EXPR_FUNCTION)
2698     return t;
2699
2700   temp = need_full_assumed_size;
2701   need_full_assumed_size = 0;
2702
2703   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2704     return FAILURE;
2705
2706   if (omp_workshare_flag
2707       && expr->value.function.esym
2708       && ! gfc_elemental (expr->value.function.esym))
2709     {
2710       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2711                  "in WORKSHARE construct", expr->value.function.esym->name,
2712                  &expr->where);
2713       t = FAILURE;
2714     }
2715
2716 #define GENERIC_ID expr->value.function.isym->id
2717   else if (expr->value.function.actual != NULL
2718            && expr->value.function.isym != NULL
2719            && GENERIC_ID != GFC_ISYM_LBOUND
2720            && GENERIC_ID != GFC_ISYM_LEN
2721            && GENERIC_ID != GFC_ISYM_LOC
2722            && GENERIC_ID != GFC_ISYM_PRESENT)
2723     {
2724       /* Array intrinsics must also have the last upper bound of an
2725          assumed size array argument.  UBOUND and SIZE have to be
2726          excluded from the check if the second argument is anything
2727          than a constant.  */
2728
2729       for (arg = expr->value.function.actual; arg; arg = arg->next)
2730         {
2731           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2732               && arg->next != NULL && arg->next->expr)
2733             {
2734               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2735                 break;
2736
2737               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2738                 break;
2739
2740               if ((int)mpz_get_si (arg->next->expr->value.integer)
2741                         < arg->expr->rank)
2742                 break;
2743             }
2744
2745           if (arg->expr != NULL
2746               && arg->expr->rank > 0
2747               && resolve_assumed_size_actual (arg->expr))
2748             return FAILURE;
2749         }
2750     }
2751 #undef GENERIC_ID
2752
2753   need_full_assumed_size = temp;
2754   name = NULL;
2755
2756   if (!pure_function (expr, &name) && name)
2757     {
2758       if (forall_flag)
2759         {
2760           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2761                      "FORALL %s", name, &expr->where,
2762                      forall_flag == 2 ? "mask" : "block");
2763           t = FAILURE;
2764         }
2765       else if (gfc_pure (NULL))
2766         {
2767           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2768                      "procedure within a PURE procedure", name, &expr->where);
2769           t = FAILURE;
2770         }
2771     }
2772
2773   /* Functions without the RECURSIVE attribution are not allowed to
2774    * call themselves.  */
2775   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2776     {
2777       gfc_symbol *esym;
2778       esym = expr->value.function.esym;
2779
2780       if (is_illegal_recursion (esym, gfc_current_ns))
2781       {
2782         if (esym->attr.entry && esym->ns->entries)
2783           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2784                      " function '%s' is not RECURSIVE",
2785                      esym->name, &expr->where, esym->ns->entries->sym->name);
2786         else
2787           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2788                      " is not RECURSIVE", esym->name, &expr->where);
2789
2790         t = FAILURE;
2791       }
2792     }
2793
2794   /* Character lengths of use associated functions may contains references to
2795      symbols not referenced from the current program unit otherwise.  Make sure
2796      those symbols are marked as referenced.  */
2797
2798   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2799       && expr->value.function.esym->attr.use_assoc)
2800     {
2801       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2802     }
2803
2804   if (t == SUCCESS
2805         && !((expr->value.function.esym
2806                 && expr->value.function.esym->attr.elemental)
2807                         ||
2808              (expr->value.function.isym
2809                 && expr->value.function.isym->elemental)))
2810     find_noncopying_intrinsics (expr->value.function.esym,
2811                                 expr->value.function.actual);
2812
2813   /* Make sure that the expression has a typespec that works.  */
2814   if (expr->ts.type == BT_UNKNOWN)
2815     {
2816       if (expr->symtree->n.sym->result
2817             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2818             && !expr->symtree->n.sym->result->attr.proc_pointer)
2819         expr->ts = expr->symtree->n.sym->result->ts;
2820     }
2821
2822   return t;
2823 }
2824
2825
2826 /************* Subroutine resolution *************/
2827
2828 static void
2829 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2830 {
2831   if (gfc_pure (sym))
2832     return;
2833
2834   if (forall_flag)
2835     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2836                sym->name, &c->loc);
2837   else if (gfc_pure (NULL))
2838     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2839                &c->loc);
2840 }
2841
2842
2843 static match
2844 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2845 {
2846   gfc_symbol *s;
2847
2848   if (sym->attr.generic)
2849     {
2850       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2851       if (s != NULL)
2852         {
2853           c->resolved_sym = s;
2854           pure_subroutine (c, s);
2855           return MATCH_YES;
2856         }
2857
2858       /* TODO: Need to search for elemental references in generic interface.  */
2859     }
2860
2861   if (sym->attr.intrinsic)
2862     return gfc_intrinsic_sub_interface (c, 0);
2863
2864   return MATCH_NO;
2865 }
2866
2867
2868 static gfc_try
2869 resolve_generic_s (gfc_code *c)
2870 {
2871   gfc_symbol *sym;
2872   match m;
2873
2874   sym = c->symtree->n.sym;
2875
2876   for (;;)
2877     {
2878       m = resolve_generic_s0 (c, sym);
2879       if (m == MATCH_YES)
2880         return SUCCESS;
2881       else if (m == MATCH_ERROR)
2882         return FAILURE;
2883
2884 generic:
2885       if (sym->ns->parent == NULL)
2886         break;
2887       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2888
2889       if (sym == NULL)
2890         break;
2891       if (!generic_sym (sym))
2892         goto generic;
2893     }
2894
2895   /* Last ditch attempt.  See if the reference is to an intrinsic
2896      that possesses a matching interface.  14.1.2.4  */
2897   sym = c->symtree->n.sym;
2898
2899   if (!gfc_is_intrinsic (sym, 1, c->loc))
2900     {
2901       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2902                  sym->name, &c->loc);
2903       return FAILURE;
2904     }
2905
2906   m = gfc_intrinsic_sub_interface (c, 0);
2907   if (m == MATCH_YES)
2908     return SUCCESS;
2909   if (m == MATCH_NO)
2910     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2911                "intrinsic subroutine interface", sym->name, &c->loc);
2912
2913   return FAILURE;
2914 }
2915
2916
2917 /* Set the name and binding label of the subroutine symbol in the call
2918    expression represented by 'c' to include the type and kind of the
2919    second parameter.  This function is for resolving the appropriate
2920    version of c_f_pointer() and c_f_procpointer().  For example, a
2921    call to c_f_pointer() for a default integer pointer could have a
2922    name of c_f_pointer_i4.  If no second arg exists, which is an error
2923    for these two functions, it defaults to the generic symbol's name
2924    and binding label.  */
2925
2926 static void
2927 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2928                     char *name, char *binding_label)
2929 {
2930   gfc_expr *arg = NULL;
2931   char type;
2932   int kind;
2933
2934   /* The second arg of c_f_pointer and c_f_procpointer determines
2935      the type and kind for the procedure name.  */
2936   arg = c->ext.actual->next->expr;
2937
2938   if (arg != NULL)
2939     {
2940       /* Set up the name to have the given symbol's name,
2941          plus the type and kind.  */
2942       /* a derived type is marked with the type letter 'u' */
2943       if (arg->ts.type == BT_DERIVED)
2944         {
2945           type = 'd';
2946           kind = 0; /* set the kind as 0 for now */
2947         }
2948       else
2949         {
2950           type = gfc_type_letter (arg->ts.type);
2951           kind = arg->ts.kind;
2952         }
2953
2954       if (arg->ts.type == BT_CHARACTER)
2955         /* Kind info for character strings not needed.  */
2956         kind = 0;
2957
2958       sprintf (name, "%s_%c%d", sym->name, type, kind);
2959       /* Set up the binding label as the given symbol's label plus
2960          the type and kind.  */
2961       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2962     }
2963   else
2964     {
2965       /* If the second arg is missing, set the name and label as
2966          was, cause it should at least be found, and the missing
2967          arg error will be caught by compare_parameters().  */
2968       sprintf (name, "%s", sym->name);
2969       sprintf (binding_label, "%s", sym->binding_label);
2970     }
2971    
2972   return;
2973 }
2974
2975
2976 /* Resolve a generic version of the iso_c_binding procedure given
2977    (sym) to the specific one based on the type and kind of the
2978    argument(s).  Currently, this function resolves c_f_pointer() and
2979    c_f_procpointer based on the type and kind of the second argument
2980    (FPTR).  Other iso_c_binding procedures aren't specially handled.
2981    Upon successfully exiting, c->resolved_sym will hold the resolved
2982    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
2983    otherwise.  */
2984
2985 match
2986 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2987 {
2988   gfc_symbol *new_sym;
2989   /* this is fine, since we know the names won't use the max */
2990   char name[GFC_MAX_SYMBOL_LEN + 1];
2991   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2992   /* default to success; will override if find error */
2993   match m = MATCH_YES;
2994
2995   /* Make sure the actual arguments are in the necessary order (based on the 
2996      formal args) before resolving.  */
2997   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2998
2999   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3000       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3001     {
3002       set_name_and_label (c, sym, name, binding_label);
3003       
3004       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3005         {
3006           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3007             {
3008               /* Make sure we got a third arg if the second arg has non-zero
3009                  rank.  We must also check that the type and rank are
3010                  correct since we short-circuit this check in
3011                  gfc_procedure_use() (called above to sort actual args).  */
3012               if (c->ext.actual->next->expr->rank != 0)
3013                 {
3014                   if(c->ext.actual->next->next == NULL 
3015                      || c->ext.actual->next->next->expr == NULL)
3016                     {
3017                       m = MATCH_ERROR;
3018                       gfc_error ("Missing SHAPE parameter for call to %s "
3019                                  "at %L", sym->name, &(c->loc));
3020                     }
3021                   else if (c->ext.actual->next->next->expr->ts.type
3022                            != BT_INTEGER
3023                            || c->ext.actual->next->next->expr->rank != 1)
3024                     {
3025                       m = MATCH_ERROR;
3026                       gfc_error ("SHAPE parameter for call to %s at %L must "
3027                                  "be a rank 1 INTEGER array", sym->name,
3028                                  &(c->loc));
3029                     }
3030                 }
3031             }
3032         }
3033       
3034       if (m != MATCH_ERROR)
3035         {
3036           /* the 1 means to add the optional arg to formal list */
3037           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3038          
3039           /* for error reporting, say it's declared where the original was */
3040           new_sym->declared_at = sym->declared_at;
3041         }
3042     }
3043   else
3044     {
3045       /* no differences for c_loc or c_funloc */
3046       new_sym = sym;
3047     }
3048
3049   /* set the resolved symbol */
3050   if (m != MATCH_ERROR)
3051     c->resolved_sym = new_sym;
3052   else
3053     c->resolved_sym = sym;
3054   
3055   return m;
3056 }
3057
3058
3059 /* Resolve a subroutine call known to be specific.  */
3060
3061 static match
3062 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3063 {
3064   match m;
3065
3066   if(sym->attr.is_iso_c)
3067     {
3068       m = gfc_iso_c_sub_interface (c,sym);
3069       return m;
3070     }
3071   
3072   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3073     {
3074       if (sym->attr.dummy)
3075         {
3076           sym->attr.proc = PROC_DUMMY;
3077           goto found;
3078         }
3079
3080       sym->attr.proc = PROC_EXTERNAL;
3081       goto found;
3082     }
3083
3084   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3085     goto found;
3086
3087   if (sym->attr.intrinsic)
3088     {
3089       m = gfc_intrinsic_sub_interface (c, 1);
3090       if (m == MATCH_YES)
3091         return MATCH_YES;
3092       if (m == MATCH_NO)
3093         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3094                    "with an intrinsic", sym->name, &c->loc);
3095
3096       return MATCH_ERROR;
3097     }
3098
3099   return MATCH_NO;
3100
3101 found:
3102   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3103
3104   c->resolved_sym = sym;
3105   pure_subroutine (c, sym);
3106
3107   return MATCH_YES;
3108 }
3109
3110
3111 static gfc_try
3112 resolve_specific_s (gfc_code *c)
3113 {
3114   gfc_symbol *sym;
3115   match m;
3116
3117   sym = c->symtree->n.sym;
3118
3119   for (;;)
3120     {
3121       m = resolve_specific_s0 (c, sym);
3122       if (m == MATCH_YES)
3123         return SUCCESS;
3124       if (m == MATCH_ERROR)
3125         return FAILURE;
3126
3127       if (sym->ns->parent == NULL)
3128         break;
3129
3130       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3131
3132       if (sym == NULL)
3133         break;
3134     }
3135
3136   sym = c->symtree->n.sym;
3137   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3138              sym->name, &c->loc);
3139
3140   return FAILURE;
3141 }
3142
3143
3144 /* Resolve a subroutine call not known to be generic nor specific.  */
3145
3146 static gfc_try
3147 resolve_unknown_s (gfc_code *c)
3148 {
3149   gfc_symbol *sym;
3150
3151   sym = c->symtree->n.sym;
3152
3153   if (sym->attr.dummy)
3154     {
3155       sym->attr.proc = PROC_DUMMY;
3156       goto found;
3157     }
3158
3159   /* See if we have an intrinsic function reference.  */
3160
3161   if (gfc_is_intrinsic (sym, 1, c->loc))
3162     {
3163       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3164         return SUCCESS;
3165       return FAILURE;
3166     }
3167
3168   /* The reference is to an external name.  */
3169
3170 found:
3171   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3172
3173   c->resolved_sym = sym;
3174
3175   pure_subroutine (c, sym);
3176
3177   return SUCCESS;
3178 }
3179
3180
3181 /* Resolve a subroutine call.  Although it was tempting to use the same code
3182    for functions, subroutines and functions are stored differently and this
3183    makes things awkward.  */
3184
3185 static gfc_try
3186 resolve_call (gfc_code *c)
3187 {
3188   gfc_try t;
3189   procedure_type ptype = PROC_INTRINSIC;
3190   gfc_symbol *csym, *sym;
3191   bool no_formal_args;
3192
3193   csym = c->symtree ? c->symtree->n.sym : NULL;
3194
3195   if (csym && csym->ts.type != BT_UNKNOWN)
3196     {
3197       gfc_error ("'%s' at %L has a type, which is not consistent with "
3198                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3199       return FAILURE;
3200     }
3201
3202   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3203     {
3204       gfc_symtree *st;
3205       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3206       sym = st ? st->n.sym : NULL;
3207       if (sym && csym != sym
3208               && sym->ns == gfc_current_ns
3209               && sym->attr.flavor == FL_PROCEDURE
3210               && sym->attr.contained)
3211         {
3212           sym->refs++;
3213           if (csym->attr.generic)
3214             c->symtree->n.sym = sym;
3215           else
3216             c->symtree = st;
3217           csym = c->symtree->n.sym;
3218         }
3219     }
3220
3221   /* If this ia a deferred TBP with an abstract interface
3222      (which may of course be referenced), c->expr1 will be set.  */
3223   if (csym && csym->attr.abstract && !c->expr1)
3224     {
3225       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3226                  csym->name, &c->loc);
3227       return FAILURE;
3228     }
3229
3230   /* Subroutines without the RECURSIVE attribution are not allowed to
3231    * call themselves.  */
3232   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3233     {
3234       if (csym->attr.entry && csym->ns->entries)
3235         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3236                    " subroutine '%s' is not RECURSIVE",
3237                    csym->name, &c->loc, csym->ns->entries->sym->name);
3238       else
3239         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3240                    " is not RECURSIVE", csym->name, &c->loc);
3241
3242       t = FAILURE;
3243     }
3244
3245   /* Switch off assumed size checking and do this again for certain kinds
3246      of procedure, once the procedure itself is resolved.  */
3247   need_full_assumed_size++;
3248
3249   if (csym)
3250     ptype = csym->attr.proc;
3251
3252   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3253   if (resolve_actual_arglist (c->ext.actual, ptype,
3254                               no_formal_args) == FAILURE)
3255     return FAILURE;
3256
3257   /* Resume assumed_size checking.  */
3258   need_full_assumed_size--;
3259
3260   /* If external, check for usage.  */
3261   if (csym && is_external_proc (csym))
3262     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3263
3264   t = SUCCESS;
3265   if (c->resolved_sym == NULL)
3266     {
3267       c->resolved_isym = NULL;
3268       switch (procedure_kind (csym))
3269         {
3270         case PTYPE_GENERIC:
3271           t = resolve_generic_s (c);
3272           break;
3273
3274         case PTYPE_SPECIFIC:
3275           t = resolve_specific_s (c);
3276           break;
3277
3278         case PTYPE_UNKNOWN:
3279           t = resolve_unknown_s (c);
3280           break;
3281
3282         default:
3283           gfc_internal_error ("resolve_subroutine(): bad function type");
3284         }
3285     }
3286
3287   /* Some checks of elemental subroutine actual arguments.  */
3288   if (resolve_elemental_actual (NULL, c) == FAILURE)
3289     return FAILURE;
3290
3291   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3292     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3293   return t;
3294 }
3295
3296
3297 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3298    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3299    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3300    if their shapes do not match.  If either op1->shape or op2->shape is
3301    NULL, return SUCCESS.  */
3302
3303 static gfc_try
3304 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3305 {
3306   gfc_try t;
3307   int i;
3308
3309   t = SUCCESS;
3310
3311   if (op1->shape != NULL && op2->shape != NULL)
3312     {
3313       for (i = 0; i < op1->rank; i++)
3314         {
3315           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3316            {
3317              gfc_error ("Shapes for operands at %L and %L are not conformable",
3318                          &op1->where, &op2->where);
3319              t = FAILURE;
3320              break;
3321            }
3322         }
3323     }
3324
3325   return t;
3326 }
3327
3328
3329 /* Resolve an operator expression node.  This can involve replacing the
3330    operation with a user defined function call.  */
3331
3332 static gfc_try
3333 resolve_operator (gfc_expr *e)
3334 {
3335   gfc_expr *op1, *op2;
3336   char msg[200];
3337   bool dual_locus_error;
3338   gfc_try t;
3339
3340   /* Resolve all subnodes-- give them types.  */
3341
3342   switch (e->value.op.op)
3343     {
3344     default:
3345       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3346         return FAILURE;
3347
3348     /* Fall through...  */
3349
3350     case INTRINSIC_NOT:
3351     case INTRINSIC_UPLUS:
3352     case INTRINSIC_UMINUS:
3353     case INTRINSIC_PARENTHESES:
3354       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3355         return FAILURE;
3356       break;
3357     }
3358
3359   /* Typecheck the new node.  */
3360
3361   op1 = e->value.op.op1;
3362   op2 = e->value.op.op2;
3363   dual_locus_error = false;
3364
3365   if ((op1 && op1->expr_type == EXPR_NULL)
3366       || (op2 && op2->expr_type == EXPR_NULL))
3367     {
3368       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3369       goto bad_op;
3370     }
3371
3372   switch (e->value.op.op)
3373     {
3374     case INTRINSIC_UPLUS:
3375     case INTRINSIC_UMINUS:
3376       if (op1->ts.type == BT_INTEGER
3377           || op1->ts.type == BT_REAL
3378           || op1->ts.type == BT_COMPLEX)
3379         {
3380           e->ts = op1->ts;
3381           break;
3382         }
3383
3384       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3385                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3386       goto bad_op;
3387
3388     case INTRINSIC_PLUS:
3389     case INTRINSIC_MINUS:
3390     case INTRINSIC_TIMES:
3391     case INTRINSIC_DIVIDE:
3392     case INTRINSIC_POWER:
3393       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3394         {
3395           gfc_type_convert_binary (e, 1);
3396           break;
3397         }
3398
3399       sprintf (msg,
3400                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3401                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3402                gfc_typename (&op2->ts));
3403       goto bad_op;
3404
3405     case INTRINSIC_CONCAT:
3406       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3407           && op1->ts.kind == op2->ts.kind)
3408         {
3409           e->ts.type = BT_CHARACTER;
3410           e->ts.kind = op1->ts.kind;
3411           break;
3412         }
3413
3414       sprintf (msg,
3415                _("Operands of string concatenation operator at %%L are %s/%s"),
3416                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3417       goto bad_op;
3418
3419     case INTRINSIC_AND:
3420     case INTRINSIC_OR:
3421     case INTRINSIC_EQV:
3422     case INTRINSIC_NEQV:
3423       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3424         {
3425           e->ts.type = BT_LOGICAL;
3426           e->ts.kind = gfc_kind_max (op1, op2);
3427           if (op1->ts.kind < e->ts.kind)
3428             gfc_convert_type (op1, &e->ts, 2);
3429           else if (op2->ts.kind < e->ts.kind)
3430             gfc_convert_type (op2, &e->ts, 2);
3431           break;
3432         }
3433
3434       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3435                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3436                gfc_typename (&op2->ts));
3437
3438       goto bad_op;
3439
3440     case INTRINSIC_NOT:
3441       if (op1->ts.type == BT_LOGICAL)
3442         {
3443           e->ts.type = BT_LOGICAL;
3444           e->ts.kind = op1->ts.kind;
3445           break;
3446         }
3447
3448       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3449                gfc_typename (&op1->ts));
3450       goto bad_op;
3451
3452     case INTRINSIC_GT:
3453     case INTRINSIC_GT_OS:
3454     case INTRINSIC_GE:
3455     case INTRINSIC_GE_OS:
3456     case INTRINSIC_LT:
3457     case INTRINSIC_LT_OS:
3458     case INTRINSIC_LE:
3459     case INTRINSIC_LE_OS:
3460       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3461         {
3462           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3463           goto bad_op;
3464         }
3465
3466       /* Fall through...  */
3467
3468     case INTRINSIC_EQ:
3469     case INTRINSIC_EQ_OS:
3470     case INTRINSIC_NE:
3471     case INTRINSIC_NE_OS:
3472       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3473           && op1->ts.kind == op2->ts.kind)
3474         {
3475           e->ts.type = BT_LOGICAL;
3476           e->ts.kind = gfc_default_logical_kind;
3477           break;
3478         }
3479
3480       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3481         {
3482           gfc_type_convert_binary (e, 1);
3483
3484           e->ts.type = BT_LOGICAL;
3485           e->ts.kind = gfc_default_logical_kind;
3486           break;
3487         }
3488
3489       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3490         sprintf (msg,
3491                  _("Logicals at %%L must be compared with %s instead of %s"),
3492                  (e->value.op.op == INTRINSIC_EQ 
3493                   || e->value.op.op == INTRINSIC_EQ_OS)
3494                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3495       else
3496         sprintf (msg,
3497                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3498                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3499                  gfc_typename (&op2->ts));
3500
3501       goto bad_op;
3502
3503     case INTRINSIC_USER:
3504       if (e->value.op.uop->op == NULL)
3505         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3506       else if (op2 == NULL)
3507         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3508                  e->value.op.uop->name, gfc_typename (&op1->ts));
3509       else
3510         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3511                  e->value.op.uop->name, gfc_typename (&op1->ts),
3512                  gfc_typename (&op2->ts));
3513
3514       goto bad_op;
3515
3516     case INTRINSIC_PARENTHESES:
3517       e->ts = op1->ts;
3518       if (e->ts.type == BT_CHARACTER)
3519         e->ts.u.cl = op1->ts.u.cl;
3520       break;
3521
3522     default:
3523       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3524     }
3525
3526   /* Deal with arrayness of an operand through an operator.  */
3527
3528   t = SUCCESS;
3529
3530   switch (e->value.op.op)
3531     {
3532     case INTRINSIC_PLUS:
3533     case INTRINSIC_MINUS:
3534     case INTRINSIC_TIMES:
3535     case INTRINSIC_DIVIDE:
3536     case INTRINSIC_POWER:
3537     case INTRINSIC_CONCAT:
3538     case INTRINSIC_AND:
3539     case INTRINSIC_OR:
3540     case INTRINSIC_EQV:
3541     case INTRINSIC_NEQV:
3542     case INTRINSIC_EQ:
3543     case INTRINSIC_EQ_OS:
3544     case INTRINSIC_NE:
3545     case INTRINSIC_NE_OS:
3546     case INTRINSIC_GT:
3547     case INTRINSIC_GT_OS:
3548     case INTRINSIC_GE:
3549     case INTRINSIC_GE_OS:
3550     case INTRINSIC_LT:
3551     case INTRINSIC_LT_OS:
3552     case INTRINSIC_LE:
3553     case INTRINSIC_LE_OS:
3554
3555       if (op1->rank == 0 && op2->rank == 0)
3556         e->rank = 0;
3557
3558       if (op1->rank == 0 && op2->rank != 0)
3559         {
3560           e->rank = op2->rank;
3561
3562           if (e->shape == NULL)
3563             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3564         }
3565
3566       if (op1->rank != 0 && op2->rank == 0)
3567         {
3568           e->rank = op1->rank;
3569
3570           if (e->shape == NULL)
3571             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3572         }
3573
3574       if (op1->rank != 0 && op2->rank != 0)
3575         {
3576           if (op1->rank == op2->rank)
3577             {
3578               e->rank = op1->rank;
3579               if (e->shape == NULL)
3580                 {
3581                   t = compare_shapes(op1, op2);
3582                   if (t == FAILURE)
3583                     e->shape = NULL;
3584                   else
3585                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3586                 }
3587             }
3588           else
3589             {
3590               /* Allow higher level expressions to work.  */
3591               e->rank = 0;
3592
3593               /* Try user-defined operators, and otherwise throw an error.  */
3594               dual_locus_error = true;
3595               sprintf (msg,
3596                        _("Inconsistent ranks for operator at %%L and %%L"));
3597               goto bad_op;
3598             }
3599         }
3600
3601       break;
3602
3603     case INTRINSIC_PARENTHESES:
3604     case INTRINSIC_NOT:
3605     case INTRINSIC_UPLUS:
3606     case INTRINSIC_UMINUS:
3607       /* Simply copy arrayness attribute */
3608       e->rank = op1->rank;
3609
3610       if (e->shape == NULL)
3611         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3612
3613       break;
3614
3615     default:
3616       break;
3617     }
3618
3619   /* Attempt to simplify the expression.  */
3620   if (t == SUCCESS)
3621     {
3622       t = gfc_simplify_expr (e, 0);
3623       /* Some calls do not succeed in simplification and return FAILURE
3624          even though there is no error; e.g. variable references to
3625          PARAMETER arrays.  */
3626       if (!gfc_is_constant_expr (e))
3627         t = SUCCESS;
3628     }
3629   return t;
3630
3631 bad_op:
3632
3633   {
3634     bool real_error;
3635     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3636       return SUCCESS;
3637
3638     if (real_error)
3639       return FAILURE;
3640   }
3641
3642   if (dual_locus_error)
3643     gfc_error (msg, &op1->where, &op2->where);
3644   else
3645     gfc_error (msg, &e->where);
3646
3647   return FAILURE;
3648 }
3649
3650
3651 /************** Array resolution subroutines **************/
3652
3653 typedef enum
3654 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3655 comparison;
3656
3657 /* Compare two integer expressions.  */
3658
3659 static comparison
3660 compare_bound (gfc_expr *a, gfc_expr *b)
3661 {
3662   int i;
3663
3664   if (a == NULL || a->expr_type != EXPR_CONSTANT
3665       || b == NULL || b->expr_type != EXPR_CONSTANT)
3666     return CMP_UNKNOWN;
3667
3668   /* If either of the types isn't INTEGER, we must have
3669      raised an error earlier.  */
3670
3671   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3672     return CMP_UNKNOWN;
3673
3674   i = mpz_cmp (a->value.integer, b->value.integer);
3675
3676   if (i < 0)
3677     return CMP_LT;
3678   if (i > 0)
3679     return CMP_GT;
3680   return CMP_EQ;
3681 }
3682
3683
3684 /* Compare an integer expression with an integer.  */
3685
3686 static comparison
3687 compare_bound_int (gfc_expr *a, int b)
3688 {
3689   int i;
3690
3691   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3692     return CMP_UNKNOWN;
3693
3694   if (a->ts.type != BT_INTEGER)
3695     gfc_internal_error ("compare_bound_int(): Bad expression");
3696
3697   i = mpz_cmp_si (a->value.integer, b);
3698
3699   if (i < 0)
3700     return CMP_LT;
3701   if (i > 0)
3702     return CMP_GT;
3703   return CMP_EQ;
3704 }
3705
3706
3707 /* Compare an integer expression with a mpz_t.  */
3708
3709 static comparison
3710 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3711 {
3712   int i;
3713
3714   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3715     return CMP_UNKNOWN;
3716
3717   if (a->ts.type != BT_INTEGER)
3718     gfc_internal_error ("compare_bound_int(): Bad expression");
3719
3720   i = mpz_cmp (a->value.integer, b);
3721
3722   if (i < 0)
3723     return CMP_LT;
3724   if (i > 0)
3725     return CMP_GT;
3726   return CMP_EQ;
3727 }
3728
3729
3730 /* Compute the last value of a sequence given by a triplet.  
3731    Return 0 if it wasn't able to compute the last value, or if the
3732    sequence if empty, and 1 otherwise.  */
3733
3734 static int
3735 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3736                                 gfc_expr *stride, mpz_t last)
3737 {
3738   mpz_t rem;
3739
3740   if (start == NULL || start->expr_type != EXPR_CONSTANT
3741       || end == NULL || end->expr_type != EXPR_CONSTANT
3742       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3743     return 0;
3744
3745   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3746       || (stride != NULL && stride->ts.type != BT_INTEGER))
3747     return 0;
3748
3749   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3750     {
3751       if (compare_bound (start, end) == CMP_GT)
3752         return 0;
3753       mpz_set (last, end->value.integer);
3754       return 1;
3755     }
3756
3757   if (compare_bound_int (stride, 0) == CMP_GT)
3758     {
3759       /* Stride is positive */
3760       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3761         return 0;
3762     }
3763   else
3764     {
3765       /* Stride is negative */
3766       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3767         return 0;
3768     }
3769
3770   mpz_init (rem);
3771   mpz_sub (rem, end->value.integer, start->value.integer);
3772   mpz_tdiv_r (rem, rem, stride->value.integer);
3773   mpz_sub (last, end->value.integer, rem);
3774   mpz_clear (rem);
3775
3776   return 1;
3777 }
3778
3779
3780 /* Compare a single dimension of an array reference to the array
3781    specification.  */
3782
3783 static gfc_try
3784 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3785 {
3786   mpz_t last_value;
3787
3788   if (ar->dimen_type[i] == DIMEN_STAR)
3789     {
3790       gcc_assert (ar->stride[i] == NULL);
3791       /* This implies [*] as [*:] and [*:3] are not possible.  */
3792       if (ar->start[i] == NULL)
3793         {
3794           gcc_assert (ar->end[i] == NULL);
3795           return SUCCESS;
3796         }
3797     }
3798
3799 /* Given start, end and stride values, calculate the minimum and
3800    maximum referenced indexes.  */
3801
3802   switch (ar->dimen_type[i])
3803     {
3804     case DIMEN_VECTOR:
3805       break;
3806
3807     case DIMEN_STAR:
3808     case DIMEN_ELEMENT:
3809       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3810         {
3811           if (i < as->rank)
3812             gfc_warning ("Array reference at %L is out of bounds "
3813                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
3814                          mpz_get_si (ar->start[i]->value.integer),
3815                          mpz_get_si (as->lower[i]->value.integer), i+1);
3816           else
3817             gfc_warning ("Array reference at %L is out of bounds "
3818                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
3819                          mpz_get_si (ar->start[i]->value.integer),
3820                          mpz_get_si (as->lower[i]->value.integer),
3821                          i + 1 - as->rank);
3822           return SUCCESS;
3823         }
3824       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3825         {
3826           if (i < as->rank)
3827             gfc_warning ("Array reference at %L is out of bounds "
3828                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
3829                          mpz_get_si (ar->start[i]->value.integer),
3830                          mpz_get_si (as->upper[i]->value.integer), i+1);
3831           else
3832             gfc_warning ("Array reference at %L is out of bounds "
3833                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
3834                          mpz_get_si (ar->start[i]->value.integer),
3835                          mpz_get_si (as->upper[i]->value.integer),
3836                          i + 1 - as->rank);
3837           return SUCCESS;
3838         }
3839
3840       break;
3841
3842     case DIMEN_RANGE:
3843       {
3844 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3845 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3846
3847         comparison comp_start_end = compare_bound (AR_START, AR_END);
3848
3849         /* Check for zero stride, which is not allowed.  */
3850         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3851           {
3852             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3853             return FAILURE;
3854           }
3855
3856         /* if start == len || (stride > 0 && start < len)
3857                            || (stride < 0 && start > len),
3858            then the array section contains at least one element.  In this
3859            case, there is an out-of-bounds access if
3860            (start < lower || start > upper).  */
3861         if (compare_bound (AR_START, AR_END) == CMP_EQ
3862             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3863                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3864             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3865                 && comp_start_end == CMP_GT))
3866           {
3867             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3868               {
3869                 gfc_warning ("Lower array reference at %L is out of bounds "
3870                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3871                        mpz_get_si (AR_START->value.integer),
3872                        mpz_get_si (as->lower[i]->value.integer), i+1);
3873                 return SUCCESS;
3874               }
3875             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3876               {
3877                 gfc_warning ("Lower array reference at %L is out of bounds "
3878                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3879                        mpz_get_si (AR_START->value.integer),
3880                        mpz_get_si (as->upper[i]->value.integer), i+1);
3881                 return SUCCESS;
3882               }
3883           }
3884
3885         /* If we can compute the highest index of the array section,
3886            then it also has to be between lower and upper.  */
3887         mpz_init (last_value);
3888         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3889                                             last_value))
3890           {
3891             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3892               {
3893                 gfc_warning ("Upper array reference at %L is out of bounds "
3894                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3895                        mpz_get_si (last_value),
3896                        mpz_get_si (as->lower[i]->value.integer), i+1);
3897                 mpz_clear (last_value);
3898                 return SUCCESS;
3899               }
3900             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3901               {
3902                 gfc_warning ("Upper array reference at %L is out of bounds "
3903                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3904                        mpz_get_si (last_value),
3905                        mpz_get_si (as->upper[i]->value.integer), i+1);
3906                 mpz_clear (last_value);
3907                 return SUCCESS;
3908               }
3909           }
3910         mpz_clear (last_value);
3911
3912 #undef AR_START
3913 #undef AR_END
3914       }
3915       break;
3916
3917     default:
3918       gfc_internal_error ("check_dimension(): Bad array reference");
3919     }
3920
3921   return SUCCESS;
3922 }
3923
3924
3925 /* Compare an array reference with an array specification.  */
3926
3927 static gfc_try
3928 compare_spec_to_ref (gfc_array_ref *ar)
3929 {
3930   gfc_array_spec *as;
3931   int i;
3932
3933   as = ar->as;
3934   i = as->rank - 1;
3935   /* TODO: Full array sections are only allowed as actual parameters.  */
3936   if (as->type == AS_ASSUMED_SIZE
3937       && (/*ar->type == AR_FULL
3938           ||*/ (ar->type == AR_SECTION
3939               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3940     {
3941       gfc_error ("Rightmost upper bound of assumed size array section "
3942                  "not specified at %L", &ar->where);
3943       return FAILURE;
3944     }
3945
3946   if (ar->type == AR_FULL)
3947     return SUCCESS;
3948
3949   if (as->rank != ar->dimen)
3950     {
3951       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3952                  &ar->where, ar->dimen, as->rank);
3953       return FAILURE;
3954     }
3955
3956   /* ar->codimen == 0 is a local array.  */
3957   if (as->corank != ar->codimen && ar->codimen != 0)
3958     {
3959       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
3960                  &ar->where, ar->codimen, as->corank);
3961       return FAILURE;
3962     }
3963
3964   for (i = 0; i < as->rank; i++)
3965     if (check_dimension (i, ar, as) == FAILURE)
3966       return FAILURE;
3967
3968   /* Local access has no coarray spec.  */
3969   if (ar->codimen != 0)
3970     for (i = as->rank; i < as->rank + as->corank; i++)
3971       {
3972         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
3973           {
3974             gfc_error ("Coindex of codimension %d must be a scalar at %L",
3975                        i + 1 - as->rank, &ar->where);
3976             return FAILURE;
3977           }
3978         if (check_dimension (i, ar, as) == FAILURE)
3979           return FAILURE;
3980       }
3981
3982   return SUCCESS;
3983 }
3984
3985
3986 /* Resolve one part of an array index.  */
3987
3988 static gfc_try
3989 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
3990                      int force_index_integer_kind)
3991 {
3992   gfc_typespec ts;
3993
3994   if (index == NULL)
3995     return SUCCESS;
3996
3997   if (gfc_resolve_expr (index) == FAILURE)
3998     return FAILURE;
3999
4000   if (check_scalar && index->rank != 0)
4001     {
4002       gfc_error ("Array index at %L must be scalar", &index->where);
4003       return FAILURE;
4004     }
4005
4006   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4007     {
4008       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4009                  &index->where, gfc_basic_typename (index->ts.type));
4010       return FAILURE;
4011     }
4012
4013   if (index->ts.type == BT_REAL)
4014     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4015                         &index->where) == FAILURE)
4016       return FAILURE;
4017
4018   if ((index->ts.kind != gfc_index_integer_kind
4019        && force_index_integer_kind)
4020       || index->ts.type != BT_INTEGER)
4021     {
4022       gfc_clear_ts (&ts);
4023       ts.type = BT_INTEGER;
4024       ts.kind = gfc_index_integer_kind;
4025
4026       gfc_convert_type_warn (index, &ts, 2, 0);
4027     }
4028
4029   return SUCCESS;
4030 }
4031
4032 /* Resolve one part of an array index.  */
4033
4034 gfc_try
4035 gfc_resolve_index (gfc_expr *index, int check_scalar)
4036 {
4037   return gfc_resolve_index_1 (index, check_scalar, 1);
4038 }
4039
4040 /* Resolve a dim argument to an intrinsic function.  */
4041
4042 gfc_try
4043 gfc_resolve_dim_arg (gfc_expr *dim)
4044 {
4045   if (dim == NULL)
4046     return SUCCESS;
4047
4048   if (gfc_resolve_expr (dim) == FAILURE)
4049     return FAILURE;
4050
4051   if (dim->rank != 0)
4052     {
4053       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4054       return FAILURE;
4055
4056     }
4057
4058   if (dim->ts.type != BT_INTEGER)
4059     {
4060       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4061       return FAILURE;
4062     }
4063
4064   if (dim->ts.kind != gfc_index_integer_kind)
4065     {
4066       gfc_typespec ts;
4067
4068       gfc_clear_ts (&ts);
4069       ts.type = BT_INTEGER;
4070       ts.kind = gfc_index_integer_kind;
4071
4072       gfc_convert_type_warn (dim, &ts, 2, 0);
4073     }
4074
4075   return SUCCESS;
4076 }
4077
4078 /* Given an expression that contains array references, update those array
4079    references to point to the right array specifications.  While this is
4080    filled in during matching, this information is difficult to save and load
4081    in a module, so we take care of it here.
4082
4083    The idea here is that the original array reference comes from the
4084    base symbol.  We traverse the list of reference structures, setting
4085    the stored reference to references.  Component references can
4086    provide an additional array specification.  */
4087
4088 static void
4089 find_array_spec (gfc_expr *e)
4090 {
4091   gfc_array_spec *as;
4092   gfc_component *c;
4093   gfc_symbol *derived;
4094   gfc_ref *ref;
4095
4096   if (e->symtree->n.sym->ts.type == BT_CLASS)
4097     as = e->symtree->n.sym->ts.u.derived->components->as;
4098   else
4099     as = e->symtree->n.sym->as;
4100   derived = NULL;
4101
4102   for (ref = e->ref; ref; ref = ref->next)
4103     switch (ref->type)
4104       {
4105       case REF_ARRAY:
4106         if (as == NULL)
4107           gfc_internal_error ("find_array_spec(): Missing spec");
4108
4109         ref->u.ar.as = as;
4110         as = NULL;
4111         break;
4112
4113       case REF_COMPONENT:
4114         if (derived == NULL)
4115           derived = e->symtree->n.sym->ts.u.derived;
4116
4117         if (derived->attr.is_class)
4118           derived = derived->components->ts.u.derived;
4119
4120         c = derived->components;
4121
4122         for (; c; c = c->next)
4123           if (c == ref->u.c.component)
4124             {
4125               /* Track the sequence of component references.  */
4126               if (c->ts.type == BT_DERIVED)
4127                 derived = c->ts.u.derived;
4128               break;
4129             }
4130
4131         if (c == NULL)
4132           gfc_internal_error ("find_array_spec(): Component not found");
4133
4134         if (c->attr.dimension)
4135           {
4136             if (as != NULL)
4137               gfc_internal_error ("find_array_spec(): unused as(1)");
4138             as = c->as;
4139           }
4140
4141         break;
4142
4143       case REF_SUBSTRING:
4144         break;
4145       }
4146
4147   if (as != NULL)
4148     gfc_internal_error ("find_array_spec(): unused as(2)");
4149 }
4150
4151
4152 /* Resolve an array reference.  */
4153
4154 static gfc_try
4155 resolve_array_ref (gfc_array_ref *ar)
4156 {
4157   int i, check_scalar;
4158   gfc_expr *e;
4159
4160   for (i = 0; i < ar->dimen + ar->codimen; i++)
4161     {
4162       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4163
4164       /* Do not force gfc_index_integer_kind for the start.  We can
4165          do fine with any integer kind.  This avoids temporary arrays
4166          created for indexing with a vector.  */
4167       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4168         return FAILURE;
4169       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4170         return FAILURE;
4171       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4172         return FAILURE;
4173
4174       e = ar->start[i];
4175
4176       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4177         switch (e->rank)
4178           {
4179           case 0:
4180             ar->dimen_type[i] = DIMEN_ELEMENT;
4181             break;
4182
4183           case 1:
4184             ar->dimen_type[i] = DIMEN_VECTOR;
4185             if (e->expr_type == EXPR_VARIABLE
4186                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4187               ar->start[i] = gfc_get_parentheses (e);
4188             break;
4189
4190           default:
4191             gfc_error ("Array index at %L is an array of rank %d",
4192                        &ar->c_where[i], e->rank);
4193             return FAILURE;
4194           }
4195     }
4196
4197   if (ar->type == AR_FULL && ar->as->rank == 0)
4198     ar->type = AR_ELEMENT;
4199
4200   /* If the reference type is unknown, figure out what kind it is.  */
4201
4202   if (ar->type == AR_UNKNOWN)
4203     {
4204       ar->type = AR_ELEMENT;
4205       for (i = 0; i < ar->dimen; i++)
4206         if (ar->dimen_type[i] == DIMEN_RANGE
4207             || ar->dimen_type[i] == DIMEN_VECTOR)
4208           {
4209             ar->type = AR_SECTION;
4210             break;
4211           }
4212     }
4213
4214   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4215     return FAILURE;
4216
4217   return SUCCESS;
4218 }
4219
4220
4221 static gfc_try
4222 resolve_substring (gfc_ref *ref)
4223 {
4224   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4225
4226   if (ref->u.ss.start != NULL)
4227     {
4228       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4229         return FAILURE;
4230
4231       if (ref->u.ss.start->ts.type != BT_INTEGER)
4232         {
4233           gfc_error ("Substring start index at %L must be of type INTEGER",
4234                      &ref->u.ss.start->where);
4235           return FAILURE;
4236         }
4237
4238       if (ref->u.ss.start->rank != 0)
4239         {
4240           gfc_error ("Substring start index at %L must be scalar",
4241                      &ref->u.ss.start->where);
4242           return FAILURE;
4243         }
4244
4245       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4246           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4247               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4248         {
4249           gfc_error ("Substring start index at %L is less than one",
4250                      &ref->u.ss.start->where);
4251           return FAILURE;
4252         }
4253     }
4254
4255   if (ref->u.ss.end != NULL)
4256     {
4257       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4258         return FAILURE;
4259
4260       if (ref->u.ss.end->ts.type != BT_INTEGER)
4261         {
4262           gfc_error ("Substring end index at %L must be of type INTEGER",
4263                      &ref->u.ss.end->where);
4264           return FAILURE;
4265         }
4266
4267       if (ref->u.ss.end->rank != 0)
4268         {
4269           gfc_error ("Substring end index at %L must be scalar",
4270                      &ref->u.ss.end->where);
4271           return FAILURE;
4272         }
4273
4274       if (ref->u.ss.length != NULL
4275           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4276           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4277               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4278         {
4279           gfc_error ("Substring end index at %L exceeds the string length",
4280                      &ref->u.ss.start->where);
4281           return FAILURE;
4282         }
4283
4284       if (compare_bound_mpz_t (ref->u.ss.end,
4285                                gfc_integer_kinds[k].huge) == CMP_GT
4286           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4287               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4288         {
4289           gfc_error ("Substring end index at %L is too large",
4290                      &ref->u.ss.end->where);
4291           return FAILURE;
4292         }
4293     }
4294
4295   return SUCCESS;
4296 }
4297
4298
4299 /* This function supplies missing substring charlens.  */
4300
4301 void
4302 gfc_resolve_substring_charlen (gfc_expr *e)
4303 {
4304   gfc_ref *char_ref;
4305   gfc_expr *start, *end;
4306
4307   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4308     if (char_ref->type == REF_SUBSTRING)
4309       break;
4310
4311   if (!char_ref)
4312     return;
4313
4314   gcc_assert (char_ref->next == NULL);
4315
4316   if (e->ts.u.cl)
4317     {
4318       if (e->ts.u.cl->length)
4319         gfc_free_expr (e->ts.u.cl->length);
4320       else if (e->expr_type == EXPR_VARIABLE
4321                  && e->symtree->n.sym->attr.dummy)
4322         return;
4323     }
4324
4325   e->ts.type = BT_CHARACTER;
4326   e->ts.kind = gfc_default_character_kind;
4327
4328   if (!e->ts.u.cl)
4329     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4330
4331   if (char_ref->u.ss.start)
4332     start = gfc_copy_expr (char_ref->u.ss.start);
4333   else
4334     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4335
4336   if (char_ref->u.ss.end)
4337     end = gfc_copy_expr (char_ref->u.ss.end);
4338   else if (e->expr_type == EXPR_VARIABLE)
4339     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4340   else
4341     end = NULL;
4342
4343   if (!start || !end)
4344     return;
4345
4346   /* Length = (end - start +1).  */
4347   e->ts.u.cl->length = gfc_subtract (end, start);
4348   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4349                                 gfc_get_int_expr (gfc_default_integer_kind,
4350                                                   NULL, 1));
4351
4352   e->ts.u.cl->length->ts.type = BT_INTEGER;
4353   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4354
4355   /* Make sure that the length is simplified.  */
4356   gfc_simplify_expr (e->ts.u.cl->length, 1);
4357   gfc_resolve_expr (e->ts.u.cl->length);
4358 }
4359
4360
4361 /* Resolve subtype references.  */
4362
4363 static gfc_try
4364 resolve_ref (gfc_expr *expr)
4365 {
4366   int current_part_dimension, n_components, seen_part_dimension;
4367   gfc_ref *ref;
4368
4369   for (ref = expr->ref; ref; ref = ref->next)
4370     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4371       {
4372         find_array_spec (expr);
4373         break;
4374       }
4375
4376   for (ref = expr->ref; ref; ref = ref->next)
4377     switch (ref->type)
4378       {
4379       case REF_ARRAY:
4380         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4381           return FAILURE;
4382         break;
4383
4384       case REF_COMPONENT:
4385         break;
4386
4387       case REF_SUBSTRING:
4388         resolve_substring (ref);
4389         break;
4390       }
4391
4392   /* Check constraints on part references.  */
4393
4394   current_part_dimension = 0;
4395   seen_part_dimension = 0;
4396   n_components = 0;
4397
4398   for (ref = expr->ref; ref; ref = ref->next)
4399     {
4400       switch (ref->type)
4401         {
4402         case REF_ARRAY:
4403           switch (ref->u.ar.type)
4404             {
4405             case AR_FULL:
4406               /* Coarray scalar.  */
4407               if (ref->u.ar.as->rank == 0)
4408                 {
4409                   current_part_dimension = 0;
4410                   break;
4411                 }
4412               /* Fall through.  */
4413             case AR_SECTION:
4414               current_part_dimension = 1;
4415               break;
4416
4417             case AR_ELEMENT:
4418               current_part_dimension = 0;
4419               break;
4420
4421             case AR_UNKNOWN:
4422               gfc_internal_error ("resolve_ref(): Bad array reference");
4423             }
4424
4425           break;
4426
4427         case REF_COMPONENT:
4428           if (current_part_dimension || seen_part_dimension)
4429             {
4430               /* F03:C614.  */
4431               if (ref->u.c.component->attr.pointer
4432                   || ref->u.c.component->attr.proc_pointer)
4433                 {
4434                   gfc_error ("Component to the right of a part reference "
4435                              "with nonzero rank must not have the POINTER "
4436                              "attribute at %L", &expr->where);
4437                   return FAILURE;
4438                 }
4439               else if (ref->u.c.component->attr.allocatable)
4440                 {
4441                   gfc_error ("Component to the right of a part reference "
4442                              "with nonzero rank must not have the ALLOCATABLE "
4443                              "attribute at %L", &expr->where);
4444                   return FAILURE;
4445                 }
4446             }
4447
4448           n_components++;
4449           break;
4450
4451         case REF_SUBSTRING:
4452           break;
4453         }
4454
4455       if (((ref->type == REF_COMPONENT && n_components > 1)
4456            || ref->next == NULL)
4457           && current_part_dimension
4458           && seen_part_dimension)
4459         {
4460           gfc_error ("Two or more part references with nonzero rank must "
4461                      "not be specified at %L", &expr->where);
4462           return FAILURE;
4463         }
4464
4465       if (ref->type == REF_COMPONENT)
4466         {
4467           if (current_part_dimension)
4468             seen_part_dimension = 1;
4469
4470           /* reset to make sure */
4471           current_part_dimension = 0;
4472         }
4473     }
4474
4475   return SUCCESS;
4476 }
4477
4478
4479 /* Given an expression, determine its shape.  This is easier than it sounds.
4480    Leaves the shape array NULL if it is not possible to determine the shape.  */
4481
4482 static void
4483 expression_shape (gfc_expr *e)
4484 {
4485   mpz_t array[GFC_MAX_DIMENSIONS];
4486   int i;
4487
4488   if (e->rank == 0 || e->shape != NULL)
4489     return;
4490
4491   for (i = 0; i < e->rank; i++)
4492     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4493       goto fail;
4494
4495   e->shape = gfc_get_shape (e->rank);
4496
4497   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4498
4499   return;
4500
4501 fail:
4502   for (i--; i >= 0; i--)
4503     mpz_clear (array[i]);
4504 }
4505
4506
4507 /* Given a variable expression node, compute the rank of the expression by
4508    examining the base symbol and any reference structures it may have.  */
4509
4510 static void
4511 expression_rank (gfc_expr *e)
4512 {
4513   gfc_ref *ref;
4514   int i, rank;
4515
4516   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4517      could lead to serious confusion...  */
4518   gcc_assert (e->expr_type != EXPR_COMPCALL);
4519
4520   if (e->ref == NULL)
4521     {
4522       if (e->expr_type == EXPR_ARRAY)
4523         goto done;
4524       /* Constructors can have a rank different from one via RESHAPE().  */
4525
4526       if (e->symtree == NULL)
4527         {
4528           e->rank = 0;
4529           goto done;
4530         }
4531
4532       e->rank = (e->symtree->n.sym->as == NULL)
4533                 ? 0 : e->symtree->n.sym->as->rank;
4534       goto done;
4535     }
4536
4537   rank = 0;
4538
4539   for (ref = e->ref; ref; ref = ref->next)
4540     {
4541       if (ref->type != REF_ARRAY)
4542         continue;
4543
4544       if (ref->u.ar.type == AR_FULL)
4545         {
4546           rank = ref->u.ar.as->rank;
4547           break;
4548         }
4549
4550       if (ref->u.ar.type == AR_SECTION)
4551         {
4552           /* Figure out the rank of the section.  */
4553           if (rank != 0)
4554             gfc_internal_error ("expression_rank(): Two array specs");
4555
4556           for (i = 0; i < ref->u.ar.dimen; i++)
4557             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4558                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4559               rank++;
4560
4561           break;
4562         }
4563     }
4564
4565   e->rank = rank;
4566
4567 done:
4568   expression_shape (e);
4569 }
4570
4571
4572 /* Resolve a variable expression.  */
4573
4574 static gfc_try
4575 resolve_variable (gfc_expr *e)
4576 {
4577   gfc_symbol *sym;
4578   gfc_try t;
4579
4580   t = SUCCESS;
4581
4582   if (e->symtree == NULL)
4583     return FAILURE;
4584
4585   if (e->ref && resolve_ref (e) == FAILURE)
4586     return FAILURE;
4587
4588   sym = e->symtree->n.sym;
4589   if (sym->attr.flavor == FL_PROCEDURE
4590       && (!sym->attr.function
4591           || (sym->attr.function && sym->result
4592               && sym->result->attr.proc_pointer
4593               && !sym->result->attr.function)))
4594     {
4595       e->ts.type = BT_PROCEDURE;
4596       goto resolve_procedure;
4597     }
4598
4599   if (sym->ts.type != BT_UNKNOWN)
4600     gfc_variable_attr (e, &e->ts);
4601   else
4602     {
4603       /* Must be a simple variable reference.  */
4604       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4605         return FAILURE;
4606       e->ts = sym->ts;
4607     }
4608
4609   if (check_assumed_size_reference (sym, e))
4610     return FAILURE;
4611
4612   /* Deal with forward references to entries during resolve_code, to
4613      satisfy, at least partially, 12.5.2.5.  */
4614   if (gfc_current_ns->entries
4615       && current_entry_id == sym->entry_id
4616       && cs_base
4617       && cs_base->current
4618       && cs_base->current->op != EXEC_ENTRY)
4619     {
4620       gfc_entry_list *entry;
4621       gfc_formal_arglist *formal;
4622       int n;
4623       bool seen;
4624
4625       /* If the symbol is a dummy...  */
4626       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4627         {
4628           entry = gfc_current_ns->entries;
4629           seen = false;
4630
4631           /* ...test if the symbol is a parameter of previous entries.  */
4632           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4633             for (formal = entry->sym->formal; formal; formal = formal->next)
4634               {
4635                 if (formal->sym && sym->name == formal->sym->name)
4636                   seen = true;
4637               }
4638
4639           /*  If it has not been seen as a dummy, this is an error.  */
4640           if (!seen)
4641             {
4642               if (specification_expr)
4643                 gfc_error ("Variable '%s', used in a specification expression"
4644                            ", is referenced at %L before the ENTRY statement "
4645                            "in which it is a parameter",
4646                            sym->name, &cs_base->current->loc);
4647               else
4648                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4649                            "statement in which it is a parameter",
4650                            sym->name, &cs_base->current->loc);
4651               t = FAILURE;
4652             }
4653         }
4654
4655       /* Now do the same check on the specification expressions.  */
4656       specification_expr = 1;
4657       if (sym->ts.type == BT_CHARACTER
4658           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4659         t = FAILURE;
4660
4661       if (sym->as)
4662         for (n = 0; n < sym->as->rank; n++)
4663           {
4664              specification_expr = 1;
4665              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4666                t = FAILURE;
4667              specification_expr = 1;
4668              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4669                t = FAILURE;
4670           }
4671       specification_expr = 0;
4672
4673       if (t == SUCCESS)
4674         /* Update the symbol's entry level.  */
4675         sym->entry_id = current_entry_id + 1;
4676     }
4677
4678 resolve_procedure:
4679   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4680     t = FAILURE;
4681
4682   /* F2008, C617 and C1229.  */
4683   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
4684       && gfc_is_coindexed (e))
4685     {
4686       gfc_ref *ref, *ref2 = NULL;
4687
4688       if (e->ts.type == BT_CLASS)
4689         {
4690           gfc_error ("Polymorphic subobject of coindexed object at %L",
4691                      &e->where);
4692           t = FAILURE;
4693         }
4694
4695       for (ref = e->ref; ref; ref = ref->next)
4696         {
4697           if (ref->type == REF_COMPONENT)
4698             ref2 = ref;
4699           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
4700             break;
4701         }
4702
4703       for ( ; ref; ref = ref->next)
4704         if (ref->type == REF_COMPONENT)
4705           break;
4706
4707       /* Expression itself is coindexed object.  */
4708       if (ref == NULL)
4709         {
4710           gfc_component *c;
4711           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
4712           for ( ; c; c = c->next)
4713             if (c->attr.allocatable && c->ts.type == BT_CLASS)
4714               {
4715                 gfc_error ("Coindexed object with polymorphic allocatable "
4716                          "subcomponent at %L", &e->where);
4717                 t = FAILURE;
4718                 break;
4719               }
4720         }
4721     }
4722
4723   return t;
4724 }
4725
4726
4727 /* Checks to see that the correct symbol has been host associated.
4728    The only situation where this arises is that in which a twice
4729    contained function is parsed after the host association is made.
4730    Therefore, on detecting this, change the symbol in the expression
4731    and convert the array reference into an actual arglist if the old
4732    symbol is a variable.  */
4733 static bool
4734 check_host_association (gfc_expr *e)
4735 {
4736   gfc_symbol *sym, *old_sym;
4737   gfc_symtree *st;
4738   int n;
4739   gfc_ref *ref;
4740   gfc_actual_arglist *arg, *tail = NULL;
4741   bool retval = e->expr_type == EXPR_FUNCTION;
4742
4743   /*  If the expression is the result of substitution in
4744       interface.c(gfc_extend_expr) because there is no way in
4745       which the host association can be wrong.  */
4746   if (e->symtree == NULL
4747         || e->symtree->n.sym == NULL
4748         || e->user_operator)
4749     return retval;
4750
4751   old_sym = e->symtree->n.sym;
4752
4753   if (gfc_current_ns->parent
4754         && old_sym->ns != gfc_current_ns)
4755     {
4756       /* Use the 'USE' name so that renamed module symbols are
4757          correctly handled.  */
4758       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4759
4760       if (sym && old_sym != sym
4761               && sym->ts.type == old_sym->ts.type
4762               && sym->attr.flavor == FL_PROCEDURE
4763               && sym->attr.contained)
4764         {
4765           /* Clear the shape, since it might not be valid.  */
4766           if (e->shape != NULL)
4767             {
4768               for (n = 0; n < e->rank; n++)
4769                 mpz_clear (e->shape[n]);
4770
4771               gfc_free (e->shape);
4772             }
4773
4774           /* Give the expression the right symtree!  */
4775           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4776           gcc_assert (st != NULL);
4777
4778           if (old_sym->attr.flavor == FL_PROCEDURE
4779                 || e->expr_type == EXPR_FUNCTION)
4780             {
4781               /* Original was function so point to the new symbol, since
4782                  the actual argument list is already attached to the
4783                  expression. */
4784               e->value.function.esym = NULL;
4785               e->symtree = st;
4786             }
4787           else
4788             {
4789               /* Original was variable so convert array references into
4790                  an actual arglist. This does not need any checking now
4791                  since gfc_resolve_function will take care of it.  */
4792               e->value.function.actual = NULL;
4793               e->expr_type = EXPR_FUNCTION;
4794               e->symtree = st;
4795
4796               /* Ambiguity will not arise if the array reference is not
4797                  the last reference.  */
4798               for (ref = e->ref; ref; ref = ref->next)
4799                 if (ref->type == REF_ARRAY && ref->next == NULL)
4800                   break;
4801
4802               gcc_assert (ref->type == REF_ARRAY);
4803
4804               /* Grab the start expressions from the array ref and
4805                  copy them into actual arguments.  */
4806               for (n = 0; n < ref->u.ar.dimen; n++)
4807                 {
4808                   arg = gfc_get_actual_arglist ();
4809                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4810                   if (e->value.function.actual == NULL)
4811                     tail = e->value.function.actual = arg;
4812                   else
4813                     {
4814                       tail->next = arg;
4815                       tail = arg;
4816                     }
4817                 }
4818
4819               /* Dump the reference list and set the rank.  */
4820               gfc_free_ref_list (e->ref);
4821               e->ref = NULL;
4822               e->rank = sym->as ? sym->as->rank : 0;
4823             }
4824
4825           gfc_resolve_expr (e);
4826           sym->refs++;
4827         }
4828     }
4829   /* This might have changed!  */
4830   return e->expr_type == EXPR_FUNCTION;
4831 }
4832
4833
4834 static void
4835 gfc_resolve_character_operator (gfc_expr *e)
4836 {
4837   gfc_expr *op1 = e->value.op.op1;
4838   gfc_expr *op2 = e->value.op.op2;
4839   gfc_expr *e1 = NULL;
4840   gfc_expr *e2 = NULL;
4841
4842   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4843
4844   if (op1->ts.u.cl && op1->ts.u.cl->length)
4845     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4846   else if (op1->expr_type == EXPR_CONSTANT)
4847     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4848                            op1->value.character.length);
4849
4850   if (op2->ts.u.cl && op2->ts.u.cl->length)
4851     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4852   else if (op2->expr_type == EXPR_CONSTANT)
4853     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4854                            op2->value.character.length);
4855
4856   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4857
4858   if (!e1 || !e2)
4859     return;
4860
4861   e->ts.u.cl->length = gfc_add (e1, e2);
4862   e->ts.u.cl->length->ts.type = BT_INTEGER;
4863   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4864   gfc_simplify_expr (e->ts.u.cl->length, 0);
4865   gfc_resolve_expr (e->ts.u.cl->length);
4866
4867   return;
4868 }
4869
4870
4871 /*  Ensure that an character expression has a charlen and, if possible, a
4872     length expression.  */
4873
4874 static void
4875 fixup_charlen (gfc_expr *e)
4876 {
4877   /* The cases fall through so that changes in expression type and the need
4878      for multiple fixes are picked up.  In all circumstances, a charlen should
4879      be available for the middle end to hang a backend_decl on.  */
4880   switch (e->expr_type)
4881     {
4882     case EXPR_OP:
4883       gfc_resolve_character_operator (e);
4884
4885     case EXPR_ARRAY:
4886       if (e->expr_type == EXPR_ARRAY)
4887         gfc_resolve_character_array_constructor (e);
4888
4889     case EXPR_SUBSTRING:
4890       if (!e->ts.u.cl && e->ref)
4891         gfc_resolve_substring_charlen (e);
4892
4893     default:
4894       if (!e->ts.u.cl)
4895         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4896
4897       break;
4898     }
4899 }
4900
4901
4902 /* Update an actual argument to include the passed-object for type-bound
4903    procedures at the right position.  */
4904
4905 static gfc_actual_arglist*
4906 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
4907                      const char *name)
4908 {
4909   gcc_assert (argpos > 0);
4910
4911   if (argpos == 1)
4912     {
4913       gfc_actual_arglist* result;
4914
4915       result = gfc_get_actual_arglist ();
4916       result->expr = po;
4917       result->next = lst;
4918       if (name)
4919         result->name = name;
4920
4921       return result;
4922     }
4923
4924   if (lst)
4925     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
4926   else
4927     lst = update_arglist_pass (NULL, po, argpos - 1, name);
4928   return lst;
4929 }
4930
4931
4932 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
4933
4934 static gfc_expr*
4935 extract_compcall_passed_object (gfc_expr* e)
4936 {
4937   gfc_expr* po;
4938
4939   gcc_assert (e->expr_type == EXPR_COMPCALL);
4940
4941   if (e->value.compcall.base_object)
4942     po = gfc_copy_expr (e->value.compcall.base_object);
4943   else
4944     {
4945       po = gfc_get_expr ();
4946       po->expr_type = EXPR_VARIABLE;
4947       po->symtree = e->symtree;
4948       po->ref = gfc_copy_ref (e->ref);
4949       po->where = e->where;
4950     }
4951
4952   if (gfc_resolve_expr (po) == FAILURE)
4953     return NULL;
4954
4955   return po;
4956 }
4957
4958
4959 /* Update the arglist of an EXPR_COMPCALL expression to include the
4960    passed-object.  */
4961
4962 static gfc_try
4963 update_compcall_arglist (gfc_expr* e)
4964 {
4965   gfc_expr* po;
4966   gfc_typebound_proc* tbp;
4967
4968   tbp = e->value.compcall.tbp;
4969
4970   if (tbp->error)
4971     return FAILURE;
4972
4973   po = extract_compcall_passed_object (e);
4974   if (!po)
4975     return FAILURE;
4976
4977   if (tbp->nopass || e->value.compcall.ignore_pass)
4978     {
4979       gfc_free_expr (po);
4980       return SUCCESS;
4981     }
4982
4983   gcc_assert (tbp->pass_arg_num > 0);
4984   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
4985                                                   tbp->pass_arg_num,
4986                                                   tbp->pass_arg);
4987
4988   return SUCCESS;
4989 }
4990
4991
4992 /* Extract the passed object from a PPC call (a copy of it).  */
4993
4994 static gfc_expr*
4995 extract_ppc_passed_object (gfc_expr *e)
4996 {
4997   gfc_expr *po;
4998   gfc_ref **ref;
4999
5000   po = gfc_get_expr ();
5001   po->expr_type = EXPR_VARIABLE;
5002   po->symtree = e->symtree;
5003   po->ref = gfc_copy_ref (e->ref);
5004   po->where = e->where;
5005
5006   /* Remove PPC reference.  */
5007   ref = &po->ref;
5008   while ((*ref)->next)
5009     ref = &(*ref)->next;
5010   gfc_free_ref_list (*ref);
5011   *ref = NULL;
5012
5013   if (gfc_resolve_expr (po) == FAILURE)
5014     return NULL;
5015
5016   return po;
5017 }
5018
5019
5020 /* Update the actual arglist of a procedure pointer component to include the
5021    passed-object.  */
5022
5023 static gfc_try
5024 update_ppc_arglist (gfc_expr* e)
5025 {
5026   gfc_expr* po;
5027   gfc_component *ppc;
5028   gfc_typebound_proc* tb;
5029
5030   if (!gfc_is_proc_ptr_comp (e, &ppc))
5031     return FAILURE;
5032
5033   tb = ppc->tb;
5034
5035   if (tb->error)
5036     return FAILURE;
5037   else if (tb->nopass)
5038     return SUCCESS;
5039
5040   po = extract_ppc_passed_object (e);
5041   if (!po)
5042     return FAILURE;
5043
5044   if (po->rank > 0)
5045     {
5046       gfc_error ("Passed-object at %L must be scalar", &e->where);
5047       return FAILURE;
5048     }
5049
5050   gcc_assert (tb->pass_arg_num > 0);
5051   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5052                                                   tb->pass_arg_num,
5053                                                   tb->pass_arg);
5054
5055   return SUCCESS;
5056 }
5057
5058
5059 /* Check that the object a TBP is called on is valid, i.e. it must not be
5060    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5061
5062 static gfc_try
5063 check_typebound_baseobject (gfc_expr* e)
5064 {
5065   gfc_expr* base;
5066
5067   base = extract_compcall_passed_object (e);
5068   if (!base)
5069     return FAILURE;
5070
5071   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5072
5073   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5074     {
5075       gfc_error ("Base object for type-bound procedure call at %L is of"
5076                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5077       return FAILURE;
5078     }
5079
5080   /* If the procedure called is NOPASS, the base object must be scalar.  */
5081   if (e->value.compcall.tbp->nopass && base->rank > 0)
5082     {
5083       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5084                  " be scalar", &e->where);
5085       return FAILURE;
5086     }
5087
5088   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5089   if (base->rank > 0)
5090     {
5091       gfc_error ("Non-scalar base object at %L currently not implemented",
5092                  &e->where);
5093       return FAILURE;
5094     }
5095
5096   return SUCCESS;
5097 }
5098
5099
5100 /* Resolve a call to a type-bound procedure, either function or subroutine,
5101    statically from the data in an EXPR_COMPCALL expression.  The adapted
5102    arglist and the target-procedure symtree are returned.  */
5103
5104 static gfc_try
5105 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5106                           gfc_actual_arglist** actual)
5107 {
5108   gcc_assert (e->expr_type == EXPR_COMPCALL);
5109   gcc_assert (!e->value.compcall.tbp->is_generic);
5110
5111   /* Update the actual arglist for PASS.  */
5112   if (update_compcall_arglist (e) == FAILURE)
5113     return FAILURE;
5114
5115   *actual = e->value.compcall.actual;
5116   *target = e->value.compcall.tbp->u.specific;
5117
5118   gfc_free_ref_list (e->ref);
5119   e->ref = NULL;
5120   e->value.compcall.actual = NULL;
5121
5122   return SUCCESS;
5123 }
5124
5125
5126 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5127    which of the specific bindings (if any) matches the arglist and transform
5128    the expression into a call of that binding.  */
5129
5130 static gfc_try
5131 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5132 {
5133   gfc_typebound_proc* genproc;
5134   const char* genname;
5135
5136   gcc_assert (e->expr_type == EXPR_COMPCALL);
5137   genname = e->value.compcall.name;
5138   genproc = e->value.compcall.tbp;
5139
5140   if (!genproc->is_generic)
5141     return SUCCESS;
5142
5143   /* Try the bindings on this type and in the inheritance hierarchy.  */
5144   for (; genproc; genproc = genproc->overridden)
5145     {
5146       gfc_tbp_generic* g;
5147
5148       gcc_assert (genproc->is_generic);
5149       for (g = genproc->u.generic; g; g = g->next)
5150         {
5151           gfc_symbol* target;
5152           gfc_actual_arglist* args;
5153           bool matches;
5154
5155           gcc_assert (g->specific);
5156
5157           if (g->specific->error)
5158             continue;
5159
5160           target = g->specific->u.specific->n.sym;
5161
5162           /* Get the right arglist by handling PASS/NOPASS.  */
5163           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5164           if (!g->specific->nopass)
5165             {
5166               gfc_expr* po;
5167               po = extract_compcall_passed_object (e);
5168               if (!po)
5169                 return FAILURE;
5170
5171               gcc_assert (g->specific->pass_arg_num > 0);
5172               gcc_assert (!g->specific->error);
5173               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5174                                           g->specific->pass_arg);
5175             }
5176           resolve_actual_arglist (args, target->attr.proc,
5177                                   is_external_proc (target) && !target->formal);
5178
5179           /* Check if this arglist matches the formal.  */
5180           matches = gfc_arglist_matches_symbol (&args, target);
5181
5182           /* Clean up and break out of the loop if we've found it.  */
5183           gfc_free_actual_arglist (args);
5184           if (matches)
5185             {
5186               e->value.compcall.tbp = g->specific;
5187               /* Pass along the name for CLASS methods, where the vtab
5188                  procedure pointer component has to be referenced.  */
5189               if (name)
5190                 *name = g->specific_st->name;
5191               goto success;
5192             }
5193         }
5194     }
5195
5196   /* Nothing matching found!  */
5197   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5198              " '%s' at %L", genname, &e->where);
5199   return FAILURE;
5200
5201 success:
5202   return SUCCESS;
5203 }
5204
5205
5206 /* Resolve a call to a type-bound subroutine.  */
5207
5208 static gfc_try
5209 resolve_typebound_call (gfc_code* c, const char **name)
5210 {
5211   gfc_actual_arglist* newactual;
5212   gfc_symtree* target;
5213
5214   /* Check that's really a SUBROUTINE.  */
5215   if (!c->expr1->value.compcall.tbp->subroutine)
5216     {
5217       gfc_error ("'%s' at %L should be a SUBROUTINE",
5218                  c->expr1->value.compcall.name, &c->loc);
5219       return FAILURE;
5220     }
5221
5222   if (check_typebound_baseobject (c->expr1) == FAILURE)
5223     return FAILURE;
5224
5225   /* Pass along the name for CLASS methods, where the vtab
5226      procedure pointer component has to be referenced.  */
5227   if (name)
5228     *name = c->expr1->value.compcall.name;
5229
5230   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5231     return FAILURE;
5232
5233   /* Transform into an ordinary EXEC_CALL for now.  */
5234
5235   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5236     return FAILURE;
5237
5238   c->ext.actual = newactual;
5239   c->symtree = target;
5240   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5241
5242   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5243
5244   gfc_free_expr (c->expr1);
5245   c->expr1 = gfc_get_expr ();
5246   c->expr1->expr_type = EXPR_FUNCTION;
5247   c->expr1->symtree = target;
5248   c->expr1->where = c->loc;
5249
5250   return resolve_call (c);
5251 }
5252
5253
5254 /* Resolve a component-call expression.  */
5255 static gfc_try
5256 resolve_compcall (gfc_expr* e, const char **name)
5257 {
5258   gfc_actual_arglist* newactual;
5259   gfc_symtree* target;
5260
5261   /* Check that's really a FUNCTION.  */
5262   if (!e->value.compcall.tbp->function)
5263     {
5264       gfc_error ("'%s' at %L should be a FUNCTION",
5265                  e->value.compcall.name, &e->where);
5266       return FAILURE;
5267     }
5268
5269   /* These must not be assign-calls!  */
5270   gcc_assert (!e->value.compcall.assign);
5271
5272   if (check_typebound_baseobject (e) == FAILURE)
5273     return FAILURE;
5274
5275   /* Pass along the name for CLASS methods, where the vtab
5276      procedure pointer component has to be referenced.  */
5277   if (name)
5278     *name = e->value.compcall.name;
5279
5280   if (resolve_typebound_generic_call (e, name) == FAILURE)
5281     return FAILURE;
5282   gcc_assert (!e->value.compcall.tbp->is_generic);
5283
5284   /* Take the rank from the function's symbol.  */
5285   if (e->value.compcall.tbp->u.specific->n.sym->as)
5286     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5287
5288   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5289      arglist to the TBP's binding target.  */
5290
5291   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5292     return FAILURE;
5293
5294   e->value.function.actual = newactual;
5295   e->value.function.name = NULL;
5296   e->value.function.esym = target->n.sym;
5297   e->value.function.isym = NULL;
5298   e->symtree = target;
5299   e->ts = target->n.sym->ts;
5300   e->expr_type = EXPR_FUNCTION;
5301
5302   /* Resolution is not necessary if this is a class subroutine; this
5303      function only has to identify the specific proc. Resolution of
5304      the call will be done next in resolve_typebound_call.  */
5305   return gfc_resolve_expr (e);
5306 }
5307
5308
5309 /* Get the ultimate declared type from an expression.  In addition,
5310    return the last class/derived type reference and the copy of the
5311    reference list.  */
5312 static gfc_symbol*
5313 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5314                         gfc_expr *e)
5315 {
5316   gfc_symbol *declared;
5317   gfc_ref *ref;
5318
5319   declared = NULL;
5320   *class_ref = NULL;
5321   *new_ref = gfc_copy_ref (e->ref);
5322   for (ref = *new_ref; ref; ref = ref->next)
5323     {
5324       if (ref->type != REF_COMPONENT)
5325         continue;
5326
5327       if (ref->u.c.component->ts.type == BT_CLASS
5328             || ref->u.c.component->ts.type == BT_DERIVED)
5329         {
5330           declared = ref->u.c.component->ts.u.derived;
5331           *class_ref = ref;
5332         }
5333     }
5334
5335   if (declared == NULL)
5336     declared = e->symtree->n.sym->ts.u.derived;
5337
5338   return declared;
5339 }
5340
5341
5342 /* Resolve a typebound function, or 'method'. First separate all
5343    the non-CLASS references by calling resolve_compcall directly.  */
5344
5345 static gfc_try
5346 resolve_typebound_function (gfc_expr* e)
5347 {
5348   gfc_symbol *declared;
5349   gfc_component *c;
5350   gfc_ref *new_ref;
5351   gfc_ref *class_ref;
5352   gfc_symtree *st;
5353   const char *name;
5354   const char *genname;
5355   gfc_typespec ts;
5356
5357   st = e->symtree;
5358   if (st == NULL)
5359     return resolve_compcall (e, NULL);
5360
5361   /* Get the CLASS declared type.  */
5362   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5363
5364   /* Weed out cases of the ultimate component being a derived type.  */
5365   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5366          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5367     {
5368       gfc_free_ref_list (new_ref);
5369       return resolve_compcall (e, NULL);
5370     }
5371
5372   c = gfc_find_component (declared, "$data", true, true);
5373   declared = c->ts.u.derived;
5374
5375   /* Keep the generic name so that the vtab reference can be made.  */
5376   genname = NULL; 
5377   if (e->value.compcall.tbp->is_generic)
5378     genname = e->value.compcall.name;
5379
5380   /* Treat the call as if it is a typebound procedure, in order to roll
5381      out the correct name for the specific function.  */
5382   resolve_compcall (e, &name);
5383   ts = e->ts;
5384
5385   /* Then convert the expression to a procedure pointer component call.  */
5386   e->value.function.esym = NULL;
5387   e->symtree = st;
5388
5389   if (class_ref)  
5390     {
5391       gfc_free_ref_list (class_ref->next);
5392       e->ref = new_ref;
5393     }
5394
5395   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5396   gfc_add_component_ref (e, "$vptr");
5397   if (genname)
5398     {
5399       /* A generic procedure needs the subsidiary vtabs and vtypes for
5400          the specific procedures to have been build.  */
5401       gfc_symbol *vtab;
5402       vtab = gfc_find_derived_vtab (declared, true);
5403       gcc_assert (vtab);
5404       gfc_add_component_ref (e, genname);
5405     }
5406   gfc_add_component_ref (e, name);
5407
5408   /* Recover the typespec for the expression.  This is really only
5409      necessary for generic procedures, where the additional call
5410      to gfc_add_component_ref seems to throw the collection of the
5411      correct typespec.  */
5412   e->ts = ts;
5413   return SUCCESS;
5414 }
5415
5416 /* Resolve a typebound subroutine, or 'method'. First separate all
5417    the non-CLASS references by calling resolve_typebound_call
5418    directly.  */
5419
5420 static gfc_try
5421 resolve_typebound_subroutine (gfc_code *code)
5422 {
5423   gfc_symbol *declared;
5424   gfc_component *c;
5425   gfc_ref *new_ref;
5426   gfc_ref *class_ref;
5427   gfc_symtree *st;
5428   const char *genname;
5429   const char *name;
5430   gfc_typespec ts;
5431
5432   st = code->expr1->symtree;
5433   if (st == NULL)
5434     return resolve_typebound_call (code, NULL);
5435
5436   /* Get the CLASS declared type.  */
5437   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5438
5439   /* Weed out cases of the ultimate component being a derived type.  */
5440   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5441          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5442     {
5443       gfc_free_ref_list (new_ref);
5444       return resolve_typebound_call (code, NULL);
5445     } 
5446
5447   c = gfc_find_component (declared, "$data", true, true);
5448   declared = c->ts.u.derived;
5449
5450   /* Keep the generic name so that the vtab reference can be made.  */
5451   genname = NULL; 
5452   if (code->expr1->value.compcall.tbp->is_generic)
5453     genname = code->expr1->value.compcall.name;
5454
5455   resolve_typebound_call (code, &name);
5456   ts = code->expr1->ts;
5457
5458   /* Then convert the expression to a procedure pointer component call.  */
5459   code->expr1->value.function.esym = NULL;
5460   code->expr1->symtree = st;
5461
5462   if (class_ref)  
5463     {
5464       gfc_free_ref_list (class_ref->next);
5465       code->expr1->ref = new_ref;
5466     }
5467
5468   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5469   gfc_add_component_ref (code->expr1, "$vptr");
5470   if (genname)
5471     {
5472       /* A generic procedure needs the subsidiary vtabs and vtypes for
5473          the specific procedures to have been build.  */
5474       gfc_symbol *vtab;
5475       vtab = gfc_find_derived_vtab (declared, true);
5476       gcc_assert (vtab);
5477       gfc_add_component_ref (code->expr1, genname);
5478     }
5479   gfc_add_component_ref (code->expr1, name);
5480
5481   /* Recover the typespec for the expression.  This is really only
5482      necessary for generic procedures, where the additional call
5483      to gfc_add_component_ref seems to throw the collection of the
5484      correct typespec.  */
5485   code->expr1->ts = ts;
5486   return SUCCESS;
5487 }
5488
5489
5490 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5491
5492 static gfc_try
5493 resolve_ppc_call (gfc_code* c)
5494 {
5495   gfc_component *comp;
5496   bool b;
5497
5498   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5499   gcc_assert (b);
5500
5501   c->resolved_sym = c->expr1->symtree->n.sym;
5502   c->expr1->expr_type = EXPR_VARIABLE;
5503
5504   if (!comp->attr.subroutine)
5505     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5506
5507   if (resolve_ref (c->expr1) == FAILURE)
5508     return FAILURE;
5509
5510   if (update_ppc_arglist (c->expr1) == FAILURE)
5511     return FAILURE;
5512
5513   c->ext.actual = c->expr1->value.compcall.actual;
5514
5515   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5516                               comp->formal == NULL) == FAILURE)
5517     return FAILURE;
5518
5519   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5520
5521   return SUCCESS;
5522 }
5523
5524
5525 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5526
5527 static gfc_try
5528 resolve_expr_ppc (gfc_expr* e)
5529 {
5530   gfc_component *comp;
5531   bool b;
5532
5533   b = gfc_is_proc_ptr_comp (e, &comp);
5534   gcc_assert (b);
5535
5536   /* Convert to EXPR_FUNCTION.  */
5537   e->expr_type = EXPR_FUNCTION;
5538   e->value.function.isym = NULL;
5539   e->value.function.actual = e->value.compcall.actual;
5540   e->ts = comp->ts;
5541   if (comp->as != NULL)
5542     e->rank = comp->as->rank;
5543
5544   if (!comp->attr.function)
5545     gfc_add_function (&comp->attr, comp->name, &e->where);
5546
5547   if (resolve_ref (e) == FAILURE)
5548     return FAILURE;
5549
5550   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5551                               comp->formal == NULL) == FAILURE)
5552     return FAILURE;
5553
5554   if (update_ppc_arglist (e) == FAILURE)
5555     return FAILURE;
5556
5557   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5558
5559   return SUCCESS;
5560 }
5561
5562
5563 static bool
5564 gfc_is_expandable_expr (gfc_expr *e)
5565 {
5566   gfc_constructor *con;
5567
5568   if (e->expr_type == EXPR_ARRAY)
5569     {
5570       /* Traverse the constructor looking for variables that are flavor
5571          parameter.  Parameters must be expanded since they are fully used at
5572          compile time.  */
5573       con = gfc_constructor_first (e->value.constructor);
5574       for (; con; con = gfc_constructor_next (con))
5575         {
5576           if (con->expr->expr_type == EXPR_VARIABLE
5577               && con->expr->symtree
5578               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5579               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5580             return true;
5581           if (con->expr->expr_type == EXPR_ARRAY
5582               && gfc_is_expandable_expr (con->expr))
5583             return true;
5584         }
5585     }
5586
5587   return false;
5588 }
5589
5590 /* Resolve an expression.  That is, make sure that types of operands agree
5591    with their operators, intrinsic operators are converted to function calls
5592    for overloaded types and unresolved function references are resolved.  */
5593
5594 gfc_try
5595 gfc_resolve_expr (gfc_expr *e)
5596 {
5597   gfc_try t;
5598   bool inquiry_save;
5599
5600   if (e == NULL)
5601     return SUCCESS;
5602
5603   /* inquiry_argument only applies to variables.  */
5604   inquiry_save = inquiry_argument;
5605   if (e->expr_type != EXPR_VARIABLE)
5606     inquiry_argument = false;
5607
5608   switch (e->expr_type)
5609     {
5610     case EXPR_OP:
5611       t = resolve_operator (e);
5612       break;
5613
5614     case EXPR_FUNCTION:
5615     case EXPR_VARIABLE:
5616
5617       if (check_host_association (e))
5618         t = resolve_function (e);
5619       else
5620         {
5621           t = resolve_variable (e);
5622           if (t == SUCCESS)
5623             expression_rank (e);
5624         }
5625
5626       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5627           && e->ref->type != REF_SUBSTRING)
5628         gfc_resolve_substring_charlen (e);
5629
5630       break;
5631
5632     case EXPR_COMPCALL:
5633       t = resolve_typebound_function (e);
5634       break;
5635
5636     case EXPR_SUBSTRING:
5637       t = resolve_ref (e);
5638       break;
5639
5640     case EXPR_CONSTANT:
5641     case EXPR_NULL:
5642       t = SUCCESS;
5643       break;
5644
5645     case EXPR_PPC:
5646       t = resolve_expr_ppc (e);
5647       break;
5648
5649     case EXPR_ARRAY:
5650       t = FAILURE;
5651       if (resolve_ref (e) == FAILURE)
5652         break;
5653
5654       t = gfc_resolve_array_constructor (e);
5655       /* Also try to expand a constructor.  */
5656       if (t == SUCCESS)
5657         {
5658           expression_rank (e);
5659           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5660             gfc_expand_constructor (e);
5661         }
5662
5663       /* This provides the opportunity for the length of constructors with
5664          character valued function elements to propagate the string length
5665          to the expression.  */
5666       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5667         {
5668           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5669              here rather then add a duplicate test for it above.  */ 
5670           gfc_expand_constructor (e);
5671           t = gfc_resolve_character_array_constructor (e);
5672         }
5673
5674       break;
5675
5676     case EXPR_STRUCTURE:
5677       t = resolve_ref (e);
5678       if (t == FAILURE)
5679         break;
5680
5681       t = resolve_structure_cons (e);
5682       if (t == FAILURE)
5683         break;
5684
5685       t = gfc_simplify_expr (e, 0);
5686       break;
5687
5688     default:
5689       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5690     }
5691
5692   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5693     fixup_charlen (e);
5694
5695   inquiry_argument = inquiry_save;
5696
5697   return t;
5698 }
5699
5700
5701 /* Resolve an expression from an iterator.  They must be scalar and have
5702    INTEGER or (optionally) REAL type.  */
5703
5704 static gfc_try
5705 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5706                            const char *name_msgid)
5707 {
5708   if (gfc_resolve_expr (expr) == FAILURE)
5709     return FAILURE;
5710
5711   if (expr->rank != 0)
5712     {
5713       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5714       return FAILURE;
5715     }
5716
5717   if (expr->ts.type != BT_INTEGER)
5718     {
5719       if (expr->ts.type == BT_REAL)
5720         {
5721           if (real_ok)
5722             return gfc_notify_std (GFC_STD_F95_DEL,
5723                                    "Deleted feature: %s at %L must be integer",
5724                                    _(name_msgid), &expr->where);
5725           else
5726             {
5727               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5728                          &expr->where);
5729               return FAILURE;
5730             }
5731         }
5732       else
5733         {
5734           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5735           return FAILURE;
5736         }
5737     }
5738   return SUCCESS;
5739 }
5740
5741
5742 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5743    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5744
5745 gfc_try
5746 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5747 {
5748   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5749       == FAILURE)
5750     return FAILURE;
5751
5752   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5753     {
5754       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5755                  &iter->var->where);
5756       return FAILURE;
5757     }
5758
5759   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5760                                  "Start expression in DO loop") == FAILURE)
5761     return FAILURE;
5762
5763   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5764                                  "End expression in DO loop") == FAILURE)
5765     return FAILURE;
5766
5767   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5768                                  "Step expression in DO loop") == FAILURE)
5769     return FAILURE;
5770
5771   if (iter->step->expr_type == EXPR_CONSTANT)
5772     {
5773       if ((iter->step->ts.type == BT_INTEGER
5774            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5775           || (iter->step->ts.type == BT_REAL
5776               && mpfr_sgn (iter->step->value.real) == 0))
5777         {
5778           gfc_error ("Step expression in DO loop at %L cannot be zero",
5779                      &iter->step->where);
5780           return FAILURE;
5781         }
5782     }
5783
5784   /* Convert start, end, and step to the same type as var.  */
5785   if (iter->start->ts.kind != iter->var->ts.kind
5786       || iter->start->ts.type != iter->var->ts.type)
5787     gfc_convert_type (iter->start, &iter->var->ts, 2);
5788
5789   if (iter->end->ts.kind != iter->var->ts.kind
5790       || iter->end->ts.type != iter->var->ts.type)
5791     gfc_convert_type (iter->end, &iter->var->ts, 2);
5792
5793   if (iter->step->ts.kind != iter->var->ts.kind
5794       || iter->step->ts.type != iter->var->ts.type)
5795     gfc_convert_type (iter->step, &iter->var->ts, 2);
5796
5797   if (iter->start->expr_type == EXPR_CONSTANT
5798       && iter->end->expr_type == EXPR_CONSTANT
5799       && iter->step->expr_type == EXPR_CONSTANT)
5800     {
5801       int sgn, cmp;
5802       if (iter->start->ts.type == BT_INTEGER)
5803         {
5804           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5805           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5806         }
5807       else
5808         {
5809           sgn = mpfr_sgn (iter->step->value.real);
5810           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5811         }
5812       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5813         gfc_warning ("DO loop at %L will be executed zero times",
5814                      &iter->step->where);
5815     }
5816
5817   return SUCCESS;
5818 }
5819
5820
5821 /* Traversal function for find_forall_index.  f == 2 signals that
5822    that variable itself is not to be checked - only the references.  */
5823
5824 static bool
5825 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5826 {
5827   if (expr->expr_type != EXPR_VARIABLE)
5828     return false;
5829   
5830   /* A scalar assignment  */
5831   if (!expr->ref || *f == 1)
5832     {
5833       if (expr->symtree->n.sym == sym)
5834         return true;
5835       else
5836         return false;
5837     }
5838
5839   if (*f == 2)
5840     *f = 1;
5841   return false;
5842 }
5843
5844
5845 /* Check whether the FORALL index appears in the expression or not.
5846    Returns SUCCESS if SYM is found in EXPR.  */
5847
5848 gfc_try
5849 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5850 {
5851   if (gfc_traverse_expr (expr, sym, forall_index, f))
5852     return SUCCESS;
5853   else
5854     return FAILURE;
5855 }
5856
5857
5858 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5859    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5860    INTEGERs, and if stride is a constant it must be nonzero.
5861    Furthermore "A subscript or stride in a forall-triplet-spec shall
5862    not contain a reference to any index-name in the
5863    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5864
5865 static void
5866 resolve_forall_iterators (gfc_forall_iterator *it)
5867 {
5868   gfc_forall_iterator *iter, *iter2;
5869
5870   for (iter = it; iter; iter = iter->next)
5871     {
5872       if (gfc_resolve_expr (iter->var) == SUCCESS
5873           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5874         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5875                    &iter->var->where);
5876
5877       if (gfc_resolve_expr (iter->start) == SUCCESS
5878           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5879         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5880                    &iter->start->where);
5881       if (iter->var->ts.kind != iter->start->ts.kind)
5882         gfc_convert_type (iter->start, &iter->var->ts, 2);
5883
5884       if (gfc_resolve_expr (iter->end) == SUCCESS
5885           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
5886         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
5887                    &iter->end->where);
5888       if (iter->var->ts.kind != iter->end->ts.kind)
5889         gfc_convert_type (iter->end, &iter->var->ts, 2);
5890
5891       if (gfc_resolve_expr (iter->stride) == SUCCESS)
5892         {
5893           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
5894             gfc_error ("FORALL stride expression at %L must be a scalar %s",
5895                        &iter->stride->where, "INTEGER");
5896
5897           if (iter->stride->expr_type == EXPR_CONSTANT
5898               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
5899             gfc_error ("FORALL stride expression at %L cannot be zero",
5900                        &iter->stride->where);
5901         }
5902       if (iter->var->ts.kind != iter->stride->ts.kind)
5903         gfc_convert_type (iter->stride, &iter->var->ts, 2);
5904     }
5905
5906   for (iter = it; iter; iter = iter->next)
5907     for (iter2 = iter; iter2; iter2 = iter2->next)
5908       {
5909         if (find_forall_index (iter2->start,
5910                                iter->var->symtree->n.sym, 0) == SUCCESS
5911             || find_forall_index (iter2->end,
5912                                   iter->var->symtree->n.sym, 0) == SUCCESS
5913             || find_forall_index (iter2->stride,
5914                                   iter->var->symtree->n.sym, 0) == SUCCESS)
5915           gfc_error ("FORALL index '%s' may not appear in triplet "
5916                      "specification at %L", iter->var->symtree->name,
5917                      &iter2->start->where);
5918       }
5919 }
5920
5921
5922 /* Given a pointer to a symbol that is a derived type, see if it's
5923    inaccessible, i.e. if it's defined in another module and the components are
5924    PRIVATE.  The search is recursive if necessary.  Returns zero if no
5925    inaccessible components are found, nonzero otherwise.  */
5926
5927 static int
5928 derived_inaccessible (gfc_symbol *sym)
5929 {
5930   gfc_component *c;
5931
5932   if (sym->attr.use_assoc && sym->attr.private_comp)
5933     return 1;
5934
5935   for (c = sym->components; c; c = c->next)
5936     {
5937         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
5938           return 1;
5939     }
5940
5941   return 0;
5942 }
5943
5944
5945 /* Resolve the argument of a deallocate expression.  The expression must be
5946    a pointer or a full array.  */
5947
5948 static gfc_try
5949 resolve_deallocate_expr (gfc_expr *e)
5950 {
5951   symbol_attribute attr;
5952   int allocatable, pointer, check_intent_in;
5953   gfc_ref *ref;
5954   gfc_symbol *sym;
5955   gfc_component *c;
5956
5957   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5958   check_intent_in = 1;
5959
5960   if (gfc_resolve_expr (e) == FAILURE)
5961     return FAILURE;
5962
5963   if (e->expr_type != EXPR_VARIABLE)
5964     goto bad;
5965
5966   sym = e->symtree->n.sym;
5967
5968   if (sym->ts.type == BT_CLASS)
5969     {
5970       allocatable = sym->ts.u.derived->components->attr.allocatable;
5971       pointer = sym->ts.u.derived->components->attr.pointer;
5972     }
5973   else
5974     {
5975       allocatable = sym->attr.allocatable;
5976       pointer = sym->attr.pointer;
5977     }
5978   for (ref = e->ref; ref; ref = ref->next)
5979     {
5980       if (pointer)
5981         check_intent_in = 0;
5982
5983       switch (ref->type)
5984         {
5985         case REF_ARRAY:
5986           if (ref->u.ar.type != AR_FULL)
5987             allocatable = 0;
5988           break;
5989
5990         case REF_COMPONENT:
5991           c = ref->u.c.component;
5992           if (c->ts.type == BT_CLASS)
5993             {
5994               allocatable = c->ts.u.derived->components->attr.allocatable;
5995               pointer = c->ts.u.derived->components->attr.pointer;
5996             }
5997           else
5998             {
5999               allocatable = c->attr.allocatable;
6000               pointer = c->attr.pointer;
6001             }
6002           break;
6003
6004         case REF_SUBSTRING:
6005           allocatable = 0;
6006           break;
6007         }
6008     }
6009
6010   attr = gfc_expr_attr (e);
6011
6012   if (allocatable == 0 && attr.pointer == 0)
6013     {
6014     bad:
6015       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6016                  &e->where);
6017     }
6018
6019   if (check_intent_in && sym->attr.intent == INTENT_IN)
6020     {
6021       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
6022                  sym->name, &e->where);
6023       return FAILURE;
6024     }
6025
6026   if (e->ts.type == BT_CLASS)
6027     {
6028       /* Only deallocate the DATA component.  */
6029       gfc_add_component_ref (e, "$data");
6030     }
6031
6032   return SUCCESS;
6033 }
6034
6035
6036 /* Returns true if the expression e contains a reference to the symbol sym.  */
6037 static bool
6038 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6039 {
6040   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6041     return true;
6042
6043   return false;
6044 }
6045
6046 bool
6047 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6048 {
6049   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6050 }
6051
6052
6053 /* Given the expression node e for an allocatable/pointer of derived type to be
6054    allocated, get the expression node to be initialized afterwards (needed for
6055    derived types with default initializers, and derived types with allocatable
6056    components that need nullification.)  */
6057
6058 gfc_expr *
6059 gfc_expr_to_initialize (gfc_expr *e)
6060 {
6061   gfc_expr *result;
6062   gfc_ref *ref;
6063   int i;
6064
6065   result = gfc_copy_expr (e);
6066
6067   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6068   for (ref = result->ref; ref; ref = ref->next)
6069     if (ref->type == REF_ARRAY && ref->next == NULL)
6070       {
6071         ref->u.ar.type = AR_FULL;
6072
6073         for (i = 0; i < ref->u.ar.dimen; i++)
6074           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6075
6076         result->rank = ref->u.ar.dimen;
6077         break;
6078       }
6079
6080   return result;
6081 }
6082
6083
6084 /* Used in resolve_allocate_expr to check that a allocation-object and
6085    a source-expr are conformable.  This does not catch all possible 
6086    cases; in particular a runtime checking is needed.  */
6087
6088 static gfc_try
6089 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6090 {
6091   /* First compare rank.  */
6092   if (e2->ref && e1->rank != e2->ref->u.ar.as->rank)
6093     {
6094       gfc_error ("Source-expr at %L must be scalar or have the "
6095                  "same rank as the allocate-object at %L",
6096                  &e1->where, &e2->where);
6097       return FAILURE;
6098     }
6099
6100   if (e1->shape)
6101     {
6102       int i;
6103       mpz_t s;
6104
6105       mpz_init (s);
6106
6107       for (i = 0; i < e1->rank; i++)
6108         {
6109           if (e2->ref->u.ar.end[i])
6110             {
6111               mpz_set (s, e2->ref->u.ar.end[i]->value.integer);
6112               mpz_sub (s, s, e2->ref->u.ar.start[i]->value.integer);
6113               mpz_add_ui (s, s, 1);
6114             }
6115           else
6116             {
6117               mpz_set (s, e2->ref->u.ar.start[i]->value.integer);
6118             }
6119
6120           if (mpz_cmp (e1->shape[i], s) != 0)
6121             {
6122               gfc_error ("Source-expr at %L and allocate-object at %L must "
6123                          "have the same shape", &e1->where, &e2->where);
6124               mpz_clear (s);
6125               return FAILURE;
6126             }
6127         }
6128
6129       mpz_clear (s);
6130     }
6131
6132   return SUCCESS;
6133 }
6134
6135
6136 /* Resolve the expression in an ALLOCATE statement, doing the additional
6137    checks to see whether the expression is OK or not.  The expression must
6138    have a trailing array reference that gives the size of the array.  */
6139
6140 static gfc_try
6141 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6142 {
6143   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6144   int codimension;
6145   symbol_attribute attr;
6146   gfc_ref *ref, *ref2;
6147   gfc_array_ref *ar;
6148   gfc_symbol *sym;
6149   gfc_alloc *a;
6150   gfc_component *c;
6151   gfc_expr *init_e;
6152
6153   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6154   check_intent_in = 1;
6155
6156   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6157      checking of coarrays.  */
6158   for (ref = e->ref; ref; ref = ref->next)
6159     if (ref->next == NULL)
6160       break;
6161
6162   if (ref && ref->type == REF_ARRAY)
6163     ref->u.ar.in_allocate = true;
6164
6165   if (gfc_resolve_expr (e) == FAILURE)
6166     goto failure;
6167
6168   /* Make sure the expression is allocatable or a pointer.  If it is
6169      pointer, the next-to-last reference must be a pointer.  */
6170
6171   ref2 = NULL;
6172   if (e->symtree)
6173     sym = e->symtree->n.sym;
6174
6175   /* Check whether ultimate component is abstract and CLASS.  */
6176   is_abstract = 0;
6177
6178   if (e->expr_type != EXPR_VARIABLE)
6179     {
6180       allocatable = 0;
6181       attr = gfc_expr_attr (e);
6182       pointer = attr.pointer;
6183       dimension = attr.dimension;
6184       codimension = attr.codimension;
6185     }
6186   else
6187     {
6188       if (sym->ts.type == BT_CLASS)
6189         {
6190           allocatable = sym->ts.u.derived->components->attr.allocatable;
6191           pointer = sym->ts.u.derived->components->attr.pointer;
6192           dimension = sym->ts.u.derived->components->attr.dimension;
6193           codimension = sym->ts.u.derived->components->attr.codimension;
6194           is_abstract = sym->ts.u.derived->components->attr.abstract;
6195         }
6196       else
6197         {
6198           allocatable = sym->attr.allocatable;
6199           pointer = sym->attr.pointer;
6200           dimension = sym->attr.dimension;
6201           codimension = sym->attr.codimension;
6202         }
6203
6204       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6205         {
6206           if (pointer)
6207             check_intent_in = 0;
6208
6209           switch (ref->type)
6210             {
6211               case REF_ARRAY:
6212                 if (ref->next != NULL)
6213                   pointer = 0;
6214                 break;
6215
6216               case REF_COMPONENT:
6217                 /* F2008, C644.  */
6218                 if (gfc_is_coindexed (e))
6219                   {
6220                     gfc_error ("Coindexed allocatable object at %L",
6221                                &e->where);
6222                     goto failure;
6223                   }
6224
6225                 c = ref->u.c.component;
6226                 if (c->ts.type == BT_CLASS)
6227                   {
6228                     allocatable = c->ts.u.derived->components->attr.allocatable;
6229                     pointer = c->ts.u.derived->components->attr.pointer;
6230                     dimension = c->ts.u.derived->components->attr.dimension;
6231                     codimension = c->ts.u.derived->components->attr.codimension;
6232                     is_abstract = c->ts.u.derived->components->attr.abstract;
6233                   }
6234                 else
6235                   {
6236                     allocatable = c->attr.allocatable;
6237                     pointer = c->attr.pointer;
6238                     dimension = c->attr.dimension;
6239                     codimension = c->attr.codimension;
6240                     is_abstract = c->attr.abstract;
6241                   }
6242                 break;
6243
6244               case REF_SUBSTRING:
6245                 allocatable = 0;
6246                 pointer = 0;
6247                 break;
6248             }
6249         }
6250     }
6251
6252   if (allocatable == 0 && pointer == 0)
6253     {
6254       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6255                  &e->where);
6256       goto failure;
6257     }
6258
6259   /* Some checks for the SOURCE tag.  */
6260   if (code->expr3)
6261     {
6262       /* Check F03:C631.  */
6263       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6264         {
6265           gfc_error ("Type of entity at %L is type incompatible with "
6266                       "source-expr at %L", &e->where, &code->expr3->where);
6267           goto failure;
6268         }
6269
6270       /* Check F03:C632 and restriction following Note 6.18.  */
6271       if (code->expr3->rank > 0
6272           && conformable_arrays (code->expr3, e) == FAILURE)
6273         goto failure;
6274
6275       /* Check F03:C633.  */
6276       if (code->expr3->ts.kind != e->ts.kind)
6277         {
6278           gfc_error ("The allocate-object at %L and the source-expr at %L "
6279                       "shall have the same kind type parameter",
6280                       &e->where, &code->expr3->where);
6281           goto failure;
6282         }
6283     }
6284   else if (is_abstract&& code->ext.alloc.ts.type == BT_UNKNOWN)
6285     {
6286       gcc_assert (e->ts.type == BT_CLASS);
6287       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6288                  "type-spec or SOURCE=", sym->name, &e->where);
6289       goto failure;
6290     }
6291
6292   if (check_intent_in && sym->attr.intent == INTENT_IN)
6293     {
6294       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6295                  sym->name, &e->where);
6296       goto failure;
6297     }
6298     
6299   if (!code->expr3)
6300     {
6301       /* Add default initializer for those derived types that need them.  */
6302       if (e->ts.type == BT_DERIVED
6303           && (init_e = gfc_default_initializer (&e->ts)))
6304         {
6305           gfc_code *init_st = gfc_get_code ();
6306           init_st->loc = code->loc;
6307           init_st->op = EXEC_INIT_ASSIGN;
6308           init_st->expr1 = gfc_expr_to_initialize (e);
6309           init_st->expr2 = init_e;
6310           init_st->next = code->next;
6311           code->next = init_st;
6312         }
6313       else if (e->ts.type == BT_CLASS
6314                && ((code->ext.alloc.ts.type == BT_UNKNOWN
6315                     && (init_e = gfc_default_initializer (&e->ts.u.derived->components->ts)))
6316                    || (code->ext.alloc.ts.type == BT_DERIVED
6317                        && (init_e = gfc_default_initializer (&code->ext.alloc.ts)))))
6318         {
6319           gfc_code *init_st = gfc_get_code ();
6320           init_st->loc = code->loc;
6321           init_st->op = EXEC_INIT_ASSIGN;
6322           init_st->expr1 = gfc_expr_to_initialize (e);
6323           init_st->expr2 = init_e;
6324           init_st->next = code->next;
6325           code->next = init_st;
6326         }
6327     }
6328
6329   if (pointer || (dimension == 0 && codimension == 0))
6330     goto success;
6331
6332   /* Make sure the next-to-last reference node is an array specification.  */
6333
6334   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6335       || (dimension && ref2->u.ar.dimen == 0))
6336     {
6337       gfc_error ("Array specification required in ALLOCATE statement "
6338                  "at %L", &e->where);
6339       goto failure;
6340     }
6341
6342   /* Make sure that the array section reference makes sense in the
6343     context of an ALLOCATE specification.  */
6344
6345   ar = &ref2->u.ar;
6346
6347   if (codimension && ar->codimen == 0)
6348     {
6349       gfc_error ("Coarray specification required in ALLOCATE statement "
6350                  "at %L", &e->where);
6351       goto failure;
6352     }
6353
6354   for (i = 0; i < ar->dimen; i++)
6355     {
6356       if (ref2->u.ar.type == AR_ELEMENT)
6357         goto check_symbols;
6358
6359       switch (ar->dimen_type[i])
6360         {
6361         case DIMEN_ELEMENT:
6362           break;
6363
6364         case DIMEN_RANGE:
6365           if (ar->start[i] != NULL
6366               && ar->end[i] != NULL
6367               && ar->stride[i] == NULL)
6368             break;
6369
6370           /* Fall Through...  */
6371
6372         case DIMEN_UNKNOWN:
6373         case DIMEN_VECTOR:
6374         case DIMEN_STAR:
6375           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6376                      &e->where);
6377           goto failure;
6378         }
6379
6380 check_symbols:
6381       for (a = code->ext.alloc.list; a; a = a->next)
6382         {
6383           sym = a->expr->symtree->n.sym;
6384
6385           /* TODO - check derived type components.  */
6386           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6387             continue;
6388
6389           if ((ar->start[i] != NULL
6390                && gfc_find_sym_in_expr (sym, ar->start[i]))
6391               || (ar->end[i] != NULL
6392                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6393             {
6394               gfc_error ("'%s' must not appear in the array specification at "
6395                          "%L in the same ALLOCATE statement where it is "
6396                          "itself allocated", sym->name, &ar->where);
6397               goto failure;
6398             }
6399         }
6400     }
6401
6402   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6403     {
6404       if (ar->dimen_type[i] == DIMEN_ELEMENT
6405           || ar->dimen_type[i] == DIMEN_RANGE)
6406         {
6407           if (i == (ar->dimen + ar->codimen - 1))
6408             {
6409               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6410                          "statement at %L", &e->where);
6411               goto failure;
6412             }
6413           break;
6414         }
6415
6416       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6417           && ar->stride[i] == NULL)
6418         break;
6419
6420       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6421                  &e->where);
6422       goto failure;
6423     }
6424
6425   if (codimension && ar->as->rank == 0)
6426     {
6427       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6428                  "at %L", &e->where);
6429       goto failure;
6430     }
6431
6432 success:
6433   return SUCCESS;
6434
6435 failure:
6436   return FAILURE;
6437 }
6438
6439 static void
6440 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6441 {
6442   gfc_expr *stat, *errmsg, *pe, *qe;
6443   gfc_alloc *a, *p, *q;
6444
6445   stat = code->expr1 ? code->expr1 : NULL;
6446
6447   errmsg = code->expr2 ? code->expr2 : NULL;
6448
6449   /* Check the stat variable.  */
6450   if (stat)
6451     {
6452       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6453         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6454                    stat->symtree->n.sym->name, &stat->where);
6455
6456       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6457         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6458                    &stat->where);
6459
6460       if ((stat->ts.type != BT_INTEGER
6461            && !(stat->ref && (stat->ref->type == REF_ARRAY
6462                               || stat->ref->type == REF_COMPONENT)))
6463           || stat->rank > 0)
6464         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6465                    "variable", &stat->where);
6466
6467       for (p = code->ext.alloc.list; p; p = p->next)
6468         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6469           gfc_error ("Stat-variable at %L shall not be %sd within "
6470                      "the same %s statement", &stat->where, fcn, fcn);
6471     }
6472
6473   /* Check the errmsg variable.  */
6474   if (errmsg)
6475     {
6476       if (!stat)
6477         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6478                      &errmsg->where);
6479
6480       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6481         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6482                    errmsg->symtree->n.sym->name, &errmsg->where);
6483
6484       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6485         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6486                    &errmsg->where);
6487
6488       if ((errmsg->ts.type != BT_CHARACTER
6489            && !(errmsg->ref
6490                 && (errmsg->ref->type == REF_ARRAY
6491                     || errmsg->ref->type == REF_COMPONENT)))
6492           || errmsg->rank > 0 )
6493         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6494                    "variable", &errmsg->where);
6495
6496       for (p = code->ext.alloc.list; p; p = p->next)
6497         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6498           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6499                      "the same %s statement", &errmsg->where, fcn, fcn);
6500     }
6501
6502   /* Check that an allocate-object appears only once in the statement.  
6503      FIXME: Checking derived types is disabled.  */
6504   for (p = code->ext.alloc.list; p; p = p->next)
6505     {
6506       pe = p->expr;
6507       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6508            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6509         {
6510           for (q = p->next; q; q = q->next)
6511             {
6512               qe = q->expr;
6513               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6514                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6515                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6516                 gfc_error ("Allocate-object at %L also appears at %L",
6517                            &pe->where, &qe->where);
6518             }
6519         }
6520     }
6521
6522   if (strcmp (fcn, "ALLOCATE") == 0)
6523     {
6524       for (a = code->ext.alloc.list; a; a = a->next)
6525         resolve_allocate_expr (a->expr, code);
6526     }
6527   else
6528     {
6529       for (a = code->ext.alloc.list; a; a = a->next)
6530         resolve_deallocate_expr (a->expr);
6531     }
6532 }
6533
6534
6535 /************ SELECT CASE resolution subroutines ************/
6536
6537 /* Callback function for our mergesort variant.  Determines interval
6538    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6539    op1 > op2.  Assumes we're not dealing with the default case.  
6540    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6541    There are nine situations to check.  */
6542
6543 static int
6544 compare_cases (const gfc_case *op1, const gfc_case *op2)
6545 {
6546   int retval;
6547
6548   if (op1->low == NULL) /* op1 = (:L)  */
6549     {
6550       /* op2 = (:N), so overlap.  */
6551       retval = 0;
6552       /* op2 = (M:) or (M:N),  L < M  */
6553       if (op2->low != NULL
6554           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6555         retval = -1;
6556     }
6557   else if (op1->high == NULL) /* op1 = (K:)  */
6558     {
6559       /* op2 = (M:), so overlap.  */
6560       retval = 0;
6561       /* op2 = (:N) or (M:N), K > N  */
6562       if (op2->high != NULL
6563           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6564         retval = 1;
6565     }
6566   else /* op1 = (K:L)  */
6567     {
6568       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6569         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6570                  ? 1 : 0;
6571       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6572         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6573                  ? -1 : 0;
6574       else                      /* op2 = (M:N)  */
6575         {
6576           retval =  0;
6577           /* L < M  */
6578           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6579             retval =  -1;
6580           /* K > N  */
6581           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6582             retval =  1;
6583         }
6584     }
6585
6586   return retval;
6587 }
6588
6589
6590 /* Merge-sort a double linked case list, detecting overlap in the
6591    process.  LIST is the head of the double linked case list before it
6592    is sorted.  Returns the head of the sorted list if we don't see any
6593    overlap, or NULL otherwise.  */
6594
6595 static gfc_case *
6596 check_case_overlap (gfc_case *list)
6597 {
6598   gfc_case *p, *q, *e, *tail;
6599   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6600
6601   /* If the passed list was empty, return immediately.  */
6602   if (!list)
6603     return NULL;
6604
6605   overlap_seen = 0;
6606   insize = 1;
6607
6608   /* Loop unconditionally.  The only exit from this loop is a return
6609      statement, when we've finished sorting the case list.  */
6610   for (;;)
6611     {
6612       p = list;
6613       list = NULL;
6614       tail = NULL;
6615
6616       /* Count the number of merges we do in this pass.  */
6617       nmerges = 0;
6618
6619       /* Loop while there exists a merge to be done.  */
6620       while (p)
6621         {
6622           int i;
6623
6624           /* Count this merge.  */
6625           nmerges++;
6626
6627           /* Cut the list in two pieces by stepping INSIZE places
6628              forward in the list, starting from P.  */
6629           psize = 0;
6630           q = p;
6631           for (i = 0; i < insize; i++)
6632             {
6633               psize++;
6634               q = q->right;
6635               if (!q)
6636                 break;
6637             }
6638           qsize = insize;
6639
6640           /* Now we have two lists.  Merge them!  */
6641           while (psize > 0 || (qsize > 0 && q != NULL))
6642             {
6643               /* See from which the next case to merge comes from.  */
6644               if (psize == 0)
6645                 {
6646                   /* P is empty so the next case must come from Q.  */
6647                   e = q;
6648                   q = q->right;
6649                   qsize--;
6650                 }
6651               else if (qsize == 0 || q == NULL)
6652                 {
6653                   /* Q is empty.  */
6654                   e = p;
6655                   p = p->right;
6656                   psize--;
6657                 }
6658               else
6659                 {
6660                   cmp = compare_cases (p, q);
6661                   if (cmp < 0)
6662                     {
6663                       /* The whole case range for P is less than the
6664                          one for Q.  */
6665                       e = p;
6666                       p = p->right;
6667                       psize--;
6668                     }
6669                   else if (cmp > 0)
6670                     {
6671                       /* The whole case range for Q is greater than
6672                          the case range for P.  */
6673                       e = q;
6674                       q = q->right;
6675                       qsize--;
6676                     }
6677                   else
6678                     {
6679                       /* The cases overlap, or they are the same
6680                          element in the list.  Either way, we must
6681                          issue an error and get the next case from P.  */
6682                       /* FIXME: Sort P and Q by line number.  */
6683                       gfc_error ("CASE label at %L overlaps with CASE "
6684                                  "label at %L", &p->where, &q->where);
6685                       overlap_seen = 1;
6686                       e = p;
6687                       p = p->right;
6688                       psize--;
6689                     }
6690                 }
6691
6692                 /* Add the next element to the merged list.  */
6693               if (tail)
6694                 tail->right = e;
6695               else
6696                 list = e;
6697               e->left = tail;
6698               tail = e;
6699             }
6700
6701           /* P has now stepped INSIZE places along, and so has Q.  So
6702              they're the same.  */
6703           p = q;
6704         }
6705       tail->right = NULL;
6706
6707       /* If we have done only one merge or none at all, we've
6708          finished sorting the cases.  */
6709       if (nmerges <= 1)
6710         {
6711           if (!overlap_seen)
6712             return list;
6713           else
6714             return NULL;
6715         }
6716
6717       /* Otherwise repeat, merging lists twice the size.  */
6718       insize *= 2;
6719     }
6720 }
6721
6722
6723 /* Check to see if an expression is suitable for use in a CASE statement.
6724    Makes sure that all case expressions are scalar constants of the same
6725    type.  Return FAILURE if anything is wrong.  */
6726
6727 static gfc_try
6728 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6729 {
6730   if (e == NULL) return SUCCESS;
6731
6732   if (e->ts.type != case_expr->ts.type)
6733     {
6734       gfc_error ("Expression in CASE statement at %L must be of type %s",
6735                  &e->where, gfc_basic_typename (case_expr->ts.type));
6736       return FAILURE;
6737     }
6738
6739   /* C805 (R808) For a given case-construct, each case-value shall be of
6740      the same type as case-expr.  For character type, length differences
6741      are allowed, but the kind type parameters shall be the same.  */
6742
6743   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6744     {
6745       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6746                  &e->where, case_expr->ts.kind);
6747       return FAILURE;
6748     }
6749
6750   /* Convert the case value kind to that of case expression kind,
6751      if needed */
6752
6753   if (e->ts.kind != case_expr->ts.kind)
6754     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6755
6756   if (e->rank != 0)
6757     {
6758       gfc_error ("Expression in CASE statement at %L must be scalar",
6759                  &e->where);
6760       return FAILURE;
6761     }
6762
6763   return SUCCESS;
6764 }
6765
6766
6767 /* Given a completely parsed select statement, we:
6768
6769      - Validate all expressions and code within the SELECT.
6770      - Make sure that the selection expression is not of the wrong type.
6771      - Make sure that no case ranges overlap.
6772      - Eliminate unreachable cases and unreachable code resulting from
6773        removing case labels.
6774
6775    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6776    they are a hassle for code generation, and to prevent that, we just
6777    cut them out here.  This is not necessary for overlapping cases
6778    because they are illegal and we never even try to generate code.
6779
6780    We have the additional caveat that a SELECT construct could have
6781    been a computed GOTO in the source code. Fortunately we can fairly
6782    easily work around that here: The case_expr for a "real" SELECT CASE
6783    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6784    we have to do is make sure that the case_expr is a scalar integer
6785    expression.  */
6786
6787 static void
6788 resolve_select (gfc_code *code)
6789 {
6790   gfc_code *body;
6791   gfc_expr *case_expr;
6792   gfc_case *cp, *default_case, *tail, *head;
6793   int seen_unreachable;
6794   int seen_logical;
6795   int ncases;
6796   bt type;
6797   gfc_try t;
6798
6799   if (code->expr1 == NULL)
6800     {
6801       /* This was actually a computed GOTO statement.  */
6802       case_expr = code->expr2;
6803       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6804         gfc_error ("Selection expression in computed GOTO statement "
6805                    "at %L must be a scalar integer expression",
6806                    &case_expr->where);
6807
6808       /* Further checking is not necessary because this SELECT was built
6809          by the compiler, so it should always be OK.  Just move the
6810          case_expr from expr2 to expr so that we can handle computed
6811          GOTOs as normal SELECTs from here on.  */
6812       code->expr1 = code->expr2;
6813       code->expr2 = NULL;
6814       return;
6815     }
6816
6817   case_expr = code->expr1;
6818
6819   type = case_expr->ts.type;
6820   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6821     {
6822       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6823                  &case_expr->where, gfc_typename (&case_expr->ts));
6824
6825       /* Punt. Going on here just produce more garbage error messages.  */
6826       return;
6827     }
6828
6829   if (case_expr->rank != 0)
6830     {
6831       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6832                  "expression", &case_expr->where);
6833
6834       /* Punt.  */
6835       return;
6836     }
6837
6838
6839   /* Raise a warning if an INTEGER case value exceeds the range of
6840      the case-expr. Later, all expressions will be promoted to the
6841      largest kind of all case-labels.  */
6842
6843   if (type == BT_INTEGER)
6844     for (body = code->block; body; body = body->block)
6845       for (cp = body->ext.case_list; cp; cp = cp->next)
6846         {
6847           if (cp->low
6848               && gfc_check_integer_range (cp->low->value.integer,
6849                                           case_expr->ts.kind) != ARITH_OK)
6850             gfc_warning ("Expression in CASE statement at %L is "
6851                          "not in the range of %s", &cp->low->where,
6852                          gfc_typename (&case_expr->ts));
6853
6854           if (cp->high
6855               && cp->low != cp->high
6856               && gfc_check_integer_range (cp->high->value.integer,
6857                                           case_expr->ts.kind) != ARITH_OK)
6858             gfc_warning ("Expression in CASE statement at %L is "
6859                          "not in the range of %s", &cp->high->where,
6860                          gfc_typename (&case_expr->ts));
6861         }
6862
6863   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6864      of the SELECT CASE expression and its CASE values.  Walk the lists
6865      of case values, and if we find a mismatch, promote case_expr to
6866      the appropriate kind.  */
6867
6868   if (type == BT_LOGICAL || type == BT_INTEGER)
6869     {
6870       for (body = code->block; body; body = body->block)
6871         {
6872           /* Walk the case label list.  */
6873           for (cp = body->ext.case_list; cp; cp = cp->next)
6874             {
6875               /* Intercept the DEFAULT case.  It does not have a kind.  */
6876               if (cp->low == NULL && cp->high == NULL)
6877                 continue;
6878
6879               /* Unreachable case ranges are discarded, so ignore.  */
6880               if (cp->low != NULL && cp->high != NULL
6881                   && cp->low != cp->high
6882                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6883                 continue;
6884
6885               if (cp->low != NULL
6886                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6887                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6888
6889               if (cp->high != NULL
6890                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6891                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6892             }
6893          }
6894     }
6895
6896   /* Assume there is no DEFAULT case.  */
6897   default_case = NULL;
6898   head = tail = NULL;
6899   ncases = 0;
6900   seen_logical = 0;
6901
6902   for (body = code->block; body; body = body->block)
6903     {
6904       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
6905       t = SUCCESS;
6906       seen_unreachable = 0;
6907
6908       /* Walk the case label list, making sure that all case labels
6909          are legal.  */
6910       for (cp = body->ext.case_list; cp; cp = cp->next)
6911         {
6912           /* Count the number of cases in the whole construct.  */
6913           ncases++;
6914
6915           /* Intercept the DEFAULT case.  */
6916           if (cp->low == NULL && cp->high == NULL)
6917             {
6918               if (default_case != NULL)
6919                 {
6920                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
6921                              "by a second DEFAULT CASE at %L",
6922                              &default_case->where, &cp->where);
6923                   t = FAILURE;
6924                   break;
6925                 }
6926               else
6927                 {
6928                   default_case = cp;
6929                   continue;
6930                 }
6931             }
6932
6933           /* Deal with single value cases and case ranges.  Errors are
6934              issued from the validation function.  */
6935           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
6936               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
6937             {
6938               t = FAILURE;
6939               break;
6940             }
6941
6942           if (type == BT_LOGICAL
6943               && ((cp->low == NULL || cp->high == NULL)
6944                   || cp->low != cp->high))
6945             {
6946               gfc_error ("Logical range in CASE statement at %L is not "
6947                          "allowed", &cp->low->where);
6948               t = FAILURE;
6949               break;
6950             }
6951
6952           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
6953             {
6954               int value;
6955               value = cp->low->value.logical == 0 ? 2 : 1;
6956               if (value & seen_logical)
6957                 {
6958                   gfc_error ("Constant logical value in CASE statement "
6959                              "is repeated at %L",
6960                              &cp->low->where);
6961                   t = FAILURE;
6962                   break;
6963                 }
6964               seen_logical |= value;
6965             }
6966
6967           if (cp->low != NULL && cp->high != NULL
6968               && cp->low != cp->high
6969               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6970             {
6971               if (gfc_option.warn_surprising)
6972                 gfc_warning ("Range specification at %L can never "
6973                              "be matched", &cp->where);
6974
6975               cp->unreachable = 1;
6976               seen_unreachable = 1;
6977             }
6978           else
6979             {
6980               /* If the case range can be matched, it can also overlap with
6981                  other cases.  To make sure it does not, we put it in a
6982                  double linked list here.  We sort that with a merge sort
6983                  later on to detect any overlapping cases.  */
6984               if (!head)
6985                 {
6986                   head = tail = cp;
6987                   head->right = head->left = NULL;
6988                 }
6989               else
6990                 {
6991                   tail->right = cp;
6992                   tail->right->left = tail;
6993                   tail = tail->right;
6994                   tail->right = NULL;
6995                 }
6996             }
6997         }
6998
6999       /* It there was a failure in the previous case label, give up
7000          for this case label list.  Continue with the next block.  */
7001       if (t == FAILURE)
7002         continue;
7003
7004       /* See if any case labels that are unreachable have been seen.
7005          If so, we eliminate them.  This is a bit of a kludge because
7006          the case lists for a single case statement (label) is a
7007          single forward linked lists.  */
7008       if (seen_unreachable)
7009       {
7010         /* Advance until the first case in the list is reachable.  */
7011         while (body->ext.case_list != NULL
7012                && body->ext.case_list->unreachable)
7013           {
7014             gfc_case *n = body->ext.case_list;
7015             body->ext.case_list = body->ext.case_list->next;
7016             n->next = NULL;
7017             gfc_free_case_list (n);
7018           }
7019
7020         /* Strip all other unreachable cases.  */
7021         if (body->ext.case_list)
7022           {
7023             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7024               {
7025                 if (cp->next->unreachable)
7026                   {
7027                     gfc_case *n = cp->next;
7028                     cp->next = cp->next->next;
7029                     n->next = NULL;
7030                     gfc_free_case_list (n);
7031                   }
7032               }
7033           }
7034       }
7035     }
7036
7037   /* See if there were overlapping cases.  If the check returns NULL,
7038      there was overlap.  In that case we don't do anything.  If head
7039      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7040      then used during code generation for SELECT CASE constructs with
7041      a case expression of a CHARACTER type.  */
7042   if (head)
7043     {
7044       head = check_case_overlap (head);
7045
7046       /* Prepend the default_case if it is there.  */
7047       if (head != NULL && default_case)
7048         {
7049           default_case->left = NULL;
7050           default_case->right = head;
7051           head->left = default_case;
7052         }
7053     }
7054
7055   /* Eliminate dead blocks that may be the result if we've seen
7056      unreachable case labels for a block.  */
7057   for (body = code; body && body->block; body = body->block)
7058     {
7059       if (body->block->ext.case_list == NULL)
7060         {
7061           /* Cut the unreachable block from the code chain.  */
7062           gfc_code *c = body->block;
7063           body->block = c->block;
7064
7065           /* Kill the dead block, but not the blocks below it.  */
7066           c->block = NULL;
7067           gfc_free_statements (c);
7068         }
7069     }
7070
7071   /* More than two cases is legal but insane for logical selects.
7072      Issue a warning for it.  */
7073   if (gfc_option.warn_surprising && type == BT_LOGICAL
7074       && ncases > 2)
7075     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7076                  &code->loc);
7077 }
7078
7079
7080 /* Check if a derived type is extensible.  */
7081
7082 bool
7083 gfc_type_is_extensible (gfc_symbol *sym)
7084 {
7085   return !(sym->attr.is_bind_c || sym->attr.sequence);
7086 }
7087
7088
7089 /* Resolve a SELECT TYPE statement.  */
7090
7091 static void
7092 resolve_select_type (gfc_code *code)
7093 {
7094   gfc_symbol *selector_type;
7095   gfc_code *body, *new_st, *if_st, *tail;
7096   gfc_code *class_is = NULL, *default_case = NULL;
7097   gfc_case *c;
7098   gfc_symtree *st;
7099   char name[GFC_MAX_SYMBOL_LEN];
7100   gfc_namespace *ns;
7101   int error = 0;
7102
7103   ns = code->ext.ns;
7104   gfc_resolve (ns);
7105
7106   /* Check for F03:C813.  */
7107   if (code->expr1->ts.type != BT_CLASS
7108       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7109     {
7110       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7111                  "at %L", &code->loc);
7112       return;
7113     }
7114
7115   if (code->expr2)
7116     {
7117       if (code->expr1->symtree->n.sym->attr.untyped)
7118         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7119       selector_type = code->expr2->ts.u.derived->components->ts.u.derived;
7120     }
7121   else
7122     selector_type = code->expr1->ts.u.derived->components->ts.u.derived;
7123
7124   /* Loop over TYPE IS / CLASS IS cases.  */
7125   for (body = code->block; body; body = body->block)
7126     {
7127       c = body->ext.case_list;
7128
7129       /* Check F03:C815.  */
7130       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7131           && !gfc_type_is_extensible (c->ts.u.derived))
7132         {
7133           gfc_error ("Derived type '%s' at %L must be extensible",
7134                      c->ts.u.derived->name, &c->where);
7135           error++;
7136           continue;
7137         }
7138
7139       /* Check F03:C816.  */
7140       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7141           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7142         {
7143           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7144                      c->ts.u.derived->name, &c->where, selector_type->name);
7145           error++;
7146           continue;
7147         }
7148
7149       /* Intercept the DEFAULT case.  */
7150       if (c->ts.type == BT_UNKNOWN)
7151         {
7152           /* Check F03:C818.  */
7153           if (default_case)
7154             {
7155               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7156                          "by a second DEFAULT CASE at %L",
7157                          &default_case->ext.case_list->where, &c->where);
7158               error++;
7159               continue;
7160             }
7161           else
7162             default_case = body;
7163         }
7164     }
7165     
7166   if (error>0)
7167     return;
7168
7169   if (code->expr2)
7170     {
7171       /* Insert assignment for selector variable.  */
7172       new_st = gfc_get_code ();
7173       new_st->op = EXEC_ASSIGN;
7174       new_st->expr1 = gfc_copy_expr (code->expr1);
7175       new_st->expr2 = gfc_copy_expr (code->expr2);
7176       ns->code = new_st;
7177     }
7178
7179   /* Put SELECT TYPE statement inside a BLOCK.  */
7180   new_st = gfc_get_code ();
7181   new_st->op = code->op;
7182   new_st->expr1 = code->expr1;
7183   new_st->expr2 = code->expr2;
7184   new_st->block = code->block;
7185   if (!ns->code)
7186     ns->code = new_st;
7187   else
7188     ns->code->next = new_st;
7189   code->op = EXEC_BLOCK;
7190   code->expr1 = code->expr2 =  NULL;
7191   code->block = NULL;
7192
7193   code = new_st;
7194
7195   /* Transform to EXEC_SELECT.  */
7196   code->op = EXEC_SELECT;
7197   gfc_add_component_ref (code->expr1, "$vptr");
7198   gfc_add_component_ref (code->expr1, "$hash");
7199
7200   /* Loop over TYPE IS / CLASS IS cases.  */
7201   for (body = code->block; body; body = body->block)
7202     {
7203       c = body->ext.case_list;
7204
7205       if (c->ts.type == BT_DERIVED)
7206         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7207                                              c->ts.u.derived->hash_value);
7208
7209       else if (c->ts.type == BT_UNKNOWN)
7210         continue;
7211
7212       /* Assign temporary to selector.  */
7213       if (c->ts.type == BT_CLASS)
7214         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7215       else
7216         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7217       st = gfc_find_symtree (ns->sym_root, name);
7218       new_st = gfc_get_code ();
7219       new_st->expr1 = gfc_get_variable_expr (st);
7220       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7221       if (c->ts.type == BT_DERIVED)
7222         {
7223           new_st->op = EXEC_POINTER_ASSIGN;
7224           gfc_add_component_ref (new_st->expr2, "$data");
7225         }
7226       else
7227         new_st->op = EXEC_POINTER_ASSIGN;
7228       new_st->next = body->next;
7229       body->next = new_st;
7230     }
7231     
7232   /* Take out CLASS IS cases for separate treatment.  */
7233   body = code;
7234   while (body && body->block)
7235     {
7236       if (body->block->ext.case_list->ts.type == BT_CLASS)
7237         {
7238           /* Add to class_is list.  */
7239           if (class_is == NULL)
7240             { 
7241               class_is = body->block;
7242               tail = class_is;
7243             }
7244           else
7245             {
7246               for (tail = class_is; tail->block; tail = tail->block) ;
7247               tail->block = body->block;
7248               tail = tail->block;
7249             }
7250           /* Remove from EXEC_SELECT list.  */
7251           body->block = body->block->block;
7252           tail->block = NULL;
7253         }
7254       else
7255         body = body->block;
7256     }
7257
7258   if (class_is)
7259     {
7260       gfc_symbol *vtab;
7261       
7262       if (!default_case)
7263         {
7264           /* Add a default case to hold the CLASS IS cases.  */
7265           for (tail = code; tail->block; tail = tail->block) ;
7266           tail->block = gfc_get_code ();
7267           tail = tail->block;
7268           tail->op = EXEC_SELECT_TYPE;
7269           tail->ext.case_list = gfc_get_case ();
7270           tail->ext.case_list->ts.type = BT_UNKNOWN;
7271           tail->next = NULL;
7272           default_case = tail;
7273         }
7274
7275       /* More than one CLASS IS block?  */
7276       if (class_is->block)
7277         {
7278           gfc_code **c1,*c2;
7279           bool swapped;
7280           /* Sort CLASS IS blocks by extension level.  */
7281           do
7282             {
7283               swapped = false;
7284               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7285                 {
7286                   c2 = (*c1)->block;
7287                   /* F03:C817 (check for doubles).  */
7288                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7289                       == c2->ext.case_list->ts.u.derived->hash_value)
7290                     {
7291                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7292                                  "statement at %L", &c2->ext.case_list->where);
7293                       return;
7294                     }
7295                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7296                       < c2->ext.case_list->ts.u.derived->attr.extension)
7297                     {
7298                       /* Swap.  */
7299                       (*c1)->block = c2->block;
7300                       c2->block = *c1;
7301                       *c1 = c2;
7302                       swapped = true;
7303                     }
7304                 }
7305             }
7306           while (swapped);
7307         }
7308         
7309       /* Generate IF chain.  */
7310       if_st = gfc_get_code ();
7311       if_st->op = EXEC_IF;
7312       new_st = if_st;
7313       for (body = class_is; body; body = body->block)
7314         {
7315           new_st->block = gfc_get_code ();
7316           new_st = new_st->block;
7317           new_st->op = EXEC_IF;
7318           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7319           new_st->expr1 = gfc_get_expr ();
7320           new_st->expr1->expr_type = EXPR_FUNCTION;
7321           new_st->expr1->ts.type = BT_LOGICAL;
7322           new_st->expr1->ts.kind = 4;
7323           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7324           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7325           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7326           /* Set up arguments.  */
7327           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7328           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7329           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7330           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived, true);
7331           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7332           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7333           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7334           new_st->next = body->next;
7335         }
7336         if (default_case->next)
7337           {
7338             new_st->block = gfc_get_code ();
7339             new_st = new_st->block;
7340             new_st->op = EXEC_IF;
7341             new_st->next = default_case->next;
7342           }
7343           
7344         /* Replace CLASS DEFAULT code by the IF chain.  */
7345         default_case->next = if_st;
7346     }
7347
7348   resolve_select (code);
7349
7350 }
7351
7352
7353 /* Resolve a transfer statement. This is making sure that:
7354    -- a derived type being transferred has only non-pointer components
7355    -- a derived type being transferred doesn't have private components, unless 
7356       it's being transferred from the module where the type was defined
7357    -- we're not trying to transfer a whole assumed size array.  */
7358
7359 static void
7360 resolve_transfer (gfc_code *code)
7361 {
7362   gfc_typespec *ts;
7363   gfc_symbol *sym;
7364   gfc_ref *ref;
7365   gfc_expr *exp;
7366
7367   exp = code->expr1;
7368
7369   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7370     return;
7371
7372   sym = exp->symtree->n.sym;
7373   ts = &sym->ts;
7374
7375   /* Go to actual component transferred.  */
7376   for (ref = code->expr1->ref; ref; ref = ref->next)
7377     if (ref->type == REF_COMPONENT)
7378       ts = &ref->u.c.component->ts;
7379
7380   if (ts->type == BT_DERIVED)
7381     {
7382       /* Check that transferred derived type doesn't contain POINTER
7383          components.  */
7384       if (ts->u.derived->attr.pointer_comp)
7385         {
7386           gfc_error ("Data transfer element at %L cannot have "
7387                      "POINTER components", &code->loc);
7388           return;
7389         }
7390
7391       if (ts->u.derived->attr.alloc_comp)
7392         {
7393           gfc_error ("Data transfer element at %L cannot have "
7394                      "ALLOCATABLE components", &code->loc);
7395           return;
7396         }
7397
7398       if (derived_inaccessible (ts->u.derived))
7399         {
7400           gfc_error ("Data transfer element at %L cannot have "
7401                      "PRIVATE components",&code->loc);
7402           return;
7403         }
7404     }
7405
7406   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7407       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7408     {
7409       gfc_error ("Data transfer element at %L cannot be a full reference to "
7410                  "an assumed-size array", &code->loc);
7411       return;
7412     }
7413 }
7414
7415
7416 /*********** Toplevel code resolution subroutines ***********/
7417
7418 /* Find the set of labels that are reachable from this block.  We also
7419    record the last statement in each block.  */
7420      
7421 static void
7422 find_reachable_labels (gfc_code *block)
7423 {
7424   gfc_code *c;
7425
7426   if (!block)
7427     return;
7428
7429   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7430
7431   /* Collect labels in this block.  We don't keep those corresponding
7432      to END {IF|SELECT}, these are checked in resolve_branch by going
7433      up through the code_stack.  */
7434   for (c = block; c; c = c->next)
7435     {
7436       if (c->here && c->op != EXEC_END_BLOCK)
7437         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7438     }
7439
7440   /* Merge with labels from parent block.  */
7441   if (cs_base->prev)
7442     {
7443       gcc_assert (cs_base->prev->reachable_labels);
7444       bitmap_ior_into (cs_base->reachable_labels,
7445                        cs_base->prev->reachable_labels);
7446     }
7447 }
7448
7449
7450 static void
7451 resolve_sync (gfc_code *code)
7452 {
7453   /* Check imageset. The * case matches expr1 == NULL.  */
7454   if (code->expr1)
7455     {
7456       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
7457         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
7458                    "INTEGER expression", &code->expr1->where);
7459       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
7460           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
7461         gfc_error ("Imageset argument at %L must between 1 and num_images()",
7462                    &code->expr1->where);
7463       else if (code->expr1->expr_type == EXPR_ARRAY
7464                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
7465         {
7466            gfc_constructor *cons;
7467            cons = gfc_constructor_first (code->expr1->value.constructor);
7468            for (; cons; cons = gfc_constructor_next (cons))
7469              if (cons->expr->expr_type == EXPR_CONSTANT
7470                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
7471                gfc_error ("Imageset argument at %L must between 1 and "
7472                           "num_images()", &cons->expr->where);
7473         }
7474     }
7475
7476   /* Check STAT.  */
7477   if (code->expr2
7478       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
7479           || code->expr2->expr_type != EXPR_VARIABLE))
7480     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
7481                &code->expr2->where);
7482
7483   /* Check ERRMSG.  */
7484   if (code->expr3
7485       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
7486           || code->expr3->expr_type != EXPR_VARIABLE))
7487     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
7488                &code->expr3->where);
7489 }
7490
7491
7492 /* Given a branch to a label, see if the branch is conforming.
7493    The code node describes where the branch is located.  */
7494
7495 static void
7496 resolve_branch (gfc_st_label *label, gfc_code *code)
7497 {
7498   code_stack *stack;
7499
7500   if (label == NULL)
7501     return;
7502
7503   /* Step one: is this a valid branching target?  */
7504
7505   if (label->defined == ST_LABEL_UNKNOWN)
7506     {
7507       gfc_error ("Label %d referenced at %L is never defined", label->value,
7508                  &label->where);
7509       return;
7510     }
7511
7512   if (label->defined != ST_LABEL_TARGET)
7513     {
7514       gfc_error ("Statement at %L is not a valid branch target statement "
7515                  "for the branch statement at %L", &label->where, &code->loc);
7516       return;
7517     }
7518
7519   /* Step two: make sure this branch is not a branch to itself ;-)  */
7520
7521   if (code->here == label)
7522     {
7523       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7524       return;
7525     }
7526
7527   /* Step three:  See if the label is in the same block as the
7528      branching statement.  The hard work has been done by setting up
7529      the bitmap reachable_labels.  */
7530
7531   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7532     {
7533       /* Check now whether there is a CRITICAL construct; if so, check
7534          whether the label is still visible outside of the CRITICAL block,
7535          which is invalid.  */
7536       for (stack = cs_base; stack; stack = stack->prev)
7537         if (stack->current->op == EXEC_CRITICAL
7538             && bitmap_bit_p (stack->reachable_labels, label->value))
7539           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7540                       " at %L", &code->loc, &label->where);
7541
7542       return;
7543     }
7544
7545   /* Step four:  If we haven't found the label in the bitmap, it may
7546     still be the label of the END of the enclosing block, in which
7547     case we find it by going up the code_stack.  */
7548
7549   for (stack = cs_base; stack; stack = stack->prev)
7550     {
7551       if (stack->current->next && stack->current->next->here == label)
7552         break;
7553       if (stack->current->op == EXEC_CRITICAL)
7554         {
7555           /* Note: A label at END CRITICAL does not leave the CRITICAL
7556              construct as END CRITICAL is still part of it.  */
7557           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7558                       " at %L", &code->loc, &label->where);
7559           return;
7560         }
7561     }
7562
7563   if (stack)
7564     {
7565       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7566       return;
7567     }
7568
7569   /* The label is not in an enclosing block, so illegal.  This was
7570      allowed in Fortran 66, so we allow it as extension.  No
7571      further checks are necessary in this case.  */
7572   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7573                   "as the GOTO statement at %L", &label->where,
7574                   &code->loc);
7575   return;
7576 }
7577
7578
7579 /* Check whether EXPR1 has the same shape as EXPR2.  */
7580
7581 static gfc_try
7582 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7583 {
7584   mpz_t shape[GFC_MAX_DIMENSIONS];
7585   mpz_t shape2[GFC_MAX_DIMENSIONS];
7586   gfc_try result = FAILURE;
7587   int i;
7588
7589   /* Compare the rank.  */
7590   if (expr1->rank != expr2->rank)
7591     return result;
7592
7593   /* Compare the size of each dimension.  */
7594   for (i=0; i<expr1->rank; i++)
7595     {
7596       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7597         goto ignore;
7598
7599       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7600         goto ignore;
7601
7602       if (mpz_cmp (shape[i], shape2[i]))
7603         goto over;
7604     }
7605
7606   /* When either of the two expression is an assumed size array, we
7607      ignore the comparison of dimension sizes.  */
7608 ignore:
7609   result = SUCCESS;
7610
7611 over:
7612   for (i--; i >= 0; i--)
7613     {
7614       mpz_clear (shape[i]);
7615       mpz_clear (shape2[i]);
7616     }
7617   return result;
7618 }
7619
7620
7621 /* Check whether a WHERE assignment target or a WHERE mask expression
7622    has the same shape as the outmost WHERE mask expression.  */
7623
7624 static void
7625 resolve_where (gfc_code *code, gfc_expr *mask)
7626 {
7627   gfc_code *cblock;
7628   gfc_code *cnext;
7629   gfc_expr *e = NULL;
7630
7631   cblock = code->block;
7632
7633   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7634      In case of nested WHERE, only the outmost one is stored.  */
7635   if (mask == NULL) /* outmost WHERE */
7636     e = cblock->expr1;
7637   else /* inner WHERE */
7638     e = mask;
7639
7640   while (cblock)
7641     {
7642       if (cblock->expr1)
7643         {
7644           /* Check if the mask-expr has a consistent shape with the
7645              outmost WHERE mask-expr.  */
7646           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7647             gfc_error ("WHERE mask at %L has inconsistent shape",
7648                        &cblock->expr1->where);
7649          }
7650
7651       /* the assignment statement of a WHERE statement, or the first
7652          statement in where-body-construct of a WHERE construct */
7653       cnext = cblock->next;
7654       while (cnext)
7655         {
7656           switch (cnext->op)
7657             {
7658             /* WHERE assignment statement */
7659             case EXEC_ASSIGN:
7660
7661               /* Check shape consistent for WHERE assignment target.  */
7662               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7663                gfc_error ("WHERE assignment target at %L has "
7664                           "inconsistent shape", &cnext->expr1->where);
7665               break;
7666
7667   
7668             case EXEC_ASSIGN_CALL:
7669               resolve_call (cnext);
7670               if (!cnext->resolved_sym->attr.elemental)
7671                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7672                           &cnext->ext.actual->expr->where);
7673               break;
7674
7675             /* WHERE or WHERE construct is part of a where-body-construct */
7676             case EXEC_WHERE:
7677               resolve_where (cnext, e);
7678               break;
7679
7680             default:
7681               gfc_error ("Unsupported statement inside WHERE at %L",
7682                          &cnext->loc);
7683             }
7684          /* the next statement within the same where-body-construct */
7685          cnext = cnext->next;
7686        }
7687     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7688     cblock = cblock->block;
7689   }
7690 }
7691
7692
7693 /* Resolve assignment in FORALL construct.
7694    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7695    FORALL index variables.  */
7696
7697 static void
7698 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7699 {
7700   int n;
7701
7702   for (n = 0; n < nvar; n++)
7703     {
7704       gfc_symbol *forall_index;
7705
7706       forall_index = var_expr[n]->symtree->n.sym;
7707
7708       /* Check whether the assignment target is one of the FORALL index
7709          variable.  */
7710       if ((code->expr1->expr_type == EXPR_VARIABLE)
7711           && (code->expr1->symtree->n.sym == forall_index))
7712         gfc_error ("Assignment to a FORALL index variable at %L",
7713                    &code->expr1->where);
7714       else
7715         {
7716           /* If one of the FORALL index variables doesn't appear in the
7717              assignment variable, then there could be a many-to-one
7718              assignment.  Emit a warning rather than an error because the
7719              mask could be resolving this problem.  */
7720           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7721             gfc_warning ("The FORALL with index '%s' is not used on the "
7722                          "left side of the assignment at %L and so might "
7723                          "cause multiple assignment to this object",
7724                          var_expr[n]->symtree->name, &code->expr1->where);
7725         }
7726     }
7727 }
7728
7729
7730 /* Resolve WHERE statement in FORALL construct.  */
7731
7732 static void
7733 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7734                                   gfc_expr **var_expr)
7735 {
7736   gfc_code *cblock;
7737   gfc_code *cnext;
7738
7739   cblock = code->block;
7740   while (cblock)
7741     {
7742       /* the assignment statement of a WHERE statement, or the first
7743          statement in where-body-construct of a WHERE construct */
7744       cnext = cblock->next;
7745       while (cnext)
7746         {
7747           switch (cnext->op)
7748             {
7749             /* WHERE assignment statement */
7750             case EXEC_ASSIGN:
7751               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7752               break;
7753   
7754             /* WHERE operator assignment statement */
7755             case EXEC_ASSIGN_CALL:
7756               resolve_call (cnext);
7757               if (!cnext->resolved_sym->attr.elemental)
7758                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7759                           &cnext->ext.actual->expr->where);
7760               break;
7761
7762             /* WHERE or WHERE construct is part of a where-body-construct */
7763             case EXEC_WHERE:
7764               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7765               break;
7766
7767             default:
7768               gfc_error ("Unsupported statement inside WHERE at %L",
7769                          &cnext->loc);
7770             }
7771           /* the next statement within the same where-body-construct */
7772           cnext = cnext->next;
7773         }
7774       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7775       cblock = cblock->block;
7776     }
7777 }
7778
7779
7780 /* Traverse the FORALL body to check whether the following errors exist:
7781    1. For assignment, check if a many-to-one assignment happens.
7782    2. For WHERE statement, check the WHERE body to see if there is any
7783       many-to-one assignment.  */
7784
7785 static void
7786 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7787 {
7788   gfc_code *c;
7789
7790   c = code->block->next;
7791   while (c)
7792     {
7793       switch (c->op)
7794         {
7795         case EXEC_ASSIGN:
7796         case EXEC_POINTER_ASSIGN:
7797           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7798           break;
7799
7800         case EXEC_ASSIGN_CALL:
7801           resolve_call (c);
7802           break;
7803
7804         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7805            there is no need to handle it here.  */
7806         case EXEC_FORALL:
7807           break;
7808         case EXEC_WHERE:
7809           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7810           break;
7811         default:
7812           break;
7813         }
7814       /* The next statement in the FORALL body.  */
7815       c = c->next;
7816     }
7817 }
7818
7819
7820 /* Counts the number of iterators needed inside a forall construct, including
7821    nested forall constructs. This is used to allocate the needed memory 
7822    in gfc_resolve_forall.  */
7823
7824 static int 
7825 gfc_count_forall_iterators (gfc_code *code)
7826 {
7827   int max_iters, sub_iters, current_iters;
7828   gfc_forall_iterator *fa;
7829
7830   gcc_assert(code->op == EXEC_FORALL);
7831   max_iters = 0;
7832   current_iters = 0;
7833
7834   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7835     current_iters ++;
7836   
7837   code = code->block->next;
7838
7839   while (code)
7840     {          
7841       if (code->op == EXEC_FORALL)
7842         {
7843           sub_iters = gfc_count_forall_iterators (code);
7844           if (sub_iters > max_iters)
7845             max_iters = sub_iters;
7846         }
7847       code = code->next;
7848     }
7849
7850   return current_iters + max_iters;
7851 }
7852
7853
7854 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7855    gfc_resolve_forall_body to resolve the FORALL body.  */
7856
7857 static void
7858 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7859 {
7860   static gfc_expr **var_expr;
7861   static int total_var = 0;
7862   static int nvar = 0;
7863   int old_nvar, tmp;
7864   gfc_forall_iterator *fa;
7865   int i;
7866
7867   old_nvar = nvar;
7868
7869   /* Start to resolve a FORALL construct   */
7870   if (forall_save == 0)
7871     {
7872       /* Count the total number of FORALL index in the nested FORALL
7873          construct in order to allocate the VAR_EXPR with proper size.  */
7874       total_var = gfc_count_forall_iterators (code);
7875
7876       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7877       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7878     }
7879
7880   /* The information about FORALL iterator, including FORALL index start, end
7881      and stride. The FORALL index can not appear in start, end or stride.  */
7882   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7883     {
7884       /* Check if any outer FORALL index name is the same as the current
7885          one.  */
7886       for (i = 0; i < nvar; i++)
7887         {
7888           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7889             {
7890               gfc_error ("An outer FORALL construct already has an index "
7891                          "with this name %L", &fa->var->where);
7892             }
7893         }
7894
7895       /* Record the current FORALL index.  */
7896       var_expr[nvar] = gfc_copy_expr (fa->var);
7897
7898       nvar++;
7899
7900       /* No memory leak.  */
7901       gcc_assert (nvar <= total_var);
7902     }
7903
7904   /* Resolve the FORALL body.  */
7905   gfc_resolve_forall_body (code, nvar, var_expr);
7906
7907   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7908   gfc_resolve_blocks (code->block, ns);
7909
7910   tmp = nvar;
7911   nvar = old_nvar;
7912   /* Free only the VAR_EXPRs allocated in this frame.  */
7913   for (i = nvar; i < tmp; i++)
7914      gfc_free_expr (var_expr[i]);
7915
7916   if (nvar == 0)
7917     {
7918       /* We are in the outermost FORALL construct.  */
7919       gcc_assert (forall_save == 0);
7920
7921       /* VAR_EXPR is not needed any more.  */
7922       gfc_free (var_expr);
7923       total_var = 0;
7924     }
7925 }
7926
7927
7928 /* Resolve a BLOCK construct statement.  */
7929
7930 static void
7931 resolve_block_construct (gfc_code* code)
7932 {
7933   /* Eventually, we may want to do some checks here or handle special stuff.
7934      But so far the only thing we can do is resolving the local namespace.  */
7935
7936   gfc_resolve (code->ext.ns);
7937 }
7938
7939
7940 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
7941    DO code nodes.  */
7942
7943 static void resolve_code (gfc_code *, gfc_namespace *);
7944
7945 void
7946 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
7947 {
7948   gfc_try t;
7949
7950   for (; b; b = b->block)
7951     {
7952       t = gfc_resolve_expr (b->expr1);
7953       if (gfc_resolve_expr (b->expr2) == FAILURE)
7954         t = FAILURE;
7955
7956       switch (b->op)
7957         {
7958         case EXEC_IF:
7959           if (t == SUCCESS && b->expr1 != NULL
7960               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
7961             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7962                        &b->expr1->where);
7963           break;
7964
7965         case EXEC_WHERE:
7966           if (t == SUCCESS
7967               && b->expr1 != NULL
7968               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
7969             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
7970                        &b->expr1->where);
7971           break;
7972
7973         case EXEC_GOTO:
7974           resolve_branch (b->label1, b);
7975           break;
7976
7977         case EXEC_BLOCK:
7978           resolve_block_construct (b);
7979           break;
7980
7981         case EXEC_SELECT:
7982         case EXEC_SELECT_TYPE:
7983         case EXEC_FORALL:
7984         case EXEC_DO:
7985         case EXEC_DO_WHILE:
7986         case EXEC_CRITICAL:
7987         case EXEC_READ:
7988         case EXEC_WRITE:
7989         case EXEC_IOLENGTH:
7990         case EXEC_WAIT:
7991           break;
7992
7993         case EXEC_OMP_ATOMIC:
7994         case EXEC_OMP_CRITICAL:
7995         case EXEC_OMP_DO:
7996         case EXEC_OMP_MASTER:
7997         case EXEC_OMP_ORDERED:
7998         case EXEC_OMP_PARALLEL:
7999         case EXEC_OMP_PARALLEL_DO:
8000         case EXEC_OMP_PARALLEL_SECTIONS:
8001         case EXEC_OMP_PARALLEL_WORKSHARE:
8002         case EXEC_OMP_SECTIONS:
8003         case EXEC_OMP_SINGLE:
8004         case EXEC_OMP_TASK:
8005         case EXEC_OMP_TASKWAIT:
8006         case EXEC_OMP_WORKSHARE:
8007           break;
8008
8009         default:
8010           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8011         }
8012
8013       resolve_code (b->next, ns);
8014     }
8015 }
8016
8017
8018 /* Does everything to resolve an ordinary assignment.  Returns true
8019    if this is an interface assignment.  */
8020 static bool
8021 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8022 {
8023   bool rval = false;
8024   gfc_expr *lhs;
8025   gfc_expr *rhs;
8026   int llen = 0;
8027   int rlen = 0;
8028   int n;
8029   gfc_ref *ref;
8030
8031   if (gfc_extend_assign (code, ns) == SUCCESS)
8032     {
8033       gfc_expr** rhsptr;
8034
8035       if (code->op == EXEC_ASSIGN_CALL)
8036         {
8037           lhs = code->ext.actual->expr;
8038           rhsptr = &code->ext.actual->next->expr;
8039         }
8040       else
8041         {
8042           gfc_actual_arglist* args;
8043           gfc_typebound_proc* tbp;
8044
8045           gcc_assert (code->op == EXEC_COMPCALL);
8046
8047           args = code->expr1->value.compcall.actual;
8048           lhs = args->expr;
8049           rhsptr = &args->next->expr;
8050
8051           tbp = code->expr1->value.compcall.tbp;
8052           gcc_assert (!tbp->is_generic);
8053         }
8054
8055       /* Make a temporary rhs when there is a default initializer
8056          and rhs is the same symbol as the lhs.  */
8057       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8058             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8059             && has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8060             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8061         *rhsptr = gfc_get_parentheses (*rhsptr);
8062
8063       return true;
8064     }
8065
8066   lhs = code->expr1;
8067   rhs = code->expr2;
8068
8069   if (rhs->is_boz
8070       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8071                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8072                          &code->loc) == FAILURE)
8073     return false;
8074
8075   /* Handle the case of a BOZ literal on the RHS.  */
8076   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8077     {
8078       int rc;
8079       if (gfc_option.warn_surprising)
8080         gfc_warning ("BOZ literal at %L is bitwise transferred "
8081                      "non-integer symbol '%s'", &code->loc,
8082                      lhs->symtree->n.sym->name);
8083
8084       if (!gfc_convert_boz (rhs, &lhs->ts))
8085         return false;
8086       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8087         {
8088           if (rc == ARITH_UNDERFLOW)
8089             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8090                        ". This check can be disabled with the option "
8091                        "-fno-range-check", &rhs->where);
8092           else if (rc == ARITH_OVERFLOW)
8093             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8094                        ". This check can be disabled with the option "
8095                        "-fno-range-check", &rhs->where);
8096           else if (rc == ARITH_NAN)
8097             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8098                        ". This check can be disabled with the option "
8099                        "-fno-range-check", &rhs->where);
8100           return false;
8101         }
8102     }
8103
8104
8105   if (lhs->ts.type == BT_CHARACTER
8106         && gfc_option.warn_character_truncation)
8107     {
8108       if (lhs->ts.u.cl != NULL
8109             && lhs->ts.u.cl->length != NULL
8110             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8111         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8112
8113       if (rhs->expr_type == EXPR_CONSTANT)
8114         rlen = rhs->value.character.length;
8115
8116       else if (rhs->ts.u.cl != NULL
8117                  && rhs->ts.u.cl->length != NULL
8118                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8119         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8120
8121       if (rlen && llen && rlen > llen)
8122         gfc_warning_now ("CHARACTER expression will be truncated "
8123                          "in assignment (%d/%d) at %L",
8124                          llen, rlen, &code->loc);
8125     }
8126
8127   /* Ensure that a vector index expression for the lvalue is evaluated
8128      to a temporary if the lvalue symbol is referenced in it.  */
8129   if (lhs->rank)
8130     {
8131       for (ref = lhs->ref; ref; ref= ref->next)
8132         if (ref->type == REF_ARRAY)
8133           {
8134             for (n = 0; n < ref->u.ar.dimen; n++)
8135               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8136                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8137                                            ref->u.ar.start[n]))
8138                 ref->u.ar.start[n]
8139                         = gfc_get_parentheses (ref->u.ar.start[n]);
8140           }
8141     }
8142
8143   if (gfc_pure (NULL))
8144     {
8145       if (gfc_impure_variable (lhs->symtree->n.sym))
8146         {
8147           gfc_error ("Cannot assign to variable '%s' in PURE "
8148                      "procedure at %L",
8149                       lhs->symtree->n.sym->name,
8150                       &lhs->where);
8151           return rval;
8152         }
8153
8154       if (lhs->ts.type == BT_DERIVED
8155             && lhs->expr_type == EXPR_VARIABLE
8156             && lhs->ts.u.derived->attr.pointer_comp
8157             && rhs->expr_type == EXPR_VARIABLE
8158             && (gfc_impure_variable (rhs->symtree->n.sym)
8159                 || gfc_is_coindexed (rhs)))
8160         {
8161           /* F2008, C1283.  */
8162           if (gfc_is_coindexed (rhs))
8163             gfc_error ("Coindexed expression at %L is assigned to "
8164                         "a derived type variable with a POINTER "
8165                         "component in a PURE procedure",
8166                         &rhs->where);
8167           else
8168             gfc_error ("The impure variable at %L is assigned to "
8169                         "a derived type variable with a POINTER "
8170                         "component in a PURE procedure (12.6)",
8171                         &rhs->where);
8172           return rval;
8173         }
8174
8175       /* Fortran 2008, C1283.  */
8176       if (gfc_is_coindexed (lhs))
8177         {
8178           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8179                      "procedure", &rhs->where);
8180           return rval;
8181         }
8182     }
8183
8184   /* F03:7.4.1.2.  */
8185   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8186      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8187   if (lhs->ts.type == BT_CLASS)
8188     {
8189       gfc_error ("Variable must not be polymorphic in assignment at %L",
8190                  &lhs->where);
8191       return false;
8192     }
8193
8194   /* F2008, Section 7.2.1.2.  */
8195   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8196     {
8197       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8198                  "component in assignment at %L", &lhs->where);
8199       return false;
8200     }
8201
8202   gfc_check_assign (lhs, rhs, 1);
8203   return false;
8204 }
8205
8206
8207 /* Given a block of code, recursively resolve everything pointed to by this
8208    code block.  */
8209
8210 static void
8211 resolve_code (gfc_code *code, gfc_namespace *ns)
8212 {
8213   int omp_workshare_save;
8214   int forall_save;
8215   code_stack frame;
8216   gfc_try t;
8217
8218   frame.prev = cs_base;
8219   frame.head = code;
8220   cs_base = &frame;
8221
8222   find_reachable_labels (code);
8223
8224   for (; code; code = code->next)
8225     {
8226       frame.current = code;
8227       forall_save = forall_flag;
8228
8229       if (code->op == EXEC_FORALL)
8230         {
8231           forall_flag = 1;
8232           gfc_resolve_forall (code, ns, forall_save);
8233           forall_flag = 2;
8234         }
8235       else if (code->block)
8236         {
8237           omp_workshare_save = -1;
8238           switch (code->op)
8239             {
8240             case EXEC_OMP_PARALLEL_WORKSHARE:
8241               omp_workshare_save = omp_workshare_flag;
8242               omp_workshare_flag = 1;
8243               gfc_resolve_omp_parallel_blocks (code, ns);
8244               break;
8245             case EXEC_OMP_PARALLEL:
8246             case EXEC_OMP_PARALLEL_DO:
8247             case EXEC_OMP_PARALLEL_SECTIONS:
8248             case EXEC_OMP_TASK:
8249               omp_workshare_save = omp_workshare_flag;
8250               omp_workshare_flag = 0;
8251               gfc_resolve_omp_parallel_blocks (code, ns);
8252               break;
8253             case EXEC_OMP_DO:
8254               gfc_resolve_omp_do_blocks (code, ns);
8255               break;
8256             case EXEC_SELECT_TYPE:
8257               gfc_current_ns = code->ext.ns;
8258               gfc_resolve_blocks (code->block, gfc_current_ns);
8259               gfc_current_ns = ns;
8260               break;
8261             case EXEC_OMP_WORKSHARE:
8262               omp_workshare_save = omp_workshare_flag;
8263               omp_workshare_flag = 1;
8264               /* FALLTHROUGH */
8265             default:
8266               gfc_resolve_blocks (code->block, ns);
8267               break;
8268             }
8269
8270           if (omp_workshare_save != -1)
8271             omp_workshare_flag = omp_workshare_save;
8272         }
8273
8274       t = SUCCESS;
8275       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8276         t = gfc_resolve_expr (code->expr1);
8277       forall_flag = forall_save;
8278
8279       if (gfc_resolve_expr (code->expr2) == FAILURE)
8280         t = FAILURE;
8281
8282       if (code->op == EXEC_ALLOCATE
8283           && gfc_resolve_expr (code->expr3) == FAILURE)
8284         t = FAILURE;
8285
8286       switch (code->op)
8287         {
8288         case EXEC_NOP:
8289         case EXEC_END_BLOCK:
8290         case EXEC_CYCLE:
8291         case EXEC_PAUSE:
8292         case EXEC_STOP:
8293         case EXEC_ERROR_STOP:
8294         case EXEC_EXIT:
8295         case EXEC_CONTINUE:
8296         case EXEC_DT_END:
8297         case EXEC_ASSIGN_CALL:
8298         case EXEC_CRITICAL:
8299           break;
8300
8301         case EXEC_SYNC_ALL:
8302         case EXEC_SYNC_IMAGES:
8303         case EXEC_SYNC_MEMORY:
8304           resolve_sync (code);
8305           break;
8306
8307         case EXEC_ENTRY:
8308           /* Keep track of which entry we are up to.  */
8309           current_entry_id = code->ext.entry->id;
8310           break;
8311
8312         case EXEC_WHERE:
8313           resolve_where (code, NULL);
8314           break;
8315
8316         case EXEC_GOTO:
8317           if (code->expr1 != NULL)
8318             {
8319               if (code->expr1->ts.type != BT_INTEGER)
8320                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8321                            "INTEGER variable", &code->expr1->where);
8322               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8323                 gfc_error ("Variable '%s' has not been assigned a target "
8324                            "label at %L", code->expr1->symtree->n.sym->name,
8325                            &code->expr1->where);
8326             }
8327           else
8328             resolve_branch (code->label1, code);
8329           break;
8330
8331         case EXEC_RETURN:
8332           if (code->expr1 != NULL
8333                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8334             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8335                        "INTEGER return specifier", &code->expr1->where);
8336           break;
8337
8338         case EXEC_INIT_ASSIGN:
8339         case EXEC_END_PROCEDURE:
8340           break;
8341
8342         case EXEC_ASSIGN:
8343           if (t == FAILURE)
8344             break;
8345
8346           if (resolve_ordinary_assign (code, ns))
8347             {
8348               if (code->op == EXEC_COMPCALL)
8349                 goto compcall;
8350               else
8351                 goto call;
8352             }
8353           break;
8354
8355         case EXEC_LABEL_ASSIGN:
8356           if (code->label1->defined == ST_LABEL_UNKNOWN)
8357             gfc_error ("Label %d referenced at %L is never defined",
8358                        code->label1->value, &code->label1->where);
8359           if (t == SUCCESS
8360               && (code->expr1->expr_type != EXPR_VARIABLE
8361                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8362                   || code->expr1->symtree->n.sym->ts.kind
8363                      != gfc_default_integer_kind
8364                   || code->expr1->symtree->n.sym->as != NULL))
8365             gfc_error ("ASSIGN statement at %L requires a scalar "
8366                        "default INTEGER variable", &code->expr1->where);
8367           break;
8368
8369         case EXEC_POINTER_ASSIGN:
8370           if (t == FAILURE)
8371             break;
8372
8373           gfc_check_pointer_assign (code->expr1, code->expr2);
8374           break;
8375
8376         case EXEC_ARITHMETIC_IF:
8377           if (t == SUCCESS
8378               && code->expr1->ts.type != BT_INTEGER
8379               && code->expr1->ts.type != BT_REAL)
8380             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8381                        "expression", &code->expr1->where);
8382
8383           resolve_branch (code->label1, code);
8384           resolve_branch (code->label2, code);
8385           resolve_branch (code->label3, code);
8386           break;
8387
8388         case EXEC_IF:
8389           if (t == SUCCESS && code->expr1 != NULL
8390               && (code->expr1->ts.type != BT_LOGICAL
8391                   || code->expr1->rank != 0))
8392             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8393                        &code->expr1->where);
8394           break;
8395
8396         case EXEC_CALL:
8397         call:
8398           resolve_call (code);
8399           break;
8400
8401         case EXEC_COMPCALL:
8402         compcall:
8403           resolve_typebound_subroutine (code);
8404           break;
8405
8406         case EXEC_CALL_PPC:
8407           resolve_ppc_call (code);
8408           break;
8409
8410         case EXEC_SELECT:
8411           /* Select is complicated. Also, a SELECT construct could be
8412              a transformed computed GOTO.  */
8413           resolve_select (code);
8414           break;
8415
8416         case EXEC_SELECT_TYPE:
8417           resolve_select_type (code);
8418           break;
8419
8420         case EXEC_BLOCK:
8421           gfc_resolve (code->ext.ns);
8422           break;
8423
8424         case EXEC_DO:
8425           if (code->ext.iterator != NULL)
8426             {
8427               gfc_iterator *iter = code->ext.iterator;
8428               if (gfc_resolve_iterator (iter, true) != FAILURE)
8429                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8430             }
8431           break;
8432
8433         case EXEC_DO_WHILE:
8434           if (code->expr1 == NULL)
8435             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8436           if (t == SUCCESS
8437               && (code->expr1->rank != 0
8438                   || code->expr1->ts.type != BT_LOGICAL))
8439             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8440                        "a scalar LOGICAL expression", &code->expr1->where);
8441           break;
8442
8443         case EXEC_ALLOCATE:
8444           if (t == SUCCESS)
8445             resolve_allocate_deallocate (code, "ALLOCATE");
8446
8447           break;
8448
8449         case EXEC_DEALLOCATE:
8450           if (t == SUCCESS)
8451             resolve_allocate_deallocate (code, "DEALLOCATE");
8452
8453           break;
8454
8455         case EXEC_OPEN:
8456           if (gfc_resolve_open (code->ext.open) == FAILURE)
8457             break;
8458
8459           resolve_branch (code->ext.open->err, code);
8460           break;
8461
8462         case EXEC_CLOSE:
8463           if (gfc_resolve_close (code->ext.close) == FAILURE)
8464             break;
8465
8466           resolve_branch (code->ext.close->err, code);
8467           break;
8468
8469         case EXEC_BACKSPACE:
8470         case EXEC_ENDFILE:
8471         case EXEC_REWIND:
8472         case EXEC_FLUSH:
8473           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8474             break;
8475
8476           resolve_branch (code->ext.filepos->err, code);
8477           break;
8478
8479         case EXEC_INQUIRE:
8480           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8481               break;
8482
8483           resolve_branch (code->ext.inquire->err, code);
8484           break;
8485
8486         case EXEC_IOLENGTH:
8487           gcc_assert (code->ext.inquire != NULL);
8488           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8489             break;
8490
8491           resolve_branch (code->ext.inquire->err, code);
8492           break;
8493
8494         case EXEC_WAIT:
8495           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8496             break;
8497
8498           resolve_branch (code->ext.wait->err, code);
8499           resolve_branch (code->ext.wait->end, code);
8500           resolve_branch (code->ext.wait->eor, code);
8501           break;
8502
8503         case EXEC_READ:
8504         case EXEC_WRITE:
8505           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8506             break;
8507
8508           resolve_branch (code->ext.dt->err, code);
8509           resolve_branch (code->ext.dt->end, code);
8510           resolve_branch (code->ext.dt->eor, code);
8511           break;
8512
8513         case EXEC_TRANSFER:
8514           resolve_transfer (code);
8515           break;
8516
8517         case EXEC_FORALL:
8518           resolve_forall_iterators (code->ext.forall_iterator);
8519
8520           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8521             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8522                        "expression", &code->expr1->where);
8523           break;
8524
8525         case EXEC_OMP_ATOMIC:
8526         case EXEC_OMP_BARRIER:
8527         case EXEC_OMP_CRITICAL:
8528         case EXEC_OMP_FLUSH:
8529         case EXEC_OMP_DO:
8530         case EXEC_OMP_MASTER:
8531         case EXEC_OMP_ORDERED:
8532         case EXEC_OMP_SECTIONS:
8533         case EXEC_OMP_SINGLE:
8534         case EXEC_OMP_TASKWAIT:
8535         case EXEC_OMP_WORKSHARE:
8536           gfc_resolve_omp_directive (code, ns);
8537           break;
8538
8539         case EXEC_OMP_PARALLEL:
8540         case EXEC_OMP_PARALLEL_DO:
8541         case EXEC_OMP_PARALLEL_SECTIONS:
8542         case EXEC_OMP_PARALLEL_WORKSHARE:
8543         case EXEC_OMP_TASK:
8544           omp_workshare_save = omp_workshare_flag;
8545           omp_workshare_flag = 0;
8546           gfc_resolve_omp_directive (code, ns);
8547           omp_workshare_flag = omp_workshare_save;
8548           break;
8549
8550         default:
8551           gfc_internal_error ("resolve_code(): Bad statement code");
8552         }
8553     }
8554
8555   cs_base = frame.prev;
8556 }
8557
8558
8559 /* Resolve initial values and make sure they are compatible with
8560    the variable.  */
8561
8562 static void
8563 resolve_values (gfc_symbol *sym)
8564 {
8565   if (sym->value == NULL)
8566     return;
8567
8568   if (gfc_resolve_expr (sym->value) == FAILURE)
8569     return;
8570
8571   gfc_check_assign_symbol (sym, sym->value);
8572 }
8573
8574
8575 /* Verify the binding labels for common blocks that are BIND(C).  The label
8576    for a BIND(C) common block must be identical in all scoping units in which
8577    the common block is declared.  Further, the binding label can not collide
8578    with any other global entity in the program.  */
8579
8580 static void
8581 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8582 {
8583   if (comm_block_tree->n.common->is_bind_c == 1)
8584     {
8585       gfc_gsymbol *binding_label_gsym;
8586       gfc_gsymbol *comm_name_gsym;
8587
8588       /* See if a global symbol exists by the common block's name.  It may
8589          be NULL if the common block is use-associated.  */
8590       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8591                                          comm_block_tree->n.common->name);
8592       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8593         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8594                    "with the global entity '%s' at %L",
8595                    comm_block_tree->n.common->binding_label,
8596                    comm_block_tree->n.common->name,
8597                    &(comm_block_tree->n.common->where),
8598                    comm_name_gsym->name, &(comm_name_gsym->where));
8599       else if (comm_name_gsym != NULL
8600                && strcmp (comm_name_gsym->name,
8601                           comm_block_tree->n.common->name) == 0)
8602         {
8603           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8604              as expected.  */
8605           if (comm_name_gsym->binding_label == NULL)
8606             /* No binding label for common block stored yet; save this one.  */
8607             comm_name_gsym->binding_label =
8608               comm_block_tree->n.common->binding_label;
8609           else
8610             if (strcmp (comm_name_gsym->binding_label,
8611                         comm_block_tree->n.common->binding_label) != 0)
8612               {
8613                 /* Common block names match but binding labels do not.  */
8614                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8615                            "does not match the binding label '%s' for common "
8616                            "block '%s' at %L",
8617                            comm_block_tree->n.common->binding_label,
8618                            comm_block_tree->n.common->name,
8619                            &(comm_block_tree->n.common->where),
8620                            comm_name_gsym->binding_label,
8621                            comm_name_gsym->name,
8622                            &(comm_name_gsym->where));
8623                 return;
8624               }
8625         }
8626
8627       /* There is no binding label (NAME="") so we have nothing further to
8628          check and nothing to add as a global symbol for the label.  */
8629       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8630         return;
8631       
8632       binding_label_gsym =
8633         gfc_find_gsymbol (gfc_gsym_root,
8634                           comm_block_tree->n.common->binding_label);
8635       if (binding_label_gsym == NULL)
8636         {
8637           /* Need to make a global symbol for the binding label to prevent
8638              it from colliding with another.  */
8639           binding_label_gsym =
8640             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8641           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8642           binding_label_gsym->type = GSYM_COMMON;
8643         }
8644       else
8645         {
8646           /* If comm_name_gsym is NULL, the name common block is use
8647              associated and the name could be colliding.  */
8648           if (binding_label_gsym->type != GSYM_COMMON)
8649             gfc_error ("Binding label '%s' for common block '%s' at %L "
8650                        "collides with the global entity '%s' at %L",
8651                        comm_block_tree->n.common->binding_label,
8652                        comm_block_tree->n.common->name,
8653                        &(comm_block_tree->n.common->where),
8654                        binding_label_gsym->name,
8655                        &(binding_label_gsym->where));
8656           else if (comm_name_gsym != NULL
8657                    && (strcmp (binding_label_gsym->name,
8658                                comm_name_gsym->binding_label) != 0)
8659                    && (strcmp (binding_label_gsym->sym_name,
8660                                comm_name_gsym->name) != 0))
8661             gfc_error ("Binding label '%s' for common block '%s' at %L "
8662                        "collides with global entity '%s' at %L",
8663                        binding_label_gsym->name, binding_label_gsym->sym_name,
8664                        &(comm_block_tree->n.common->where),
8665                        comm_name_gsym->name, &(comm_name_gsym->where));
8666         }
8667     }
8668   
8669   return;
8670 }
8671
8672
8673 /* Verify any BIND(C) derived types in the namespace so we can report errors
8674    for them once, rather than for each variable declared of that type.  */
8675
8676 static void
8677 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8678 {
8679   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8680       && derived_sym->attr.is_bind_c == 1)
8681     verify_bind_c_derived_type (derived_sym);
8682   
8683   return;
8684 }
8685
8686
8687 /* Verify that any binding labels used in a given namespace do not collide 
8688    with the names or binding labels of any global symbols.  */
8689
8690 static void
8691 gfc_verify_binding_labels (gfc_symbol *sym)
8692 {
8693   int has_error = 0;
8694   
8695   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8696       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8697     {
8698       gfc_gsymbol *bind_c_sym;
8699
8700       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8701       if (bind_c_sym != NULL 
8702           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8703         {
8704           if (sym->attr.if_source == IFSRC_DECL 
8705               && (bind_c_sym->type != GSYM_SUBROUTINE 
8706                   && bind_c_sym->type != GSYM_FUNCTION) 
8707               && ((sym->attr.contained == 1 
8708                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8709                   || (sym->attr.use_assoc == 1 
8710                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8711             {
8712               /* Make sure global procedures don't collide with anything.  */
8713               gfc_error ("Binding label '%s' at %L collides with the global "
8714                          "entity '%s' at %L", sym->binding_label,
8715                          &(sym->declared_at), bind_c_sym->name,
8716                          &(bind_c_sym->where));
8717               has_error = 1;
8718             }
8719           else if (sym->attr.contained == 0 
8720                    && (sym->attr.if_source == IFSRC_IFBODY 
8721                        && sym->attr.flavor == FL_PROCEDURE) 
8722                    && (bind_c_sym->sym_name != NULL 
8723                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8724             {
8725               /* Make sure procedures in interface bodies don't collide.  */
8726               gfc_error ("Binding label '%s' in interface body at %L collides "
8727                          "with the global entity '%s' at %L",
8728                          sym->binding_label,
8729                          &(sym->declared_at), bind_c_sym->name,
8730                          &(bind_c_sym->where));
8731               has_error = 1;
8732             }
8733           else if (sym->attr.contained == 0 
8734                    && sym->attr.if_source == IFSRC_UNKNOWN)
8735             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8736                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8737                 || sym->attr.use_assoc == 0)
8738               {
8739                 gfc_error ("Binding label '%s' at %L collides with global "
8740                            "entity '%s' at %L", sym->binding_label,
8741                            &(sym->declared_at), bind_c_sym->name,
8742                            &(bind_c_sym->where));
8743                 has_error = 1;
8744               }
8745
8746           if (has_error != 0)
8747             /* Clear the binding label to prevent checking multiple times.  */
8748             sym->binding_label[0] = '\0';
8749         }
8750       else if (bind_c_sym == NULL)
8751         {
8752           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8753           bind_c_sym->where = sym->declared_at;
8754           bind_c_sym->sym_name = sym->name;
8755
8756           if (sym->attr.use_assoc == 1)
8757             bind_c_sym->mod_name = sym->module;
8758           else
8759             if (sym->ns->proc_name != NULL)
8760               bind_c_sym->mod_name = sym->ns->proc_name->name;
8761
8762           if (sym->attr.contained == 0)
8763             {
8764               if (sym->attr.subroutine)
8765                 bind_c_sym->type = GSYM_SUBROUTINE;
8766               else if (sym->attr.function)
8767                 bind_c_sym->type = GSYM_FUNCTION;
8768             }
8769         }
8770     }
8771   return;
8772 }
8773
8774
8775 /* Resolve an index expression.  */
8776
8777 static gfc_try
8778 resolve_index_expr (gfc_expr *e)
8779 {
8780   if (gfc_resolve_expr (e) == FAILURE)
8781     return FAILURE;
8782
8783   if (gfc_simplify_expr (e, 0) == FAILURE)
8784     return FAILURE;
8785
8786   if (gfc_specification_expr (e) == FAILURE)
8787     return FAILURE;
8788
8789   return SUCCESS;
8790 }
8791
8792 /* Resolve a charlen structure.  */
8793
8794 static gfc_try
8795 resolve_charlen (gfc_charlen *cl)
8796 {
8797   int i, k;
8798
8799   if (cl->resolved)
8800     return SUCCESS;
8801
8802   cl->resolved = 1;
8803
8804   specification_expr = 1;
8805
8806   if (resolve_index_expr (cl->length) == FAILURE)
8807     {
8808       specification_expr = 0;
8809       return FAILURE;
8810     }
8811
8812   /* "If the character length parameter value evaluates to a negative
8813      value, the length of character entities declared is zero."  */
8814   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8815     {
8816       if (gfc_option.warn_surprising)
8817         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
8818                          " the length has been set to zero",
8819                          &cl->length->where, i);
8820       gfc_replace_expr (cl->length,
8821                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
8822     }
8823
8824   /* Check that the character length is not too large.  */
8825   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8826   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8827       && cl->length->ts.type == BT_INTEGER
8828       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8829     {
8830       gfc_error ("String length at %L is too large", &cl->length->where);
8831       return FAILURE;
8832     }
8833
8834   return SUCCESS;
8835 }
8836
8837
8838 /* Test for non-constant shape arrays.  */
8839
8840 static bool
8841 is_non_constant_shape_array (gfc_symbol *sym)
8842 {
8843   gfc_expr *e;
8844   int i;
8845   bool not_constant;
8846
8847   not_constant = false;
8848   if (sym->as != NULL)
8849     {
8850       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8851          has not been simplified; parameter array references.  Do the
8852          simplification now.  */
8853       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
8854         {
8855           e = sym->as->lower[i];
8856           if (e && (resolve_index_expr (e) == FAILURE
8857                     || !gfc_is_constant_expr (e)))
8858             not_constant = true;
8859           e = sym->as->upper[i];
8860           if (e && (resolve_index_expr (e) == FAILURE
8861                     || !gfc_is_constant_expr (e)))
8862             not_constant = true;
8863         }
8864     }
8865   return not_constant;
8866 }
8867
8868 /* Given a symbol and an initialization expression, add code to initialize
8869    the symbol to the function entry.  */
8870 static void
8871 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8872 {
8873   gfc_expr *lval;
8874   gfc_code *init_st;
8875   gfc_namespace *ns = sym->ns;
8876
8877   /* Search for the function namespace if this is a contained
8878      function without an explicit result.  */
8879   if (sym->attr.function && sym == sym->result
8880       && sym->name != sym->ns->proc_name->name)
8881     {
8882       ns = ns->contained;
8883       for (;ns; ns = ns->sibling)
8884         if (strcmp (ns->proc_name->name, sym->name) == 0)
8885           break;
8886     }
8887
8888   if (ns == NULL)
8889     {
8890       gfc_free_expr (init);
8891       return;
8892     }
8893
8894   /* Build an l-value expression for the result.  */
8895   lval = gfc_lval_expr_from_sym (sym);
8896
8897   /* Add the code at scope entry.  */
8898   init_st = gfc_get_code ();
8899   init_st->next = ns->code;
8900   ns->code = init_st;
8901
8902   /* Assign the default initializer to the l-value.  */
8903   init_st->loc = sym->declared_at;
8904   init_st->op = EXEC_INIT_ASSIGN;
8905   init_st->expr1 = lval;
8906   init_st->expr2 = init;
8907 }
8908
8909 /* Assign the default initializer to a derived type variable or result.  */
8910
8911 static void
8912 apply_default_init (gfc_symbol *sym)
8913 {
8914   gfc_expr *init = NULL;
8915
8916   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8917     return;
8918
8919   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
8920     init = gfc_default_initializer (&sym->ts);
8921
8922   if (init == NULL)
8923     return;
8924
8925   build_init_assign (sym, init);
8926 }
8927
8928 /* Build an initializer for a local integer, real, complex, logical, or
8929    character variable, based on the command line flags finit-local-zero,
8930    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
8931    null if the symbol should not have a default initialization.  */
8932 static gfc_expr *
8933 build_default_init_expr (gfc_symbol *sym)
8934 {
8935   int char_len;
8936   gfc_expr *init_expr;
8937   int i;
8938
8939   /* These symbols should never have a default initialization.  */
8940   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
8941       || sym->attr.external
8942       || sym->attr.dummy
8943       || sym->attr.pointer
8944       || sym->attr.in_equivalence
8945       || sym->attr.in_common
8946       || sym->attr.data
8947       || sym->module
8948       || sym->attr.cray_pointee
8949       || sym->attr.cray_pointer)
8950     return NULL;
8951
8952   /* Now we'll try to build an initializer expression.  */
8953   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
8954                                      &sym->declared_at);
8955
8956   /* We will only initialize integers, reals, complex, logicals, and
8957      characters, and only if the corresponding command-line flags
8958      were set.  Otherwise, we free init_expr and return null.  */
8959   switch (sym->ts.type)
8960     {    
8961     case BT_INTEGER:
8962       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
8963         mpz_init_set_si (init_expr->value.integer, 
8964                          gfc_option.flag_init_integer_value);
8965       else
8966         {
8967           gfc_free_expr (init_expr);
8968           init_expr = NULL;
8969         }
8970       break;
8971
8972     case BT_REAL:
8973       mpfr_init (init_expr->value.real);
8974       switch (gfc_option.flag_init_real)
8975         {
8976         case GFC_INIT_REAL_SNAN:
8977           init_expr->is_snan = 1;
8978           /* Fall through.  */
8979         case GFC_INIT_REAL_NAN:
8980           mpfr_set_nan (init_expr->value.real);
8981           break;
8982
8983         case GFC_INIT_REAL_INF:
8984           mpfr_set_inf (init_expr->value.real, 1);
8985           break;
8986
8987         case GFC_INIT_REAL_NEG_INF:
8988           mpfr_set_inf (init_expr->value.real, -1);
8989           break;
8990
8991         case GFC_INIT_REAL_ZERO:
8992           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
8993           break;
8994
8995         default:
8996           gfc_free_expr (init_expr);
8997           init_expr = NULL;
8998           break;
8999         }
9000       break;
9001           
9002     case BT_COMPLEX:
9003       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
9004       switch (gfc_option.flag_init_real)
9005         {
9006         case GFC_INIT_REAL_SNAN:
9007           init_expr->is_snan = 1;
9008           /* Fall through.  */
9009         case GFC_INIT_REAL_NAN:
9010           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9011           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9012           break;
9013
9014         case GFC_INIT_REAL_INF:
9015           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9016           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9017           break;
9018
9019         case GFC_INIT_REAL_NEG_INF:
9020           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9021           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9022           break;
9023
9024         case GFC_INIT_REAL_ZERO:
9025           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9026           break;
9027
9028         default:
9029           gfc_free_expr (init_expr);
9030           init_expr = NULL;
9031           break;
9032         }
9033       break;
9034           
9035     case BT_LOGICAL:
9036       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9037         init_expr->value.logical = 0;
9038       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9039         init_expr->value.logical = 1;
9040       else
9041         {
9042           gfc_free_expr (init_expr);
9043           init_expr = NULL;
9044         }
9045       break;
9046           
9047     case BT_CHARACTER:
9048       /* For characters, the length must be constant in order to 
9049          create a default initializer.  */
9050       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9051           && sym->ts.u.cl->length
9052           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9053         {
9054           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9055           init_expr->value.character.length = char_len;
9056           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9057           for (i = 0; i < char_len; i++)
9058             init_expr->value.character.string[i]
9059               = (unsigned char) gfc_option.flag_init_character_value;
9060         }
9061       else
9062         {
9063           gfc_free_expr (init_expr);
9064           init_expr = NULL;
9065         }
9066       break;
9067           
9068     default:
9069      gfc_free_expr (init_expr);
9070      init_expr = NULL;
9071     }
9072   return init_expr;
9073 }
9074
9075 /* Add an initialization expression to a local variable.  */
9076 static void
9077 apply_default_init_local (gfc_symbol *sym)
9078 {
9079   gfc_expr *init = NULL;
9080
9081   /* The symbol should be a variable or a function return value.  */
9082   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9083       || (sym->attr.function && sym->result != sym))
9084     return;
9085
9086   /* Try to build the initializer expression.  If we can't initialize
9087      this symbol, then init will be NULL.  */
9088   init = build_default_init_expr (sym);
9089   if (init == NULL)
9090     return;
9091
9092   /* For saved variables, we don't want to add an initializer at 
9093      function entry, so we just add a static initializer.  */
9094   if (sym->attr.save || sym->ns->save_all 
9095       || gfc_option.flag_max_stack_var_size == 0)
9096     {
9097       /* Don't clobber an existing initializer!  */
9098       gcc_assert (sym->value == NULL);
9099       sym->value = init;
9100       return;
9101     }
9102
9103   build_init_assign (sym, init);
9104 }
9105
9106 /* Resolution of common features of flavors variable and procedure.  */
9107
9108 static gfc_try
9109 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9110 {
9111   /* Constraints on deferred shape variable.  */
9112   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9113     {
9114       if (sym->attr.allocatable)
9115         {
9116           if (sym->attr.dimension)
9117             {
9118               gfc_error ("Allocatable array '%s' at %L must have "
9119                          "a deferred shape", sym->name, &sym->declared_at);
9120               return FAILURE;
9121             }
9122           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9123                                    "may not be ALLOCATABLE", sym->name,
9124                                    &sym->declared_at) == FAILURE)
9125             return FAILURE;
9126         }
9127
9128       if (sym->attr.pointer && sym->attr.dimension)
9129         {
9130           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9131                      sym->name, &sym->declared_at);
9132           return FAILURE;
9133         }
9134
9135     }
9136   else
9137     {
9138       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9139           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
9140         {
9141           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9142                      sym->name, &sym->declared_at);
9143           return FAILURE;
9144          }
9145     }
9146   return SUCCESS;
9147 }
9148
9149
9150 /* Additional checks for symbols with flavor variable and derived
9151    type.  To be called from resolve_fl_variable.  */
9152
9153 static gfc_try
9154 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9155 {
9156   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9157
9158   /* Check to see if a derived type is blocked from being host
9159      associated by the presence of another class I symbol in the same
9160      namespace.  14.6.1.3 of the standard and the discussion on
9161      comp.lang.fortran.  */
9162   if (sym->ns != sym->ts.u.derived->ns
9163       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9164     {
9165       gfc_symbol *s;
9166       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9167       if (s && s->attr.flavor != FL_DERIVED)
9168         {
9169           gfc_error ("The type '%s' cannot be host associated at %L "
9170                      "because it is blocked by an incompatible object "
9171                      "of the same name declared at %L",
9172                      sym->ts.u.derived->name, &sym->declared_at,
9173                      &s->declared_at);
9174           return FAILURE;
9175         }
9176     }
9177
9178   /* 4th constraint in section 11.3: "If an object of a type for which
9179      component-initialization is specified (R429) appears in the
9180      specification-part of a module and does not have the ALLOCATABLE
9181      or POINTER attribute, the object shall have the SAVE attribute."
9182
9183      The check for initializers is performed with
9184      has_default_initializer because gfc_default_initializer generates
9185      a hidden default for allocatable components.  */
9186   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9187       && sym->ns->proc_name->attr.flavor == FL_MODULE
9188       && !sym->ns->save_all && !sym->attr.save
9189       && !sym->attr.pointer && !sym->attr.allocatable
9190       && has_default_initializer (sym->ts.u.derived)
9191       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9192                          "module variable '%s' at %L, needed due to "
9193                          "the default initialization", sym->name,
9194                          &sym->declared_at) == FAILURE)
9195     return FAILURE;
9196
9197   if (sym->ts.type == BT_CLASS)
9198     {
9199       /* C502.  */
9200       if (!gfc_type_is_extensible (sym->ts.u.derived->components->ts.u.derived))
9201         {
9202           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9203                      sym->ts.u.derived->components->ts.u.derived->name,
9204                      sym->name, &sym->declared_at);
9205           return FAILURE;
9206         }
9207
9208       /* C509.  */
9209       /* Assume that use associated symbols were checked in the module ns.  */ 
9210       if (!sym->attr.class_ok && !sym->attr.use_assoc)
9211         {
9212           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9213                      "or pointer", sym->name, &sym->declared_at);
9214           return FAILURE;
9215         }
9216     }
9217
9218   /* Assign default initializer.  */
9219   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9220       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9221     {
9222       sym->value = gfc_default_initializer (&sym->ts);
9223     }
9224
9225   return SUCCESS;
9226 }
9227
9228
9229 /* Resolve symbols with flavor variable.  */
9230
9231 static gfc_try
9232 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9233 {
9234   int no_init_flag, automatic_flag;
9235   gfc_expr *e;
9236   const char *auto_save_msg;
9237
9238   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9239                   "SAVE attribute";
9240
9241   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9242     return FAILURE;
9243
9244   /* Set this flag to check that variables are parameters of all entries.
9245      This check is effected by the call to gfc_resolve_expr through
9246      is_non_constant_shape_array.  */
9247   specification_expr = 1;
9248
9249   if (sym->ns->proc_name
9250       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9251           || sym->ns->proc_name->attr.is_main_program)
9252       && !sym->attr.use_assoc
9253       && !sym->attr.allocatable
9254       && !sym->attr.pointer
9255       && is_non_constant_shape_array (sym))
9256     {
9257       /* The shape of a main program or module array needs to be
9258          constant.  */
9259       gfc_error ("The module or main program array '%s' at %L must "
9260                  "have constant shape", sym->name, &sym->declared_at);
9261       specification_expr = 0;
9262       return FAILURE;
9263     }
9264
9265   if (sym->ts.type == BT_CHARACTER)
9266     {
9267       /* Make sure that character string variables with assumed length are
9268          dummy arguments.  */
9269       e = sym->ts.u.cl->length;
9270       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9271         {
9272           gfc_error ("Entity with assumed character length at %L must be a "
9273                      "dummy argument or a PARAMETER", &sym->declared_at);
9274           return FAILURE;
9275         }
9276
9277       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9278         {
9279           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9280           return FAILURE;
9281         }
9282
9283       if (!gfc_is_constant_expr (e)
9284           && !(e->expr_type == EXPR_VARIABLE
9285                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9286           && sym->ns->proc_name
9287           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9288               || sym->ns->proc_name->attr.is_main_program)
9289           && !sym->attr.use_assoc)
9290         {
9291           gfc_error ("'%s' at %L must have constant character length "
9292                      "in this context", sym->name, &sym->declared_at);
9293           return FAILURE;
9294         }
9295     }
9296
9297   if (sym->value == NULL && sym->attr.referenced)
9298     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9299
9300   /* Determine if the symbol may not have an initializer.  */
9301   no_init_flag = automatic_flag = 0;
9302   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9303       || sym->attr.intrinsic || sym->attr.result)
9304     no_init_flag = 1;
9305   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9306            && is_non_constant_shape_array (sym))
9307     {
9308       no_init_flag = automatic_flag = 1;
9309
9310       /* Also, they must not have the SAVE attribute.
9311          SAVE_IMPLICIT is checked below.  */
9312       if (sym->attr.save == SAVE_EXPLICIT)
9313         {
9314           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9315           return FAILURE;
9316         }
9317     }
9318
9319   /* Ensure that any initializer is simplified.  */
9320   if (sym->value)
9321     gfc_simplify_expr (sym->value, 1);
9322
9323   /* Reject illegal initializers.  */
9324   if (!sym->mark && sym->value)
9325     {
9326       if (sym->attr.allocatable)
9327         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9328                    sym->name, &sym->declared_at);
9329       else if (sym->attr.external)
9330         gfc_error ("External '%s' at %L cannot have an initializer",
9331                    sym->name, &sym->declared_at);
9332       else if (sym->attr.dummy
9333         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9334         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9335                    sym->name, &sym->declared_at);
9336       else if (sym->attr.intrinsic)
9337         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9338                    sym->name, &sym->declared_at);
9339       else if (sym->attr.result)
9340         gfc_error ("Function result '%s' at %L cannot have an initializer",
9341                    sym->name, &sym->declared_at);
9342       else if (automatic_flag)
9343         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9344                    sym->name, &sym->declared_at);
9345       else
9346         goto no_init_error;
9347       return FAILURE;
9348     }
9349
9350 no_init_error:
9351   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9352     return resolve_fl_variable_derived (sym, no_init_flag);
9353
9354   return SUCCESS;
9355 }
9356
9357
9358 /* Resolve a procedure.  */
9359
9360 static gfc_try
9361 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9362 {
9363   gfc_formal_arglist *arg;
9364
9365   if (sym->attr.function
9366       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9367     return FAILURE;
9368
9369   if (sym->ts.type == BT_CHARACTER)
9370     {
9371       gfc_charlen *cl = sym->ts.u.cl;
9372
9373       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9374              && resolve_charlen (cl) == FAILURE)
9375         return FAILURE;
9376
9377       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9378           && sym->attr.proc == PROC_ST_FUNCTION)
9379         {
9380           gfc_error ("Character-valued statement function '%s' at %L must "
9381                      "have constant length", sym->name, &sym->declared_at);
9382           return FAILURE;
9383         }
9384     }
9385
9386   /* Ensure that derived type for are not of a private type.  Internal
9387      module procedures are excluded by 2.2.3.3 - i.e., they are not
9388      externally accessible and can access all the objects accessible in
9389      the host.  */
9390   if (!(sym->ns->parent
9391         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9392       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9393     {
9394       gfc_interface *iface;
9395
9396       for (arg = sym->formal; arg; arg = arg->next)
9397         {
9398           if (arg->sym
9399               && arg->sym->ts.type == BT_DERIVED
9400               && !arg->sym->ts.u.derived->attr.use_assoc
9401               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9402                                     arg->sym->ts.u.derived->ns->default_access)
9403               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9404                                  "PRIVATE type and cannot be a dummy argument"
9405                                  " of '%s', which is PUBLIC at %L",
9406                                  arg->sym->name, sym->name, &sym->declared_at)
9407                  == FAILURE)
9408             {
9409               /* Stop this message from recurring.  */
9410               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9411               return FAILURE;
9412             }
9413         }
9414
9415       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9416          PRIVATE to the containing module.  */
9417       for (iface = sym->generic; iface; iface = iface->next)
9418         {
9419           for (arg = iface->sym->formal; arg; arg = arg->next)
9420             {
9421               if (arg->sym
9422                   && arg->sym->ts.type == BT_DERIVED
9423                   && !arg->sym->ts.u.derived->attr.use_assoc
9424                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9425                                         arg->sym->ts.u.derived->ns->default_access)
9426                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9427                                      "'%s' in PUBLIC interface '%s' at %L "
9428                                      "takes dummy arguments of '%s' which is "
9429                                      "PRIVATE", iface->sym->name, sym->name,
9430                                      &iface->sym->declared_at,
9431                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9432                 {
9433                   /* Stop this message from recurring.  */
9434                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9435                   return FAILURE;
9436                 }
9437              }
9438         }
9439
9440       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9441          PRIVATE to the containing module.  */
9442       for (iface = sym->generic; iface; iface = iface->next)
9443         {
9444           for (arg = iface->sym->formal; arg; arg = arg->next)
9445             {
9446               if (arg->sym
9447                   && arg->sym->ts.type == BT_DERIVED
9448                   && !arg->sym->ts.u.derived->attr.use_assoc
9449                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9450                                         arg->sym->ts.u.derived->ns->default_access)
9451                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9452                                      "'%s' in PUBLIC interface '%s' at %L "
9453                                      "takes dummy arguments of '%s' which is "
9454                                      "PRIVATE", iface->sym->name, sym->name,
9455                                      &iface->sym->declared_at,
9456                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9457                 {
9458                   /* Stop this message from recurring.  */
9459                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9460                   return FAILURE;
9461                 }
9462              }
9463         }
9464     }
9465
9466   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9467       && !sym->attr.proc_pointer)
9468     {
9469       gfc_error ("Function '%s' at %L cannot have an initializer",
9470                  sym->name, &sym->declared_at);
9471       return FAILURE;
9472     }
9473
9474   /* An external symbol may not have an initializer because it is taken to be
9475      a procedure. Exception: Procedure Pointers.  */
9476   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9477     {
9478       gfc_error ("External object '%s' at %L may not have an initializer",
9479                  sym->name, &sym->declared_at);
9480       return FAILURE;
9481     }
9482
9483   /* An elemental function is required to return a scalar 12.7.1  */
9484   if (sym->attr.elemental && sym->attr.function && sym->as)
9485     {
9486       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9487                  "result", sym->name, &sym->declared_at);
9488       /* Reset so that the error only occurs once.  */
9489       sym->attr.elemental = 0;
9490       return FAILURE;
9491     }
9492
9493   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9494      char-len-param shall not be array-valued, pointer-valued, recursive
9495      or pure.  ....snip... A character value of * may only be used in the
9496      following ways: (i) Dummy arg of procedure - dummy associates with
9497      actual length; (ii) To declare a named constant; or (iii) External
9498      function - but length must be declared in calling scoping unit.  */
9499   if (sym->attr.function
9500       && sym->ts.type == BT_CHARACTER
9501       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9502     {
9503       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9504           || (sym->attr.recursive) || (sym->attr.pure))
9505         {
9506           if (sym->as && sym->as->rank)
9507             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9508                        "array-valued", sym->name, &sym->declared_at);
9509
9510           if (sym->attr.pointer)
9511             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9512                        "pointer-valued", sym->name, &sym->declared_at);
9513
9514           if (sym->attr.pure)
9515             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9516                        "pure", sym->name, &sym->declared_at);
9517
9518           if (sym->attr.recursive)
9519             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9520                        "recursive", sym->name, &sym->declared_at);
9521
9522           return FAILURE;
9523         }
9524
9525       /* Appendix B.2 of the standard.  Contained functions give an
9526          error anyway.  Fixed-form is likely to be F77/legacy.  */
9527       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9528         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9529                         "CHARACTER(*) function '%s' at %L",
9530                         sym->name, &sym->declared_at);
9531     }
9532
9533   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9534     {
9535       gfc_formal_arglist *curr_arg;
9536       int has_non_interop_arg = 0;
9537
9538       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9539                              sym->common_block) == FAILURE)
9540         {
9541           /* Clear these to prevent looking at them again if there was an
9542              error.  */
9543           sym->attr.is_bind_c = 0;
9544           sym->attr.is_c_interop = 0;
9545           sym->ts.is_c_interop = 0;
9546         }
9547       else
9548         {
9549           /* So far, no errors have been found.  */
9550           sym->attr.is_c_interop = 1;
9551           sym->ts.is_c_interop = 1;
9552         }
9553       
9554       curr_arg = sym->formal;
9555       while (curr_arg != NULL)
9556         {
9557           /* Skip implicitly typed dummy args here.  */
9558           if (curr_arg->sym->attr.implicit_type == 0)
9559             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9560               /* If something is found to fail, record the fact so we
9561                  can mark the symbol for the procedure as not being
9562                  BIND(C) to try and prevent multiple errors being
9563                  reported.  */
9564               has_non_interop_arg = 1;
9565           
9566           curr_arg = curr_arg->next;
9567         }
9568
9569       /* See if any of the arguments were not interoperable and if so, clear
9570          the procedure symbol to prevent duplicate error messages.  */
9571       if (has_non_interop_arg != 0)
9572         {
9573           sym->attr.is_c_interop = 0;
9574           sym->ts.is_c_interop = 0;
9575           sym->attr.is_bind_c = 0;
9576         }
9577     }
9578   
9579   if (!sym->attr.proc_pointer)
9580     {
9581       if (sym->attr.save == SAVE_EXPLICIT)
9582         {
9583           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9584                      "in '%s' at %L", sym->name, &sym->declared_at);
9585           return FAILURE;
9586         }
9587       if (sym->attr.intent)
9588         {
9589           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9590                      "in '%s' at %L", sym->name, &sym->declared_at);
9591           return FAILURE;
9592         }
9593       if (sym->attr.subroutine && sym->attr.result)
9594         {
9595           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9596                      "in '%s' at %L", sym->name, &sym->declared_at);
9597           return FAILURE;
9598         }
9599       if (sym->attr.external && sym->attr.function
9600           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9601               || sym->attr.contained))
9602         {
9603           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9604                      "in '%s' at %L", sym->name, &sym->declared_at);
9605           return FAILURE;
9606         }
9607       if (strcmp ("ppr@", sym->name) == 0)
9608         {
9609           gfc_error ("Procedure pointer result '%s' at %L "
9610                      "is missing the pointer attribute",
9611                      sym->ns->proc_name->name, &sym->declared_at);
9612           return FAILURE;
9613         }
9614     }
9615
9616   return SUCCESS;
9617 }
9618
9619
9620 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9621    been defined and we now know their defined arguments, check that they fulfill
9622    the requirements of the standard for procedures used as finalizers.  */
9623
9624 static gfc_try
9625 gfc_resolve_finalizers (gfc_symbol* derived)
9626 {
9627   gfc_finalizer* list;
9628   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9629   gfc_try result = SUCCESS;
9630   bool seen_scalar = false;
9631
9632   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9633     return SUCCESS;
9634
9635   /* Walk over the list of finalizer-procedures, check them, and if any one
9636      does not fit in with the standard's definition, print an error and remove
9637      it from the list.  */
9638   prev_link = &derived->f2k_derived->finalizers;
9639   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9640     {
9641       gfc_symbol* arg;
9642       gfc_finalizer* i;
9643       int my_rank;
9644
9645       /* Skip this finalizer if we already resolved it.  */
9646       if (list->proc_tree)
9647         {
9648           prev_link = &(list->next);
9649           continue;
9650         }
9651
9652       /* Check this exists and is a SUBROUTINE.  */
9653       if (!list->proc_sym->attr.subroutine)
9654         {
9655           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9656                      list->proc_sym->name, &list->where);
9657           goto error;
9658         }
9659
9660       /* We should have exactly one argument.  */
9661       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9662         {
9663           gfc_error ("FINAL procedure at %L must have exactly one argument",
9664                      &list->where);
9665           goto error;
9666         }
9667       arg = list->proc_sym->formal->sym;
9668
9669       /* This argument must be of our type.  */
9670       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9671         {
9672           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9673                      &arg->declared_at, derived->name);
9674           goto error;
9675         }
9676
9677       /* It must neither be a pointer nor allocatable nor optional.  */
9678       if (arg->attr.pointer)
9679         {
9680           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9681                      &arg->declared_at);
9682           goto error;
9683         }
9684       if (arg->attr.allocatable)
9685         {
9686           gfc_error ("Argument of FINAL procedure at %L must not be"
9687                      " ALLOCATABLE", &arg->declared_at);
9688           goto error;
9689         }
9690       if (arg->attr.optional)
9691         {
9692           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9693                      &arg->declared_at);
9694           goto error;
9695         }
9696
9697       /* It must not be INTENT(OUT).  */
9698       if (arg->attr.intent == INTENT_OUT)
9699         {
9700           gfc_error ("Argument of FINAL procedure at %L must not be"
9701                      " INTENT(OUT)", &arg->declared_at);
9702           goto error;
9703         }
9704
9705       /* Warn if the procedure is non-scalar and not assumed shape.  */
9706       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9707           && arg->as->type != AS_ASSUMED_SHAPE)
9708         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9709                      " shape argument", &arg->declared_at);
9710
9711       /* Check that it does not match in kind and rank with a FINAL procedure
9712          defined earlier.  To really loop over the *earlier* declarations,
9713          we need to walk the tail of the list as new ones were pushed at the
9714          front.  */
9715       /* TODO: Handle kind parameters once they are implemented.  */
9716       my_rank = (arg->as ? arg->as->rank : 0);
9717       for (i = list->next; i; i = i->next)
9718         {
9719           /* Argument list might be empty; that is an error signalled earlier,
9720              but we nevertheless continued resolving.  */
9721           if (i->proc_sym->formal)
9722             {
9723               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9724               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9725               if (i_rank == my_rank)
9726                 {
9727                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9728                              " rank (%d) as '%s'",
9729                              list->proc_sym->name, &list->where, my_rank, 
9730                              i->proc_sym->name);
9731                   goto error;
9732                 }
9733             }
9734         }
9735
9736         /* Is this the/a scalar finalizer procedure?  */
9737         if (!arg->as || arg->as->rank == 0)
9738           seen_scalar = true;
9739
9740         /* Find the symtree for this procedure.  */
9741         gcc_assert (!list->proc_tree);
9742         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9743
9744         prev_link = &list->next;
9745         continue;
9746
9747         /* Remove wrong nodes immediately from the list so we don't risk any
9748            troubles in the future when they might fail later expectations.  */
9749 error:
9750         result = FAILURE;
9751         i = list;
9752         *prev_link = list->next;
9753         gfc_free_finalizer (i);
9754     }
9755
9756   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9757      were nodes in the list, must have been for arrays.  It is surely a good
9758      idea to have a scalar version there if there's something to finalize.  */
9759   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9760     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9761                  " defined at %L, suggest also scalar one",
9762                  derived->name, &derived->declared_at);
9763
9764   /* TODO:  Remove this error when finalization is finished.  */
9765   gfc_error ("Finalization at %L is not yet implemented",
9766              &derived->declared_at);
9767
9768   return result;
9769 }
9770
9771
9772 /* Check that it is ok for the typebound procedure proc to override the
9773    procedure old.  */
9774
9775 static gfc_try
9776 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9777 {
9778   locus where;
9779   const gfc_symbol* proc_target;
9780   const gfc_symbol* old_target;
9781   unsigned proc_pass_arg, old_pass_arg, argpos;
9782   gfc_formal_arglist* proc_formal;
9783   gfc_formal_arglist* old_formal;
9784
9785   /* This procedure should only be called for non-GENERIC proc.  */
9786   gcc_assert (!proc->n.tb->is_generic);
9787
9788   /* If the overwritten procedure is GENERIC, this is an error.  */
9789   if (old->n.tb->is_generic)
9790     {
9791       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9792                  old->name, &proc->n.tb->where);
9793       return FAILURE;
9794     }
9795
9796   where = proc->n.tb->where;
9797   proc_target = proc->n.tb->u.specific->n.sym;
9798   old_target = old->n.tb->u.specific->n.sym;
9799
9800   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9801   if (old->n.tb->non_overridable)
9802     {
9803       gfc_error ("'%s' at %L overrides a procedure binding declared"
9804                  " NON_OVERRIDABLE", proc->name, &where);
9805       return FAILURE;
9806     }
9807
9808   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9809   if (!old->n.tb->deferred && proc->n.tb->deferred)
9810     {
9811       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9812                  " non-DEFERRED binding", proc->name, &where);
9813       return FAILURE;
9814     }
9815
9816   /* If the overridden binding is PURE, the overriding must be, too.  */
9817   if (old_target->attr.pure && !proc_target->attr.pure)
9818     {
9819       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9820                  proc->name, &where);
9821       return FAILURE;
9822     }
9823
9824   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9825      is not, the overriding must not be either.  */
9826   if (old_target->attr.elemental && !proc_target->attr.elemental)
9827     {
9828       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9829                  " ELEMENTAL", proc->name, &where);
9830       return FAILURE;
9831     }
9832   if (!old_target->attr.elemental && proc_target->attr.elemental)
9833     {
9834       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9835                  " be ELEMENTAL, either", proc->name, &where);
9836       return FAILURE;
9837     }
9838
9839   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9840      SUBROUTINE.  */
9841   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9842     {
9843       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9844                  " SUBROUTINE", proc->name, &where);
9845       return FAILURE;
9846     }
9847
9848   /* If the overridden binding is a FUNCTION, the overriding must also be a
9849      FUNCTION and have the same characteristics.  */
9850   if (old_target->attr.function)
9851     {
9852       if (!proc_target->attr.function)
9853         {
9854           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9855                      " FUNCTION", proc->name, &where);
9856           return FAILURE;
9857         }
9858
9859       /* FIXME:  Do more comprehensive checking (including, for instance, the
9860          rank and array-shape).  */
9861       gcc_assert (proc_target->result && old_target->result);
9862       if (!gfc_compare_types (&proc_target->result->ts,
9863                               &old_target->result->ts))
9864         {
9865           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9866                      " matching result types", proc->name, &where);
9867           return FAILURE;
9868         }
9869     }
9870
9871   /* If the overridden binding is PUBLIC, the overriding one must not be
9872      PRIVATE.  */
9873   if (old->n.tb->access == ACCESS_PUBLIC
9874       && proc->n.tb->access == ACCESS_PRIVATE)
9875     {
9876       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9877                  " PRIVATE", proc->name, &where);
9878       return FAILURE;
9879     }
9880
9881   /* Compare the formal argument lists of both procedures.  This is also abused
9882      to find the position of the passed-object dummy arguments of both
9883      bindings as at least the overridden one might not yet be resolved and we
9884      need those positions in the check below.  */
9885   proc_pass_arg = old_pass_arg = 0;
9886   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9887     proc_pass_arg = 1;
9888   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9889     old_pass_arg = 1;
9890   argpos = 1;
9891   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9892        proc_formal && old_formal;
9893        proc_formal = proc_formal->next, old_formal = old_formal->next)
9894     {
9895       if (proc->n.tb->pass_arg
9896           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9897         proc_pass_arg = argpos;
9898       if (old->n.tb->pass_arg
9899           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9900         old_pass_arg = argpos;
9901
9902       /* Check that the names correspond.  */
9903       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9904         {
9905           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9906                      " to match the corresponding argument of the overridden"
9907                      " procedure", proc_formal->sym->name, proc->name, &where,
9908                      old_formal->sym->name);
9909           return FAILURE;
9910         }
9911
9912       /* Check that the types correspond if neither is the passed-object
9913          argument.  */
9914       /* FIXME:  Do more comprehensive testing here.  */
9915       if (proc_pass_arg != argpos && old_pass_arg != argpos
9916           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
9917         {
9918           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
9919                      "in respect to the overridden procedure",
9920                      proc_formal->sym->name, proc->name, &where);
9921           return FAILURE;
9922         }
9923
9924       ++argpos;
9925     }
9926   if (proc_formal || old_formal)
9927     {
9928       gfc_error ("'%s' at %L must have the same number of formal arguments as"
9929                  " the overridden procedure", proc->name, &where);
9930       return FAILURE;
9931     }
9932
9933   /* If the overridden binding is NOPASS, the overriding one must also be
9934      NOPASS.  */
9935   if (old->n.tb->nopass && !proc->n.tb->nopass)
9936     {
9937       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
9938                  " NOPASS", proc->name, &where);
9939       return FAILURE;
9940     }
9941
9942   /* If the overridden binding is PASS(x), the overriding one must also be
9943      PASS and the passed-object dummy arguments must correspond.  */
9944   if (!old->n.tb->nopass)
9945     {
9946       if (proc->n.tb->nopass)
9947         {
9948           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
9949                      " PASS", proc->name, &where);
9950           return FAILURE;
9951         }
9952
9953       if (proc_pass_arg != old_pass_arg)
9954         {
9955           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
9956                      " the same position as the passed-object dummy argument of"
9957                      " the overridden procedure", proc->name, &where);
9958           return FAILURE;
9959         }
9960     }
9961
9962   return SUCCESS;
9963 }
9964
9965
9966 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
9967
9968 static gfc_try
9969 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
9970                              const char* generic_name, locus where)
9971 {
9972   gfc_symbol* sym1;
9973   gfc_symbol* sym2;
9974
9975   gcc_assert (t1->specific && t2->specific);
9976   gcc_assert (!t1->specific->is_generic);
9977   gcc_assert (!t2->specific->is_generic);
9978
9979   sym1 = t1->specific->u.specific->n.sym;
9980   sym2 = t2->specific->u.specific->n.sym;
9981
9982   if (sym1 == sym2)
9983     return SUCCESS;
9984
9985   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
9986   if (sym1->attr.subroutine != sym2->attr.subroutine
9987       || sym1->attr.function != sym2->attr.function)
9988     {
9989       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
9990                  " GENERIC '%s' at %L",
9991                  sym1->name, sym2->name, generic_name, &where);
9992       return FAILURE;
9993     }
9994
9995   /* Compare the interfaces.  */
9996   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
9997     {
9998       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
9999                  sym1->name, sym2->name, generic_name, &where);
10000       return FAILURE;
10001     }
10002
10003   return SUCCESS;
10004 }
10005
10006
10007 /* Worker function for resolving a generic procedure binding; this is used to
10008    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10009
10010    The difference between those cases is finding possible inherited bindings
10011    that are overridden, as one has to look for them in tb_sym_root,
10012    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10013    the super-type and set p->overridden correctly.  */
10014
10015 static gfc_try
10016 resolve_tb_generic_targets (gfc_symbol* super_type,
10017                             gfc_typebound_proc* p, const char* name)
10018 {
10019   gfc_tbp_generic* target;
10020   gfc_symtree* first_target;
10021   gfc_symtree* inherited;
10022
10023   gcc_assert (p && p->is_generic);
10024
10025   /* Try to find the specific bindings for the symtrees in our target-list.  */
10026   gcc_assert (p->u.generic);
10027   for (target = p->u.generic; target; target = target->next)
10028     if (!target->specific)
10029       {
10030         gfc_typebound_proc* overridden_tbp;
10031         gfc_tbp_generic* g;
10032         const char* target_name;
10033
10034         target_name = target->specific_st->name;
10035
10036         /* Defined for this type directly.  */
10037         if (target->specific_st->n.tb)
10038           {
10039             target->specific = target->specific_st->n.tb;
10040             goto specific_found;
10041           }
10042
10043         /* Look for an inherited specific binding.  */
10044         if (super_type)
10045           {
10046             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10047                                                  true, NULL);
10048
10049             if (inherited)
10050               {
10051                 gcc_assert (inherited->n.tb);
10052                 target->specific = inherited->n.tb;
10053                 goto specific_found;
10054               }
10055           }
10056
10057         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10058                    " at %L", target_name, name, &p->where);
10059         return FAILURE;
10060
10061         /* Once we've found the specific binding, check it is not ambiguous with
10062            other specifics already found or inherited for the same GENERIC.  */
10063 specific_found:
10064         gcc_assert (target->specific);
10065
10066         /* This must really be a specific binding!  */
10067         if (target->specific->is_generic)
10068           {
10069             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10070                        " '%s' is GENERIC, too", name, &p->where, target_name);
10071             return FAILURE;
10072           }
10073
10074         /* Check those already resolved on this type directly.  */
10075         for (g = p->u.generic; g; g = g->next)
10076           if (g != target && g->specific
10077               && check_generic_tbp_ambiguity (target, g, name, p->where)
10078                   == FAILURE)
10079             return FAILURE;
10080
10081         /* Check for ambiguity with inherited specific targets.  */
10082         for (overridden_tbp = p->overridden; overridden_tbp;
10083              overridden_tbp = overridden_tbp->overridden)
10084           if (overridden_tbp->is_generic)
10085             {
10086               for (g = overridden_tbp->u.generic; g; g = g->next)
10087                 {
10088                   gcc_assert (g->specific);
10089                   if (check_generic_tbp_ambiguity (target, g,
10090                                                    name, p->where) == FAILURE)
10091                     return FAILURE;
10092                 }
10093             }
10094       }
10095
10096   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10097   if (p->overridden && !p->overridden->is_generic)
10098     {
10099       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10100                  " the same name", name, &p->where);
10101       return FAILURE;
10102     }
10103
10104   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10105      all must have the same attributes here.  */
10106   first_target = p->u.generic->specific->u.specific;
10107   gcc_assert (first_target);
10108   p->subroutine = first_target->n.sym->attr.subroutine;
10109   p->function = first_target->n.sym->attr.function;
10110
10111   return SUCCESS;
10112 }
10113
10114
10115 /* Resolve a GENERIC procedure binding for a derived type.  */
10116
10117 static gfc_try
10118 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10119 {
10120   gfc_symbol* super_type;
10121
10122   /* Find the overridden binding if any.  */
10123   st->n.tb->overridden = NULL;
10124   super_type = gfc_get_derived_super_type (derived);
10125   if (super_type)
10126     {
10127       gfc_symtree* overridden;
10128       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10129                                             true, NULL);
10130
10131       if (overridden && overridden->n.tb)
10132         st->n.tb->overridden = overridden->n.tb;
10133     }
10134
10135   /* Resolve using worker function.  */
10136   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10137 }
10138
10139
10140 /* Retrieve the target-procedure of an operator binding and do some checks in
10141    common for intrinsic and user-defined type-bound operators.  */
10142
10143 static gfc_symbol*
10144 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10145 {
10146   gfc_symbol* target_proc;
10147
10148   gcc_assert (target->specific && !target->specific->is_generic);
10149   target_proc = target->specific->u.specific->n.sym;
10150   gcc_assert (target_proc);
10151
10152   /* All operator bindings must have a passed-object dummy argument.  */
10153   if (target->specific->nopass)
10154     {
10155       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10156       return NULL;
10157     }
10158
10159   return target_proc;
10160 }
10161
10162
10163 /* Resolve a type-bound intrinsic operator.  */
10164
10165 static gfc_try
10166 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10167                                 gfc_typebound_proc* p)
10168 {
10169   gfc_symbol* super_type;
10170   gfc_tbp_generic* target;
10171   
10172   /* If there's already an error here, do nothing (but don't fail again).  */
10173   if (p->error)
10174     return SUCCESS;
10175
10176   /* Operators should always be GENERIC bindings.  */
10177   gcc_assert (p->is_generic);
10178
10179   /* Look for an overridden binding.  */
10180   super_type = gfc_get_derived_super_type (derived);
10181   if (super_type && super_type->f2k_derived)
10182     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10183                                                      op, true, NULL);
10184   else
10185     p->overridden = NULL;
10186
10187   /* Resolve general GENERIC properties using worker function.  */
10188   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10189     goto error;
10190
10191   /* Check the targets to be procedures of correct interface.  */
10192   for (target = p->u.generic; target; target = target->next)
10193     {
10194       gfc_symbol* target_proc;
10195
10196       target_proc = get_checked_tb_operator_target (target, p->where);
10197       if (!target_proc)
10198         goto error;
10199
10200       if (!gfc_check_operator_interface (target_proc, op, p->where))
10201         goto error;
10202     }
10203
10204   return SUCCESS;
10205
10206 error:
10207   p->error = 1;
10208   return FAILURE;
10209 }
10210
10211
10212 /* Resolve a type-bound user operator (tree-walker callback).  */
10213
10214 static gfc_symbol* resolve_bindings_derived;
10215 static gfc_try resolve_bindings_result;
10216
10217 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10218
10219 static void
10220 resolve_typebound_user_op (gfc_symtree* stree)
10221 {
10222   gfc_symbol* super_type;
10223   gfc_tbp_generic* target;
10224
10225   gcc_assert (stree && stree->n.tb);
10226
10227   if (stree->n.tb->error)
10228     return;
10229
10230   /* Operators should always be GENERIC bindings.  */
10231   gcc_assert (stree->n.tb->is_generic);
10232
10233   /* Find overridden procedure, if any.  */
10234   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10235   if (super_type && super_type->f2k_derived)
10236     {
10237       gfc_symtree* overridden;
10238       overridden = gfc_find_typebound_user_op (super_type, NULL,
10239                                                stree->name, true, NULL);
10240
10241       if (overridden && overridden->n.tb)
10242         stree->n.tb->overridden = overridden->n.tb;
10243     }
10244   else
10245     stree->n.tb->overridden = NULL;
10246
10247   /* Resolve basically using worker function.  */
10248   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10249         == FAILURE)
10250     goto error;
10251
10252   /* Check the targets to be functions of correct interface.  */
10253   for (target = stree->n.tb->u.generic; target; target = target->next)
10254     {
10255       gfc_symbol* target_proc;
10256
10257       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10258       if (!target_proc)
10259         goto error;
10260
10261       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10262         goto error;
10263     }
10264
10265   return;
10266
10267 error:
10268   resolve_bindings_result = FAILURE;
10269   stree->n.tb->error = 1;
10270 }
10271
10272
10273 /* Resolve the type-bound procedures for a derived type.  */
10274
10275 static void
10276 resolve_typebound_procedure (gfc_symtree* stree)
10277 {
10278   gfc_symbol* proc;
10279   locus where;
10280   gfc_symbol* me_arg;
10281   gfc_symbol* super_type;
10282   gfc_component* comp;
10283
10284   gcc_assert (stree);
10285
10286   /* Undefined specific symbol from GENERIC target definition.  */
10287   if (!stree->n.tb)
10288     return;
10289
10290   if (stree->n.tb->error)
10291     return;
10292
10293   /* If this is a GENERIC binding, use that routine.  */
10294   if (stree->n.tb->is_generic)
10295     {
10296       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10297             == FAILURE)
10298         goto error;
10299       return;
10300     }
10301
10302   /* Get the target-procedure to check it.  */
10303   gcc_assert (!stree->n.tb->is_generic);
10304   gcc_assert (stree->n.tb->u.specific);
10305   proc = stree->n.tb->u.specific->n.sym;
10306   where = stree->n.tb->where;
10307
10308   /* Default access should already be resolved from the parser.  */
10309   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10310
10311   /* It should be a module procedure or an external procedure with explicit
10312      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10313   if ((!proc->attr.subroutine && !proc->attr.function)
10314       || (proc->attr.proc != PROC_MODULE
10315           && proc->attr.if_source != IFSRC_IFBODY)
10316       || (proc->attr.abstract && !stree->n.tb->deferred))
10317     {
10318       gfc_error ("'%s' must be a module procedure or an external procedure with"
10319                  " an explicit interface at %L", proc->name, &where);
10320       goto error;
10321     }
10322   stree->n.tb->subroutine = proc->attr.subroutine;
10323   stree->n.tb->function = proc->attr.function;
10324
10325   /* Find the super-type of the current derived type.  We could do this once and
10326      store in a global if speed is needed, but as long as not I believe this is
10327      more readable and clearer.  */
10328   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10329
10330   /* If PASS, resolve and check arguments if not already resolved / loaded
10331      from a .mod file.  */
10332   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10333     {
10334       if (stree->n.tb->pass_arg)
10335         {
10336           gfc_formal_arglist* i;
10337
10338           /* If an explicit passing argument name is given, walk the arg-list
10339              and look for it.  */
10340
10341           me_arg = NULL;
10342           stree->n.tb->pass_arg_num = 1;
10343           for (i = proc->formal; i; i = i->next)
10344             {
10345               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10346                 {
10347                   me_arg = i->sym;
10348                   break;
10349                 }
10350               ++stree->n.tb->pass_arg_num;
10351             }
10352
10353           if (!me_arg)
10354             {
10355               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10356                          " argument '%s'",
10357                          proc->name, stree->n.tb->pass_arg, &where,
10358                          stree->n.tb->pass_arg);
10359               goto error;
10360             }
10361         }
10362       else
10363         {
10364           /* Otherwise, take the first one; there should in fact be at least
10365              one.  */
10366           stree->n.tb->pass_arg_num = 1;
10367           if (!proc->formal)
10368             {
10369               gfc_error ("Procedure '%s' with PASS at %L must have at"
10370                          " least one argument", proc->name, &where);
10371               goto error;
10372             }
10373           me_arg = proc->formal->sym;
10374         }
10375
10376       /* Now check that the argument-type matches and the passed-object
10377          dummy argument is generally fine.  */
10378
10379       gcc_assert (me_arg);
10380
10381       if (me_arg->ts.type != BT_CLASS)
10382         {
10383           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10384                      " at %L", proc->name, &where);
10385           goto error;
10386         }
10387
10388       if (me_arg->ts.u.derived->components->ts.u.derived
10389           != resolve_bindings_derived)
10390         {
10391           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10392                      " the derived-type '%s'", me_arg->name, proc->name,
10393                      me_arg->name, &where, resolve_bindings_derived->name);
10394           goto error;
10395         }
10396   
10397       gcc_assert (me_arg->ts.type == BT_CLASS);
10398       if (me_arg->ts.u.derived->components->as
10399           && me_arg->ts.u.derived->components->as->rank > 0)
10400         {
10401           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10402                      " scalar", proc->name, &where);
10403           goto error;
10404         }
10405       if (me_arg->ts.u.derived->components->attr.allocatable)
10406         {
10407           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10408                      " be ALLOCATABLE", proc->name, &where);
10409           goto error;
10410         }
10411       if (me_arg->ts.u.derived->components->attr.class_pointer)
10412         {
10413           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10414                      " be POINTER", proc->name, &where);
10415           goto error;
10416         }
10417     }
10418
10419   /* If we are extending some type, check that we don't override a procedure
10420      flagged NON_OVERRIDABLE.  */
10421   stree->n.tb->overridden = NULL;
10422   if (super_type)
10423     {
10424       gfc_symtree* overridden;
10425       overridden = gfc_find_typebound_proc (super_type, NULL,
10426                                             stree->name, true, NULL);
10427
10428       if (overridden && overridden->n.tb)
10429         stree->n.tb->overridden = overridden->n.tb;
10430
10431       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10432         goto error;
10433     }
10434
10435   /* See if there's a name collision with a component directly in this type.  */
10436   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10437     if (!strcmp (comp->name, stree->name))
10438       {
10439         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10440                    " '%s'",
10441                    stree->name, &where, resolve_bindings_derived->name);
10442         goto error;
10443       }
10444
10445   /* Try to find a name collision with an inherited component.  */
10446   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10447     {
10448       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10449                  " component of '%s'",
10450                  stree->name, &where, resolve_bindings_derived->name);
10451       goto error;
10452     }
10453
10454   stree->n.tb->error = 0;
10455   return;
10456
10457 error:
10458   resolve_bindings_result = FAILURE;
10459   stree->n.tb->error = 1;
10460 }
10461
10462 static gfc_try
10463 resolve_typebound_procedures (gfc_symbol* derived)
10464 {
10465   int op;
10466
10467   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10468     return SUCCESS;
10469
10470   resolve_bindings_derived = derived;
10471   resolve_bindings_result = SUCCESS;
10472
10473   if (derived->f2k_derived->tb_sym_root)
10474     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10475                           &resolve_typebound_procedure);
10476
10477   if (derived->f2k_derived->tb_uop_root)
10478     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10479                           &resolve_typebound_user_op);
10480
10481   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10482     {
10483       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10484       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10485                                                p) == FAILURE)
10486         resolve_bindings_result = FAILURE;
10487     }
10488
10489   return resolve_bindings_result;
10490 }
10491
10492
10493 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10494    to give all identical derived types the same backend_decl.  */
10495 static void
10496 add_dt_to_dt_list (gfc_symbol *derived)
10497 {
10498   gfc_dt_list *dt_list;
10499
10500   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10501     if (derived == dt_list->derived)
10502       break;
10503
10504   if (dt_list == NULL)
10505     {
10506       dt_list = gfc_get_dt_list ();
10507       dt_list->next = gfc_derived_types;
10508       dt_list->derived = derived;
10509       gfc_derived_types = dt_list;
10510     }
10511 }
10512
10513
10514 /* Ensure that a derived-type is really not abstract, meaning that every
10515    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10516
10517 static gfc_try
10518 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10519 {
10520   if (!st)
10521     return SUCCESS;
10522
10523   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10524     return FAILURE;
10525   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10526     return FAILURE;
10527
10528   if (st->n.tb && st->n.tb->deferred)
10529     {
10530       gfc_symtree* overriding;
10531       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10532       if (!overriding)
10533         return FAILURE;
10534       gcc_assert (overriding->n.tb);
10535       if (overriding->n.tb->deferred)
10536         {
10537           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10538                      " '%s' is DEFERRED and not overridden",
10539                      sub->name, &sub->declared_at, st->name);
10540           return FAILURE;
10541         }
10542     }
10543
10544   return SUCCESS;
10545 }
10546
10547 static gfc_try
10548 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10549 {
10550   /* The algorithm used here is to recursively travel up the ancestry of sub
10551      and for each ancestor-type, check all bindings.  If any of them is
10552      DEFERRED, look it up starting from sub and see if the found (overriding)
10553      binding is not DEFERRED.
10554      This is not the most efficient way to do this, but it should be ok and is
10555      clearer than something sophisticated.  */
10556
10557   gcc_assert (ancestor && ancestor->attr.abstract && !sub->attr.abstract);
10558
10559   /* Walk bindings of this ancestor.  */
10560   if (ancestor->f2k_derived)
10561     {
10562       gfc_try t;
10563       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10564       if (t == FAILURE)
10565         return FAILURE;
10566     }
10567
10568   /* Find next ancestor type and recurse on it.  */
10569   ancestor = gfc_get_derived_super_type (ancestor);
10570   if (ancestor)
10571     return ensure_not_abstract (sub, ancestor);
10572
10573   return SUCCESS;
10574 }
10575
10576
10577 static void resolve_symbol (gfc_symbol *sym);
10578
10579
10580 /* Resolve the components of a derived type.  */
10581
10582 static gfc_try
10583 resolve_fl_derived (gfc_symbol *sym)
10584 {
10585   gfc_symbol* super_type;
10586   gfc_component *c;
10587   int i;
10588
10589   super_type = gfc_get_derived_super_type (sym);
10590
10591   /* F2008, C432. */
10592   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
10593     {
10594       gfc_error ("As extending type '%s' at %L has a coarray component, "
10595                  "parent type '%s' shall also have one", sym->name,
10596                  &sym->declared_at, super_type->name);
10597       return FAILURE;
10598     }
10599
10600   /* Ensure the extended type gets resolved before we do.  */
10601   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10602     return FAILURE;
10603
10604   /* An ABSTRACT type must be extensible.  */
10605   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10606     {
10607       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10608                  sym->name, &sym->declared_at);
10609       return FAILURE;
10610     }
10611
10612   for (c = sym->components; c != NULL; c = c->next)
10613     {
10614       /* F2008, C442.  */
10615       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
10616           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
10617         {
10618           gfc_error ("Coarray component '%s' at %L must be allocatable with "
10619                      "deferred shape", c->name, &c->loc);
10620           return FAILURE;
10621         }
10622
10623       /* F2008, C443.  */
10624       if (c->attr.codimension && c->ts.type == BT_DERIVED
10625           && c->ts.u.derived->ts.is_iso_c)
10626         {
10627           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
10628                      "shall not be a coarray", c->name, &c->loc);
10629           return FAILURE;
10630         }
10631
10632       /* F2008, C444.  */
10633       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
10634           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
10635               || c->attr.allocatable))
10636         {
10637           gfc_error ("Component '%s' at %L with coarray component "
10638                      "shall be a nonpointer, nonallocatable scalar",
10639                      c->name, &c->loc);
10640           return FAILURE;
10641         }
10642
10643       if (c->attr.proc_pointer && c->ts.interface)
10644         {
10645           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
10646             gfc_error ("Interface '%s', used by procedure pointer component "
10647                        "'%s' at %L, is declared in a later PROCEDURE statement",
10648                        c->ts.interface->name, c->name, &c->loc);
10649
10650           /* Get the attributes from the interface (now resolved).  */
10651           if (c->ts.interface->attr.if_source
10652               || c->ts.interface->attr.intrinsic)
10653             {
10654               gfc_symbol *ifc = c->ts.interface;
10655
10656               if (ifc->formal && !ifc->formal_ns)
10657                 resolve_symbol (ifc);
10658
10659               if (ifc->attr.intrinsic)
10660                 resolve_intrinsic (ifc, &ifc->declared_at);
10661
10662               if (ifc->result)
10663                 {
10664                   c->ts = ifc->result->ts;
10665                   c->attr.allocatable = ifc->result->attr.allocatable;
10666                   c->attr.pointer = ifc->result->attr.pointer;
10667                   c->attr.dimension = ifc->result->attr.dimension;
10668                   c->as = gfc_copy_array_spec (ifc->result->as);
10669                 }
10670               else
10671                 {   
10672                   c->ts = ifc->ts;
10673                   c->attr.allocatable = ifc->attr.allocatable;
10674                   c->attr.pointer = ifc->attr.pointer;
10675                   c->attr.dimension = ifc->attr.dimension;
10676                   c->as = gfc_copy_array_spec (ifc->as);
10677                 }
10678               c->ts.interface = ifc;
10679               c->attr.function = ifc->attr.function;
10680               c->attr.subroutine = ifc->attr.subroutine;
10681               gfc_copy_formal_args_ppc (c, ifc);
10682
10683               c->attr.pure = ifc->attr.pure;
10684               c->attr.elemental = ifc->attr.elemental;
10685               c->attr.recursive = ifc->attr.recursive;
10686               c->attr.always_explicit = ifc->attr.always_explicit;
10687               c->attr.ext_attr |= ifc->attr.ext_attr;
10688               /* Replace symbols in array spec.  */
10689               if (c->as)
10690                 {
10691                   int i;
10692                   for (i = 0; i < c->as->rank; i++)
10693                     {
10694                       gfc_expr_replace_comp (c->as->lower[i], c);
10695                       gfc_expr_replace_comp (c->as->upper[i], c);
10696                     }
10697                 }
10698               /* Copy char length.  */
10699               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10700                 {
10701                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10702                   gfc_expr_replace_comp (cl->length, c);
10703                   if (cl->length && !cl->resolved
10704                         && gfc_resolve_expr (cl->length) == FAILURE)
10705                     return FAILURE;
10706                   c->ts.u.cl = cl;
10707                 }
10708             }
10709           else if (c->ts.interface->name[0] != '\0' && !sym->attr.vtype)
10710             {
10711               gfc_error ("Interface '%s' of procedure pointer component "
10712                          "'%s' at %L must be explicit", c->ts.interface->name,
10713                          c->name, &c->loc);
10714               return FAILURE;
10715             }
10716         }
10717       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10718         {
10719           /* Since PPCs are not implicitly typed, a PPC without an explicit
10720              interface must be a subroutine.  */
10721           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10722         }
10723
10724       /* Procedure pointer components: Check PASS arg.  */
10725       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
10726           && !sym->attr.vtype)
10727         {
10728           gfc_symbol* me_arg;
10729
10730           if (c->tb->pass_arg)
10731             {
10732               gfc_formal_arglist* i;
10733
10734               /* If an explicit passing argument name is given, walk the arg-list
10735                 and look for it.  */
10736
10737               me_arg = NULL;
10738               c->tb->pass_arg_num = 1;
10739               for (i = c->formal; i; i = i->next)
10740                 {
10741                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10742                     {
10743                       me_arg = i->sym;
10744                       break;
10745                     }
10746                   c->tb->pass_arg_num++;
10747                 }
10748
10749               if (!me_arg)
10750                 {
10751                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10752                              "at %L has no argument '%s'", c->name,
10753                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10754                   c->tb->error = 1;
10755                   return FAILURE;
10756                 }
10757             }
10758           else
10759             {
10760               /* Otherwise, take the first one; there should in fact be at least
10761                 one.  */
10762               c->tb->pass_arg_num = 1;
10763               if (!c->formal)
10764                 {
10765                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10766                              "must have at least one argument",
10767                              c->name, &c->loc);
10768                   c->tb->error = 1;
10769                   return FAILURE;
10770                 }
10771               me_arg = c->formal->sym;
10772             }
10773
10774           /* Now check that the argument-type matches.  */
10775           gcc_assert (me_arg);
10776           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10777               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10778               || (me_arg->ts.type == BT_CLASS
10779                   && me_arg->ts.u.derived->components->ts.u.derived != sym))
10780             {
10781               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10782                          " the derived type '%s'", me_arg->name, c->name,
10783                          me_arg->name, &c->loc, sym->name);
10784               c->tb->error = 1;
10785               return FAILURE;
10786             }
10787
10788           /* Check for C453.  */
10789           if (me_arg->attr.dimension)
10790             {
10791               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10792                          "must be scalar", me_arg->name, c->name, me_arg->name,
10793                          &c->loc);
10794               c->tb->error = 1;
10795               return FAILURE;
10796             }
10797
10798           if (me_arg->attr.pointer)
10799             {
10800               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10801                          "may not have the POINTER attribute", me_arg->name,
10802                          c->name, me_arg->name, &c->loc);
10803               c->tb->error = 1;
10804               return FAILURE;
10805             }
10806
10807           if (me_arg->attr.allocatable)
10808             {
10809               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10810                          "may not be ALLOCATABLE", me_arg->name, c->name,
10811                          me_arg->name, &c->loc);
10812               c->tb->error = 1;
10813               return FAILURE;
10814             }
10815
10816           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10817             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10818                        " at %L", c->name, &c->loc);
10819
10820         }
10821
10822       /* Check type-spec if this is not the parent-type component.  */
10823       if ((!sym->attr.extension || c != sym->components)
10824           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10825         return FAILURE;
10826
10827       /* If this type is an extension, set the accessibility of the parent
10828          component.  */
10829       if (super_type && c == sym->components
10830           && strcmp (super_type->name, c->name) == 0)
10831         c->attr.access = super_type->attr.access;
10832       
10833       /* If this type is an extension, see if this component has the same name
10834          as an inherited type-bound procedure.  */
10835       if (super_type && !sym->attr.is_class
10836           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10837         {
10838           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10839                      " inherited type-bound procedure",
10840                      c->name, sym->name, &c->loc);
10841           return FAILURE;
10842         }
10843
10844       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10845         {
10846          if (c->ts.u.cl->length == NULL
10847              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10848              || !gfc_is_constant_expr (c->ts.u.cl->length))
10849            {
10850              gfc_error ("Character length of component '%s' needs to "
10851                         "be a constant specification expression at %L",
10852                         c->name,
10853                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10854              return FAILURE;
10855            }
10856         }
10857
10858       if (c->ts.type == BT_DERIVED
10859           && sym->component_access != ACCESS_PRIVATE
10860           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10861           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10862           && !c->ts.u.derived->attr.use_assoc
10863           && !gfc_check_access (c->ts.u.derived->attr.access,
10864                                 c->ts.u.derived->ns->default_access)
10865           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10866                              "is a PRIVATE type and cannot be a component of "
10867                              "'%s', which is PUBLIC at %L", c->name,
10868                              sym->name, &sym->declared_at) == FAILURE)
10869         return FAILURE;
10870
10871       if (sym->attr.sequence)
10872         {
10873           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10874             {
10875               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10876                          "not have the SEQUENCE attribute",
10877                          c->ts.u.derived->name, &sym->declared_at);
10878               return FAILURE;
10879             }
10880         }
10881
10882       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && c->attr.pointer
10883           && c->ts.u.derived->components == NULL
10884           && !c->ts.u.derived->attr.zero_comp)
10885         {
10886           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10887                      "that has not been declared", c->name, sym->name,
10888                      &c->loc);
10889           return FAILURE;
10890         }
10891
10892       if (c->ts.type == BT_CLASS && c->ts.u.derived->components->attr.pointer
10893           && c->ts.u.derived->components->ts.u.derived->components == NULL
10894           && !c->ts.u.derived->components->ts.u.derived->attr.zero_comp)
10895         {
10896           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10897                      "that has not been declared", c->name, sym->name,
10898                      &c->loc);
10899           return FAILURE;
10900         }
10901
10902       /* C437.  */
10903       if (c->ts.type == BT_CLASS
10904           && !(c->ts.u.derived->components->attr.pointer
10905                || c->ts.u.derived->components->attr.allocatable))
10906         {
10907           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10908                      "or pointer", c->name, &c->loc);
10909           return FAILURE;
10910         }
10911
10912       /* Ensure that all the derived type components are put on the
10913          derived type list; even in formal namespaces, where derived type
10914          pointer components might not have been declared.  */
10915       if (c->ts.type == BT_DERIVED
10916             && c->ts.u.derived
10917             && c->ts.u.derived->components
10918             && c->attr.pointer
10919             && sym != c->ts.u.derived)
10920         add_dt_to_dt_list (c->ts.u.derived);
10921
10922       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10923           || c->as == NULL)
10924         continue;
10925
10926       for (i = 0; i < c->as->rank; i++)
10927         {
10928           if (c->as->lower[i] == NULL
10929               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
10930               || !gfc_is_constant_expr (c->as->lower[i])
10931               || c->as->upper[i] == NULL
10932               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
10933               || !gfc_is_constant_expr (c->as->upper[i]))
10934             {
10935               gfc_error ("Component '%s' of '%s' at %L must have "
10936                          "constant array bounds",
10937                          c->name, sym->name, &c->loc);
10938               return FAILURE;
10939             }
10940         }
10941     }
10942
10943   /* Resolve the type-bound procedures.  */
10944   if (resolve_typebound_procedures (sym) == FAILURE)
10945     return FAILURE;
10946
10947   /* Resolve the finalizer procedures.  */
10948   if (gfc_resolve_finalizers (sym) == FAILURE)
10949     return FAILURE;
10950
10951   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
10952      all DEFERRED bindings are overridden.  */
10953   if (super_type && super_type->attr.abstract && !sym->attr.abstract
10954       && ensure_not_abstract (sym, super_type) == FAILURE)
10955     return FAILURE;
10956
10957   /* Add derived type to the derived type list.  */
10958   add_dt_to_dt_list (sym);
10959
10960   return SUCCESS;
10961 }
10962
10963
10964 static gfc_try
10965 resolve_fl_namelist (gfc_symbol *sym)
10966 {
10967   gfc_namelist *nl;
10968   gfc_symbol *nlsym;
10969
10970   /* Reject PRIVATE objects in a PUBLIC namelist.  */
10971   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
10972     {
10973       for (nl = sym->namelist; nl; nl = nl->next)
10974         {
10975           if (!nl->sym->attr.use_assoc
10976               && !is_sym_host_assoc (nl->sym, sym->ns)
10977               && !gfc_check_access(nl->sym->attr.access,
10978                                 nl->sym->ns->default_access))
10979             {
10980               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
10981                          "cannot be member of PUBLIC namelist '%s' at %L",
10982                          nl->sym->name, sym->name, &sym->declared_at);
10983               return FAILURE;
10984             }
10985
10986           /* Types with private components that came here by USE-association.  */
10987           if (nl->sym->ts.type == BT_DERIVED
10988               && derived_inaccessible (nl->sym->ts.u.derived))
10989             {
10990               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
10991                          "components and cannot be member of namelist '%s' at %L",
10992                          nl->sym->name, sym->name, &sym->declared_at);
10993               return FAILURE;
10994             }
10995
10996           /* Types with private components that are defined in the same module.  */
10997           if (nl->sym->ts.type == BT_DERIVED
10998               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
10999               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11000                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11001                                         nl->sym->ns->default_access))
11002             {
11003               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11004                          "cannot be a member of PUBLIC namelist '%s' at %L",
11005                          nl->sym->name, sym->name, &sym->declared_at);
11006               return FAILURE;
11007             }
11008         }
11009     }
11010
11011   for (nl = sym->namelist; nl; nl = nl->next)
11012     {
11013       /* Reject namelist arrays of assumed shape.  */
11014       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11015           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11016                              "must not have assumed shape in namelist "
11017                              "'%s' at %L", nl->sym->name, sym->name,
11018                              &sym->declared_at) == FAILURE)
11019             return FAILURE;
11020
11021       /* Reject namelist arrays that are not constant shape.  */
11022       if (is_non_constant_shape_array (nl->sym))
11023         {
11024           gfc_error ("NAMELIST array object '%s' must have constant "
11025                      "shape in namelist '%s' at %L", nl->sym->name,
11026                      sym->name, &sym->declared_at);
11027           return FAILURE;
11028         }
11029
11030       /* Namelist objects cannot have allocatable or pointer components.  */
11031       if (nl->sym->ts.type != BT_DERIVED)
11032         continue;
11033
11034       if (nl->sym->ts.u.derived->attr.alloc_comp)
11035         {
11036           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11037                      "have ALLOCATABLE components",
11038                      nl->sym->name, sym->name, &sym->declared_at);
11039           return FAILURE;
11040         }
11041
11042       if (nl->sym->ts.u.derived->attr.pointer_comp)
11043         {
11044           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11045                      "have POINTER components", 
11046                      nl->sym->name, sym->name, &sym->declared_at);
11047           return FAILURE;
11048         }
11049     }
11050
11051
11052   /* 14.1.2 A module or internal procedure represent local entities
11053      of the same type as a namelist member and so are not allowed.  */
11054   for (nl = sym->namelist; nl; nl = nl->next)
11055     {
11056       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11057         continue;
11058
11059       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11060         if ((nl->sym == sym->ns->proc_name)
11061                ||
11062             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11063           continue;
11064
11065       nlsym = NULL;
11066       if (nl->sym && nl->sym->name)
11067         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11068       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11069         {
11070           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11071                      "attribute in '%s' at %L", nlsym->name,
11072                      &sym->declared_at);
11073           return FAILURE;
11074         }
11075     }
11076
11077   return SUCCESS;
11078 }
11079
11080
11081 static gfc_try
11082 resolve_fl_parameter (gfc_symbol *sym)
11083 {
11084   /* A parameter array's shape needs to be constant.  */
11085   if (sym->as != NULL 
11086       && (sym->as->type == AS_DEFERRED
11087           || is_non_constant_shape_array (sym)))
11088     {
11089       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11090                  "or of deferred shape", sym->name, &sym->declared_at);
11091       return FAILURE;
11092     }
11093
11094   /* Make sure a parameter that has been implicitly typed still
11095      matches the implicit type, since PARAMETER statements can precede
11096      IMPLICIT statements.  */
11097   if (sym->attr.implicit_type
11098       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11099                                                              sym->ns)))
11100     {
11101       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11102                  "later IMPLICIT type", sym->name, &sym->declared_at);
11103       return FAILURE;
11104     }
11105
11106   /* Make sure the types of derived parameters are consistent.  This
11107      type checking is deferred until resolution because the type may
11108      refer to a derived type from the host.  */
11109   if (sym->ts.type == BT_DERIVED
11110       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11111     {
11112       gfc_error ("Incompatible derived type in PARAMETER at %L",
11113                  &sym->value->where);
11114       return FAILURE;
11115     }
11116   return SUCCESS;
11117 }
11118
11119
11120 /* Do anything necessary to resolve a symbol.  Right now, we just
11121    assume that an otherwise unknown symbol is a variable.  This sort
11122    of thing commonly happens for symbols in module.  */
11123
11124 static void
11125 resolve_symbol (gfc_symbol *sym)
11126 {
11127   int check_constant, mp_flag;
11128   gfc_symtree *symtree;
11129   gfc_symtree *this_symtree;
11130   gfc_namespace *ns;
11131   gfc_component *c;
11132
11133   if (sym->attr.flavor == FL_UNKNOWN)
11134     {
11135
11136     /* If we find that a flavorless symbol is an interface in one of the
11137        parent namespaces, find its symtree in this namespace, free the
11138        symbol and set the symtree to point to the interface symbol.  */
11139       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11140         {
11141           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11142           if (symtree && symtree->n.sym->generic)
11143             {
11144               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11145                                                sym->name);
11146               sym->refs--;
11147               if (!sym->refs)
11148                 gfc_free_symbol (sym);
11149               symtree->n.sym->refs++;
11150               this_symtree->n.sym = symtree->n.sym;
11151               return;
11152             }
11153         }
11154
11155       /* Otherwise give it a flavor according to such attributes as
11156          it has.  */
11157       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11158         sym->attr.flavor = FL_VARIABLE;
11159       else
11160         {
11161           sym->attr.flavor = FL_PROCEDURE;
11162           if (sym->attr.dimension)
11163             sym->attr.function = 1;
11164         }
11165     }
11166
11167   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11168     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11169
11170   if (sym->attr.procedure && sym->ts.interface
11171       && sym->attr.if_source != IFSRC_DECL)
11172     {
11173       if (sym->ts.interface == sym)
11174         {
11175           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
11176                      "interface", sym->name, &sym->declared_at);
11177           return;
11178         }
11179       if (sym->ts.interface->attr.procedure)
11180         {
11181           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
11182                      " in a later PROCEDURE statement", sym->ts.interface->name,
11183                      sym->name,&sym->declared_at);
11184           return;
11185         }
11186
11187       /* Get the attributes from the interface (now resolved).  */
11188       if (sym->ts.interface->attr.if_source
11189           || sym->ts.interface->attr.intrinsic)
11190         {
11191           gfc_symbol *ifc = sym->ts.interface;
11192           resolve_symbol (ifc);
11193
11194           if (ifc->attr.intrinsic)
11195             resolve_intrinsic (ifc, &ifc->declared_at);
11196
11197           if (ifc->result)
11198             sym->ts = ifc->result->ts;
11199           else   
11200             sym->ts = ifc->ts;
11201           sym->ts.interface = ifc;
11202           sym->attr.function = ifc->attr.function;
11203           sym->attr.subroutine = ifc->attr.subroutine;
11204           gfc_copy_formal_args (sym, ifc);
11205
11206           sym->attr.allocatable = ifc->attr.allocatable;
11207           sym->attr.pointer = ifc->attr.pointer;
11208           sym->attr.pure = ifc->attr.pure;
11209           sym->attr.elemental = ifc->attr.elemental;
11210           sym->attr.dimension = ifc->attr.dimension;
11211           sym->attr.recursive = ifc->attr.recursive;
11212           sym->attr.always_explicit = ifc->attr.always_explicit;
11213           sym->attr.ext_attr |= ifc->attr.ext_attr;
11214           /* Copy array spec.  */
11215           sym->as = gfc_copy_array_spec (ifc->as);
11216           if (sym->as)
11217             {
11218               int i;
11219               for (i = 0; i < sym->as->rank; i++)
11220                 {
11221                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
11222                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
11223                 }
11224             }
11225           /* Copy char length.  */
11226           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11227             {
11228               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11229               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
11230               if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
11231                     && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
11232                 return;
11233             }
11234         }
11235       else if (sym->ts.interface->name[0] != '\0')
11236         {
11237           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
11238                     sym->ts.interface->name, sym->name, &sym->declared_at);
11239           return;
11240         }
11241     }
11242
11243   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11244     return;
11245
11246   /* Symbols that are module procedures with results (functions) have
11247      the types and array specification copied for type checking in
11248      procedures that call them, as well as for saving to a module
11249      file.  These symbols can't stand the scrutiny that their results
11250      can.  */
11251   mp_flag = (sym->result != NULL && sym->result != sym);
11252
11253
11254   /* Make sure that the intrinsic is consistent with its internal 
11255      representation. This needs to be done before assigning a default 
11256      type to avoid spurious warnings.  */
11257   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11258       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11259     return;
11260
11261   /* Assign default type to symbols that need one and don't have one.  */
11262   if (sym->ts.type == BT_UNKNOWN)
11263     {
11264       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11265         gfc_set_default_type (sym, 1, NULL);
11266
11267       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11268           && !sym->attr.function && !sym->attr.subroutine
11269           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11270         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11271
11272       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11273         {
11274           /* The specific case of an external procedure should emit an error
11275              in the case that there is no implicit type.  */
11276           if (!mp_flag)
11277             gfc_set_default_type (sym, sym->attr.external, NULL);
11278           else
11279             {
11280               /* Result may be in another namespace.  */
11281               resolve_symbol (sym->result);
11282
11283               if (!sym->result->attr.proc_pointer)
11284                 {
11285                   sym->ts = sym->result->ts;
11286                   sym->as = gfc_copy_array_spec (sym->result->as);
11287                   sym->attr.dimension = sym->result->attr.dimension;
11288                   sym->attr.pointer = sym->result->attr.pointer;
11289                   sym->attr.allocatable = sym->result->attr.allocatable;
11290                 }
11291             }
11292         }
11293     }
11294
11295   /* Assumed size arrays and assumed shape arrays must be dummy
11296      arguments.  */
11297
11298   if (sym->as != NULL
11299       && ((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11300           || sym->as->type == AS_ASSUMED_SHAPE)
11301       && sym->attr.dummy == 0)
11302     {
11303       if (sym->as->type == AS_ASSUMED_SIZE)
11304         gfc_error ("Assumed size array at %L must be a dummy argument",
11305                    &sym->declared_at);
11306       else
11307         gfc_error ("Assumed shape array at %L must be a dummy argument",
11308                    &sym->declared_at);
11309       return;
11310     }
11311
11312   /* Make sure symbols with known intent or optional are really dummy
11313      variable.  Because of ENTRY statement, this has to be deferred
11314      until resolution time.  */
11315
11316   if (!sym->attr.dummy
11317       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11318     {
11319       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11320       return;
11321     }
11322
11323   if (sym->attr.value && !sym->attr.dummy)
11324     {
11325       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11326                  "it is not a dummy argument", sym->name, &sym->declared_at);
11327       return;
11328     }
11329
11330   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11331     {
11332       gfc_charlen *cl = sym->ts.u.cl;
11333       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11334         {
11335           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11336                      "attribute must have constant length",
11337                      sym->name, &sym->declared_at);
11338           return;
11339         }
11340
11341       if (sym->ts.is_c_interop
11342           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11343         {
11344           gfc_error ("C interoperable character dummy variable '%s' at %L "
11345                      "with VALUE attribute must have length one",
11346                      sym->name, &sym->declared_at);
11347           return;
11348         }
11349     }
11350
11351   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11352      do this for something that was implicitly typed because that is handled
11353      in gfc_set_default_type.  Handle dummy arguments and procedure
11354      definitions separately.  Also, anything that is use associated is not
11355      handled here but instead is handled in the module it is declared in.
11356      Finally, derived type definitions are allowed to be BIND(C) since that
11357      only implies that they're interoperable, and they are checked fully for
11358      interoperability when a variable is declared of that type.  */
11359   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11360       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11361       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11362     {
11363       gfc_try t = SUCCESS;
11364       
11365       /* First, make sure the variable is declared at the
11366          module-level scope (J3/04-007, Section 15.3).  */
11367       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11368           sym->attr.in_common == 0)
11369         {
11370           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11371                      "is neither a COMMON block nor declared at the "
11372                      "module level scope", sym->name, &(sym->declared_at));
11373           t = FAILURE;
11374         }
11375       else if (sym->common_head != NULL)
11376         {
11377           t = verify_com_block_vars_c_interop (sym->common_head);
11378         }
11379       else
11380         {
11381           /* If type() declaration, we need to verify that the components
11382              of the given type are all C interoperable, etc.  */
11383           if (sym->ts.type == BT_DERIVED &&
11384               sym->ts.u.derived->attr.is_c_interop != 1)
11385             {
11386               /* Make sure the user marked the derived type as BIND(C).  If
11387                  not, call the verify routine.  This could print an error
11388                  for the derived type more than once if multiple variables
11389                  of that type are declared.  */
11390               if (sym->ts.u.derived->attr.is_bind_c != 1)
11391                 verify_bind_c_derived_type (sym->ts.u.derived);
11392               t = FAILURE;
11393             }
11394           
11395           /* Verify the variable itself as C interoperable if it
11396              is BIND(C).  It is not possible for this to succeed if
11397              the verify_bind_c_derived_type failed, so don't have to handle
11398              any error returned by verify_bind_c_derived_type.  */
11399           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11400                                  sym->common_block);
11401         }
11402
11403       if (t == FAILURE)
11404         {
11405           /* clear the is_bind_c flag to prevent reporting errors more than
11406              once if something failed.  */
11407           sym->attr.is_bind_c = 0;
11408           return;
11409         }
11410     }
11411
11412   /* If a derived type symbol has reached this point, without its
11413      type being declared, we have an error.  Notice that most
11414      conditions that produce undefined derived types have already
11415      been dealt with.  However, the likes of:
11416      implicit type(t) (t) ..... call foo (t) will get us here if
11417      the type is not declared in the scope of the implicit
11418      statement. Change the type to BT_UNKNOWN, both because it is so
11419      and to prevent an ICE.  */
11420   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11421       && !sym->ts.u.derived->attr.zero_comp)
11422     {
11423       gfc_error ("The derived type '%s' at %L is of type '%s', "
11424                  "which has not been defined", sym->name,
11425                   &sym->declared_at, sym->ts.u.derived->name);
11426       sym->ts.type = BT_UNKNOWN;
11427       return;
11428     }
11429
11430   /* Make sure that the derived type has been resolved and that the
11431      derived type is visible in the symbol's namespace, if it is a
11432      module function and is not PRIVATE.  */
11433   if (sym->ts.type == BT_DERIVED
11434         && sym->ts.u.derived->attr.use_assoc
11435         && sym->ns->proc_name
11436         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11437     {
11438       gfc_symbol *ds;
11439
11440       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11441         return;
11442
11443       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11444       if (!ds && sym->attr.function
11445             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11446         {
11447           symtree = gfc_new_symtree (&sym->ns->sym_root,
11448                                      sym->ts.u.derived->name);
11449           symtree->n.sym = sym->ts.u.derived;
11450           sym->ts.u.derived->refs++;
11451         }
11452     }
11453
11454   /* Unless the derived-type declaration is use associated, Fortran 95
11455      does not allow public entries of private derived types.
11456      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11457      161 in 95-006r3.  */
11458   if (sym->ts.type == BT_DERIVED
11459       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11460       && !sym->ts.u.derived->attr.use_assoc
11461       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11462       && !gfc_check_access (sym->ts.u.derived->attr.access,
11463                             sym->ts.u.derived->ns->default_access)
11464       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11465                          "of PRIVATE derived type '%s'",
11466                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11467                          : "variable", sym->name, &sym->declared_at,
11468                          sym->ts.u.derived->name) == FAILURE)
11469     return;
11470
11471   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11472      default initialization is defined (5.1.2.4.4).  */
11473   if (sym->ts.type == BT_DERIVED
11474       && sym->attr.dummy
11475       && sym->attr.intent == INTENT_OUT
11476       && sym->as
11477       && sym->as->type == AS_ASSUMED_SIZE)
11478     {
11479       for (c = sym->ts.u.derived->components; c; c = c->next)
11480         {
11481           if (c->initializer)
11482             {
11483               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11484                          "ASSUMED SIZE and so cannot have a default initializer",
11485                          sym->name, &sym->declared_at);
11486               return;
11487             }
11488         }
11489     }
11490
11491   /* F2008, C526.  */
11492   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11493        || sym->attr.codimension)
11494       && sym->attr.result)
11495     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
11496                "a coarray component", sym->name, &sym->declared_at);
11497
11498   /* F2008, C524.  */
11499   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
11500       && sym->ts.u.derived->ts.is_iso_c)
11501     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11502                "shall not be a coarray", sym->name, &sym->declared_at);
11503
11504   /* F2008, C525.  */
11505   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
11506       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
11507           || sym->attr.allocatable))
11508     gfc_error ("Variable '%s' at %L with coarray component "
11509                "shall be a nonpointer, nonallocatable scalar",
11510                sym->name, &sym->declared_at);
11511
11512   /* F2008, C526.  The function-result case was handled above.  */
11513   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11514        || sym->attr.codimension)
11515       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
11516            || sym->ns->proc_name->attr.flavor == FL_MODULE
11517            || sym->ns->proc_name->attr.is_main_program
11518            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
11519     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
11520                "component and is not ALLOCATABLE, SAVE nor a "
11521                "dummy argument", sym->name, &sym->declared_at);
11522   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
11523   else if (sym->attr.codimension && !sym->attr.allocatable
11524       && sym->as && sym->as->cotype == AS_DEFERRED)
11525     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
11526                 "deferred shape", sym->name, &sym->declared_at);
11527   else if (sym->attr.codimension && sym->attr.allocatable
11528       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
11529     gfc_error ("Allocatable coarray variable '%s' at %L must have "
11530                "deferred shape", sym->name, &sym->declared_at);
11531
11532
11533   /* F2008, C541.  */
11534   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11535        || (sym->attr.codimension && sym->attr.allocatable))
11536       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
11537     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
11538                "allocatable coarray or have coarray components",
11539                sym->name, &sym->declared_at);
11540
11541   if (sym->attr.codimension && sym->attr.dummy
11542       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
11543     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
11544                "procedure '%s'", sym->name, &sym->declared_at,
11545                sym->ns->proc_name->name);
11546
11547   switch (sym->attr.flavor)
11548     {
11549     case FL_VARIABLE:
11550       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11551         return;
11552       break;
11553
11554     case FL_PROCEDURE:
11555       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11556         return;
11557       break;
11558
11559     case FL_NAMELIST:
11560       if (resolve_fl_namelist (sym) == FAILURE)
11561         return;
11562       break;
11563
11564     case FL_PARAMETER:
11565       if (resolve_fl_parameter (sym) == FAILURE)
11566         return;
11567       break;
11568
11569     default:
11570       break;
11571     }
11572
11573   /* Resolve array specifier. Check as well some constraints
11574      on COMMON blocks.  */
11575
11576   check_constant = sym->attr.in_common && !sym->attr.pointer;
11577
11578   /* Set the formal_arg_flag so that check_conflict will not throw
11579      an error for host associated variables in the specification
11580      expression for an array_valued function.  */
11581   if (sym->attr.function && sym->as)
11582     formal_arg_flag = 1;
11583
11584   gfc_resolve_array_spec (sym->as, check_constant);
11585
11586   formal_arg_flag = 0;
11587
11588   /* Resolve formal namespaces.  */
11589   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11590       && !sym->attr.contained && !sym->attr.intrinsic)
11591     gfc_resolve (sym->formal_ns);
11592
11593   /* Make sure the formal namespace is present.  */
11594   if (sym->formal && !sym->formal_ns)
11595     {
11596       gfc_formal_arglist *formal = sym->formal;
11597       while (formal && !formal->sym)
11598         formal = formal->next;
11599
11600       if (formal)
11601         {
11602           sym->formal_ns = formal->sym->ns;
11603           sym->formal_ns->refs++;
11604         }
11605     }
11606
11607   /* Check threadprivate restrictions.  */
11608   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11609       && (!sym->attr.in_common
11610           && sym->module == NULL
11611           && (sym->ns->proc_name == NULL
11612               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11613     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11614
11615   /* If we have come this far we can apply default-initializers, as
11616      described in 14.7.5, to those variables that have not already
11617      been assigned one.  */
11618   if (sym->ts.type == BT_DERIVED
11619       && sym->attr.referenced
11620       && sym->ns == gfc_current_ns
11621       && !sym->value
11622       && !sym->attr.allocatable
11623       && !sym->attr.alloc_comp)
11624     {
11625       symbol_attribute *a = &sym->attr;
11626
11627       if ((!a->save && !a->dummy && !a->pointer
11628            && !a->in_common && !a->use_assoc
11629            && !(a->function && sym != sym->result))
11630           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11631         apply_default_init (sym);
11632     }
11633
11634   /* If this symbol has a type-spec, check it.  */
11635   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11636       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11637     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11638           == FAILURE)
11639       return;
11640 }
11641
11642
11643 /************* Resolve DATA statements *************/
11644
11645 static struct
11646 {
11647   gfc_data_value *vnode;
11648   mpz_t left;
11649 }
11650 values;
11651
11652
11653 /* Advance the values structure to point to the next value in the data list.  */
11654
11655 static gfc_try
11656 next_data_value (void)
11657 {
11658   while (mpz_cmp_ui (values.left, 0) == 0)
11659     {
11660
11661       if (values.vnode->next == NULL)
11662         return FAILURE;
11663
11664       values.vnode = values.vnode->next;
11665       mpz_set (values.left, values.vnode->repeat);
11666     }
11667
11668   return SUCCESS;
11669 }
11670
11671
11672 static gfc_try
11673 check_data_variable (gfc_data_variable *var, locus *where)
11674 {
11675   gfc_expr *e;
11676   mpz_t size;
11677   mpz_t offset;
11678   gfc_try t;
11679   ar_type mark = AR_UNKNOWN;
11680   int i;
11681   mpz_t section_index[GFC_MAX_DIMENSIONS];
11682   gfc_ref *ref;
11683   gfc_array_ref *ar;
11684   gfc_symbol *sym;
11685   int has_pointer;
11686
11687   if (gfc_resolve_expr (var->expr) == FAILURE)
11688     return FAILURE;
11689
11690   ar = NULL;
11691   mpz_init_set_si (offset, 0);
11692   e = var->expr;
11693
11694   if (e->expr_type != EXPR_VARIABLE)
11695     gfc_internal_error ("check_data_variable(): Bad expression");
11696
11697   sym = e->symtree->n.sym;
11698
11699   if (sym->ns->is_block_data && !sym->attr.in_common)
11700     {
11701       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11702                  sym->name, &sym->declared_at);
11703     }
11704
11705   if (e->ref == NULL && sym->as)
11706     {
11707       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11708                  " declaration", sym->name, where);
11709       return FAILURE;
11710     }
11711
11712   has_pointer = sym->attr.pointer;
11713
11714   for (ref = e->ref; ref; ref = ref->next)
11715     {
11716       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11717         has_pointer = 1;
11718
11719       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
11720         {
11721           gfc_error ("DATA element '%s' at %L cannot have a coindex",
11722                      sym->name, where);
11723           return FAILURE;
11724         }
11725
11726       if (has_pointer
11727             && ref->type == REF_ARRAY
11728             && ref->u.ar.type != AR_FULL)
11729           {
11730             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11731                         "be a full array", sym->name, where);
11732             return FAILURE;
11733           }
11734     }
11735
11736   if (e->rank == 0 || has_pointer)
11737     {
11738       mpz_init_set_ui (size, 1);
11739       ref = NULL;
11740     }
11741   else
11742     {
11743       ref = e->ref;
11744
11745       /* Find the array section reference.  */
11746       for (ref = e->ref; ref; ref = ref->next)
11747         {
11748           if (ref->type != REF_ARRAY)
11749             continue;
11750           if (ref->u.ar.type == AR_ELEMENT)
11751             continue;
11752           break;
11753         }
11754       gcc_assert (ref);
11755
11756       /* Set marks according to the reference pattern.  */
11757       switch (ref->u.ar.type)
11758         {
11759         case AR_FULL:
11760           mark = AR_FULL;
11761           break;
11762
11763         case AR_SECTION:
11764           ar = &ref->u.ar;
11765           /* Get the start position of array section.  */
11766           gfc_get_section_index (ar, section_index, &offset);
11767           mark = AR_SECTION;
11768           break;
11769
11770         default:
11771           gcc_unreachable ();
11772         }
11773
11774       if (gfc_array_size (e, &size) == FAILURE)
11775         {
11776           gfc_error ("Nonconstant array section at %L in DATA statement",
11777                      &e->where);
11778           mpz_clear (offset);
11779           return FAILURE;
11780         }
11781     }
11782
11783   t = SUCCESS;
11784
11785   while (mpz_cmp_ui (size, 0) > 0)
11786     {
11787       if (next_data_value () == FAILURE)
11788         {
11789           gfc_error ("DATA statement at %L has more variables than values",
11790                      where);
11791           t = FAILURE;
11792           break;
11793         }
11794
11795       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
11796       if (t == FAILURE)
11797         break;
11798
11799       /* If we have more than one element left in the repeat count,
11800          and we have more than one element left in the target variable,
11801          then create a range assignment.  */
11802       /* FIXME: Only done for full arrays for now, since array sections
11803          seem tricky.  */
11804       if (mark == AR_FULL && ref && ref->next == NULL
11805           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
11806         {
11807           mpz_t range;
11808
11809           if (mpz_cmp (size, values.left) >= 0)
11810             {
11811               mpz_init_set (range, values.left);
11812               mpz_sub (size, size, values.left);
11813               mpz_set_ui (values.left, 0);
11814             }
11815           else
11816             {
11817               mpz_init_set (range, size);
11818               mpz_sub (values.left, values.left, size);
11819               mpz_set_ui (size, 0);
11820             }
11821
11822           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
11823                                            offset, range);
11824
11825           mpz_add (offset, offset, range);
11826           mpz_clear (range);
11827
11828           if (t == FAILURE)
11829             break;
11830         }
11831
11832       /* Assign initial value to symbol.  */
11833       else
11834         {
11835           mpz_sub_ui (values.left, values.left, 1);
11836           mpz_sub_ui (size, size, 1);
11837
11838           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11839           if (t == FAILURE)
11840             break;
11841
11842           if (mark == AR_FULL)
11843             mpz_add_ui (offset, offset, 1);
11844
11845           /* Modify the array section indexes and recalculate the offset
11846              for next element.  */
11847           else if (mark == AR_SECTION)
11848             gfc_advance_section (section_index, ar, &offset);
11849         }
11850     }
11851
11852   if (mark == AR_SECTION)
11853     {
11854       for (i = 0; i < ar->dimen; i++)
11855         mpz_clear (section_index[i]);
11856     }
11857
11858   mpz_clear (size);
11859   mpz_clear (offset);
11860
11861   return t;
11862 }
11863
11864
11865 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11866
11867 /* Iterate over a list of elements in a DATA statement.  */
11868
11869 static gfc_try
11870 traverse_data_list (gfc_data_variable *var, locus *where)
11871 {
11872   mpz_t trip;
11873   iterator_stack frame;
11874   gfc_expr *e, *start, *end, *step;
11875   gfc_try retval = SUCCESS;
11876
11877   mpz_init (frame.value);
11878   mpz_init (trip);
11879
11880   start = gfc_copy_expr (var->iter.start);
11881   end = gfc_copy_expr (var->iter.end);
11882   step = gfc_copy_expr (var->iter.step);
11883
11884   if (gfc_simplify_expr (start, 1) == FAILURE
11885       || start->expr_type != EXPR_CONSTANT)
11886     {
11887       gfc_error ("start of implied-do loop at %L could not be "
11888                  "simplified to a constant value", &start->where);
11889       retval = FAILURE;
11890       goto cleanup;
11891     }
11892   if (gfc_simplify_expr (end, 1) == FAILURE
11893       || end->expr_type != EXPR_CONSTANT)
11894     {
11895       gfc_error ("end of implied-do loop at %L could not be "
11896                  "simplified to a constant value", &start->where);
11897       retval = FAILURE;
11898       goto cleanup;
11899     }
11900   if (gfc_simplify_expr (step, 1) == FAILURE
11901       || step->expr_type != EXPR_CONSTANT)
11902     {
11903       gfc_error ("step of implied-do loop at %L could not be "
11904                  "simplified to a constant value", &start->where);
11905       retval = FAILURE;
11906       goto cleanup;
11907     }
11908
11909   mpz_set (trip, end->value.integer);
11910   mpz_sub (trip, trip, start->value.integer);
11911   mpz_add (trip, trip, step->value.integer);
11912
11913   mpz_div (trip, trip, step->value.integer);
11914
11915   mpz_set (frame.value, start->value.integer);
11916
11917   frame.prev = iter_stack;
11918   frame.variable = var->iter.var->symtree;
11919   iter_stack = &frame;
11920
11921   while (mpz_cmp_ui (trip, 0) > 0)
11922     {
11923       if (traverse_data_var (var->list, where) == FAILURE)
11924         {
11925           retval = FAILURE;
11926           goto cleanup;
11927         }
11928
11929       e = gfc_copy_expr (var->expr);
11930       if (gfc_simplify_expr (e, 1) == FAILURE)
11931         {
11932           gfc_free_expr (e);
11933           retval = FAILURE;
11934           goto cleanup;
11935         }
11936
11937       mpz_add (frame.value, frame.value, step->value.integer);
11938
11939       mpz_sub_ui (trip, trip, 1);
11940     }
11941
11942 cleanup:
11943   mpz_clear (frame.value);
11944   mpz_clear (trip);
11945
11946   gfc_free_expr (start);
11947   gfc_free_expr (end);
11948   gfc_free_expr (step);
11949
11950   iter_stack = frame.prev;
11951   return retval;
11952 }
11953
11954
11955 /* Type resolve variables in the variable list of a DATA statement.  */
11956
11957 static gfc_try
11958 traverse_data_var (gfc_data_variable *var, locus *where)
11959 {
11960   gfc_try t;
11961
11962   for (; var; var = var->next)
11963     {
11964       if (var->expr == NULL)
11965         t = traverse_data_list (var, where);
11966       else
11967         t = check_data_variable (var, where);
11968
11969       if (t == FAILURE)
11970         return FAILURE;
11971     }
11972
11973   return SUCCESS;
11974 }
11975
11976
11977 /* Resolve the expressions and iterators associated with a data statement.
11978    This is separate from the assignment checking because data lists should
11979    only be resolved once.  */
11980
11981 static gfc_try
11982 resolve_data_variables (gfc_data_variable *d)
11983 {
11984   for (; d; d = d->next)
11985     {
11986       if (d->list == NULL)
11987         {
11988           if (gfc_resolve_expr (d->expr) == FAILURE)
11989             return FAILURE;
11990         }
11991       else
11992         {
11993           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
11994             return FAILURE;
11995
11996           if (resolve_data_variables (d->list) == FAILURE)
11997             return FAILURE;
11998         }
11999     }
12000
12001   return SUCCESS;
12002 }
12003
12004
12005 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12006    the value list into static variables, and then recursively traversing the
12007    variables list, expanding iterators and such.  */
12008
12009 static void
12010 resolve_data (gfc_data *d)
12011 {
12012
12013   if (resolve_data_variables (d->var) == FAILURE)
12014     return;
12015
12016   values.vnode = d->value;
12017   if (d->value == NULL)
12018     mpz_set_ui (values.left, 0);
12019   else
12020     mpz_set (values.left, d->value->repeat);
12021
12022   if (traverse_data_var (d->var, &d->where) == FAILURE)
12023     return;
12024
12025   /* At this point, we better not have any values left.  */
12026
12027   if (next_data_value () == SUCCESS)
12028     gfc_error ("DATA statement at %L has more values than variables",
12029                &d->where);
12030 }
12031
12032
12033 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12034    accessed by host or use association, is a dummy argument to a pure function,
12035    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12036    is storage associated with any such variable, shall not be used in the
12037    following contexts: (clients of this function).  */
12038
12039 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12040    procedure.  Returns zero if assignment is OK, nonzero if there is a
12041    problem.  */
12042 int
12043 gfc_impure_variable (gfc_symbol *sym)
12044 {
12045   gfc_symbol *proc;
12046   gfc_namespace *ns;
12047
12048   if (sym->attr.use_assoc || sym->attr.in_common)
12049     return 1;
12050
12051   /* Check if the symbol's ns is inside the pure procedure.  */
12052   for (ns = gfc_current_ns; ns; ns = ns->parent)
12053     {
12054       if (ns == sym->ns)
12055         break;
12056       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12057         return 1;
12058     }
12059
12060   proc = sym->ns->proc_name;
12061   if (sym->attr.dummy && gfc_pure (proc)
12062         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12063                 ||
12064              proc->attr.function))
12065     return 1;
12066
12067   /* TODO: Sort out what can be storage associated, if anything, and include
12068      it here.  In principle equivalences should be scanned but it does not
12069      seem to be possible to storage associate an impure variable this way.  */
12070   return 0;
12071 }
12072
12073
12074 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12075    current namespace is inside a pure procedure.  */
12076
12077 int
12078 gfc_pure (gfc_symbol *sym)
12079 {
12080   symbol_attribute attr;
12081   gfc_namespace *ns;
12082
12083   if (sym == NULL)
12084     {
12085       /* Check if the current namespace or one of its parents
12086         belongs to a pure procedure.  */
12087       for (ns = gfc_current_ns; ns; ns = ns->parent)
12088         {
12089           sym = ns->proc_name;
12090           if (sym == NULL)
12091             return 0;
12092           attr = sym->attr;
12093           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
12094             return 1;
12095         }
12096       return 0;
12097     }
12098
12099   attr = sym->attr;
12100
12101   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
12102 }
12103
12104
12105 /* Test whether the current procedure is elemental or not.  */
12106
12107 int
12108 gfc_elemental (gfc_symbol *sym)
12109 {
12110   symbol_attribute attr;
12111
12112   if (sym == NULL)
12113     sym = gfc_current_ns->proc_name;
12114   if (sym == NULL)
12115     return 0;
12116   attr = sym->attr;
12117
12118   return attr.flavor == FL_PROCEDURE && attr.elemental;
12119 }
12120
12121
12122 /* Warn about unused labels.  */
12123
12124 static void
12125 warn_unused_fortran_label (gfc_st_label *label)
12126 {
12127   if (label == NULL)
12128     return;
12129
12130   warn_unused_fortran_label (label->left);
12131
12132   if (label->defined == ST_LABEL_UNKNOWN)
12133     return;
12134
12135   switch (label->referenced)
12136     {
12137     case ST_LABEL_UNKNOWN:
12138       gfc_warning ("Label %d at %L defined but not used", label->value,
12139                    &label->where);
12140       break;
12141
12142     case ST_LABEL_BAD_TARGET:
12143       gfc_warning ("Label %d at %L defined but cannot be used",
12144                    label->value, &label->where);
12145       break;
12146
12147     default:
12148       break;
12149     }
12150
12151   warn_unused_fortran_label (label->right);
12152 }
12153
12154
12155 /* Returns the sequence type of a symbol or sequence.  */
12156
12157 static seq_type
12158 sequence_type (gfc_typespec ts)
12159 {
12160   seq_type result;
12161   gfc_component *c;
12162
12163   switch (ts.type)
12164   {
12165     case BT_DERIVED:
12166
12167       if (ts.u.derived->components == NULL)
12168         return SEQ_NONDEFAULT;
12169
12170       result = sequence_type (ts.u.derived->components->ts);
12171       for (c = ts.u.derived->components->next; c; c = c->next)
12172         if (sequence_type (c->ts) != result)
12173           return SEQ_MIXED;
12174
12175       return result;
12176
12177     case BT_CHARACTER:
12178       if (ts.kind != gfc_default_character_kind)
12179           return SEQ_NONDEFAULT;
12180
12181       return SEQ_CHARACTER;
12182
12183     case BT_INTEGER:
12184       if (ts.kind != gfc_default_integer_kind)
12185           return SEQ_NONDEFAULT;
12186
12187       return SEQ_NUMERIC;
12188
12189     case BT_REAL:
12190       if (!(ts.kind == gfc_default_real_kind
12191             || ts.kind == gfc_default_double_kind))
12192           return SEQ_NONDEFAULT;
12193
12194       return SEQ_NUMERIC;
12195
12196     case BT_COMPLEX:
12197       if (ts.kind != gfc_default_complex_kind)
12198           return SEQ_NONDEFAULT;
12199
12200       return SEQ_NUMERIC;
12201
12202     case BT_LOGICAL:
12203       if (ts.kind != gfc_default_logical_kind)
12204           return SEQ_NONDEFAULT;
12205
12206       return SEQ_NUMERIC;
12207
12208     default:
12209       return SEQ_NONDEFAULT;
12210   }
12211 }
12212
12213
12214 /* Resolve derived type EQUIVALENCE object.  */
12215
12216 static gfc_try
12217 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12218 {
12219   gfc_component *c = derived->components;
12220
12221   if (!derived)
12222     return SUCCESS;
12223
12224   /* Shall not be an object of nonsequence derived type.  */
12225   if (!derived->attr.sequence)
12226     {
12227       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12228                  "attribute to be an EQUIVALENCE object", sym->name,
12229                  &e->where);
12230       return FAILURE;
12231     }
12232
12233   /* Shall not have allocatable components.  */
12234   if (derived->attr.alloc_comp)
12235     {
12236       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12237                  "components to be an EQUIVALENCE object",sym->name,
12238                  &e->where);
12239       return FAILURE;
12240     }
12241
12242   if (sym->attr.in_common && has_default_initializer (sym->ts.u.derived))
12243     {
12244       gfc_error ("Derived type variable '%s' at %L with default "
12245                  "initialization cannot be in EQUIVALENCE with a variable "
12246                  "in COMMON", sym->name, &e->where);
12247       return FAILURE;
12248     }
12249
12250   for (; c ; c = c->next)
12251     {
12252       if (c->ts.type == BT_DERIVED
12253           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12254         return FAILURE;
12255
12256       /* Shall not be an object of sequence derived type containing a pointer
12257          in the structure.  */
12258       if (c->attr.pointer)
12259         {
12260           gfc_error ("Derived type variable '%s' at %L with pointer "
12261                      "component(s) cannot be an EQUIVALENCE object",
12262                      sym->name, &e->where);
12263           return FAILURE;
12264         }
12265     }
12266   return SUCCESS;
12267 }
12268
12269
12270 /* Resolve equivalence object. 
12271    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12272    an allocatable array, an object of nonsequence derived type, an object of
12273    sequence derived type containing a pointer at any level of component
12274    selection, an automatic object, a function name, an entry name, a result
12275    name, a named constant, a structure component, or a subobject of any of
12276    the preceding objects.  A substring shall not have length zero.  A
12277    derived type shall not have components with default initialization nor
12278    shall two objects of an equivalence group be initialized.
12279    Either all or none of the objects shall have an protected attribute.
12280    The simple constraints are done in symbol.c(check_conflict) and the rest
12281    are implemented here.  */
12282
12283 static void
12284 resolve_equivalence (gfc_equiv *eq)
12285 {
12286   gfc_symbol *sym;
12287   gfc_symbol *first_sym;
12288   gfc_expr *e;
12289   gfc_ref *r;
12290   locus *last_where = NULL;
12291   seq_type eq_type, last_eq_type;
12292   gfc_typespec *last_ts;
12293   int object, cnt_protected;
12294   const char *msg;
12295
12296   last_ts = &eq->expr->symtree->n.sym->ts;
12297
12298   first_sym = eq->expr->symtree->n.sym;
12299
12300   cnt_protected = 0;
12301
12302   for (object = 1; eq; eq = eq->eq, object++)
12303     {
12304       e = eq->expr;
12305
12306       e->ts = e->symtree->n.sym->ts;
12307       /* match_varspec might not know yet if it is seeing
12308          array reference or substring reference, as it doesn't
12309          know the types.  */
12310       if (e->ref && e->ref->type == REF_ARRAY)
12311         {
12312           gfc_ref *ref = e->ref;
12313           sym = e->symtree->n.sym;
12314
12315           if (sym->attr.dimension)
12316             {
12317               ref->u.ar.as = sym->as;
12318               ref = ref->next;
12319             }
12320
12321           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12322           if (e->ts.type == BT_CHARACTER
12323               && ref
12324               && ref->type == REF_ARRAY
12325               && ref->u.ar.dimen == 1
12326               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12327               && ref->u.ar.stride[0] == NULL)
12328             {
12329               gfc_expr *start = ref->u.ar.start[0];
12330               gfc_expr *end = ref->u.ar.end[0];
12331               void *mem = NULL;
12332
12333               /* Optimize away the (:) reference.  */
12334               if (start == NULL && end == NULL)
12335                 {
12336                   if (e->ref == ref)
12337                     e->ref = ref->next;
12338                   else
12339                     e->ref->next = ref->next;
12340                   mem = ref;
12341                 }
12342               else
12343                 {
12344                   ref->type = REF_SUBSTRING;
12345                   if (start == NULL)
12346                     start = gfc_get_int_expr (gfc_default_integer_kind,
12347                                               NULL, 1);
12348                   ref->u.ss.start = start;
12349                   if (end == NULL && e->ts.u.cl)
12350                     end = gfc_copy_expr (e->ts.u.cl->length);
12351                   ref->u.ss.end = end;
12352                   ref->u.ss.length = e->ts.u.cl;
12353                   e->ts.u.cl = NULL;
12354                 }
12355               ref = ref->next;
12356               gfc_free (mem);
12357             }
12358
12359           /* Any further ref is an error.  */
12360           if (ref)
12361             {
12362               gcc_assert (ref->type == REF_ARRAY);
12363               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12364                          &ref->u.ar.where);
12365               continue;
12366             }
12367         }
12368
12369       if (gfc_resolve_expr (e) == FAILURE)
12370         continue;
12371
12372       sym = e->symtree->n.sym;
12373
12374       if (sym->attr.is_protected)
12375         cnt_protected++;
12376       if (cnt_protected > 0 && cnt_protected != object)
12377         {
12378               gfc_error ("Either all or none of the objects in the "
12379                          "EQUIVALENCE set at %L shall have the "
12380                          "PROTECTED attribute",
12381                          &e->where);
12382               break;
12383         }
12384
12385       /* Shall not equivalence common block variables in a PURE procedure.  */
12386       if (sym->ns->proc_name
12387           && sym->ns->proc_name->attr.pure
12388           && sym->attr.in_common)
12389         {
12390           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12391                      "object in the pure procedure '%s'",
12392                      sym->name, &e->where, sym->ns->proc_name->name);
12393           break;
12394         }
12395
12396       /* Shall not be a named constant.  */
12397       if (e->expr_type == EXPR_CONSTANT)
12398         {
12399           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12400                      "object", sym->name, &e->where);
12401           continue;
12402         }
12403
12404       if (e->ts.type == BT_DERIVED
12405           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12406         continue;
12407
12408       /* Check that the types correspond correctly:
12409          Note 5.28:
12410          A numeric sequence structure may be equivalenced to another sequence
12411          structure, an object of default integer type, default real type, double
12412          precision real type, default logical type such that components of the
12413          structure ultimately only become associated to objects of the same
12414          kind. A character sequence structure may be equivalenced to an object
12415          of default character kind or another character sequence structure.
12416          Other objects may be equivalenced only to objects of the same type and
12417          kind parameters.  */
12418
12419       /* Identical types are unconditionally OK.  */
12420       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12421         goto identical_types;
12422
12423       last_eq_type = sequence_type (*last_ts);
12424       eq_type = sequence_type (sym->ts);
12425
12426       /* Since the pair of objects is not of the same type, mixed or
12427          non-default sequences can be rejected.  */
12428
12429       msg = "Sequence %s with mixed components in EQUIVALENCE "
12430             "statement at %L with different type objects";
12431       if ((object ==2
12432            && last_eq_type == SEQ_MIXED
12433            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12434               == FAILURE)
12435           || (eq_type == SEQ_MIXED
12436               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12437                                  &e->where) == FAILURE))
12438         continue;
12439
12440       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12441             "statement at %L with objects of different type";
12442       if ((object ==2
12443            && last_eq_type == SEQ_NONDEFAULT
12444            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12445                               last_where) == FAILURE)
12446           || (eq_type == SEQ_NONDEFAULT
12447               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12448                                  &e->where) == FAILURE))
12449         continue;
12450
12451       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12452            "EQUIVALENCE statement at %L";
12453       if (last_eq_type == SEQ_CHARACTER
12454           && eq_type != SEQ_CHARACTER
12455           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12456                              &e->where) == FAILURE)
12457                 continue;
12458
12459       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12460            "EQUIVALENCE statement at %L";
12461       if (last_eq_type == SEQ_NUMERIC
12462           && eq_type != SEQ_NUMERIC
12463           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12464                              &e->where) == FAILURE)
12465                 continue;
12466
12467   identical_types:
12468       last_ts =&sym->ts;
12469       last_where = &e->where;
12470
12471       if (!e->ref)
12472         continue;
12473
12474       /* Shall not be an automatic array.  */
12475       if (e->ref->type == REF_ARRAY
12476           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12477         {
12478           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12479                      "an EQUIVALENCE object", sym->name, &e->where);
12480           continue;
12481         }
12482
12483       r = e->ref;
12484       while (r)
12485         {
12486           /* Shall not be a structure component.  */
12487           if (r->type == REF_COMPONENT)
12488             {
12489               gfc_error ("Structure component '%s' at %L cannot be an "
12490                          "EQUIVALENCE object",
12491                          r->u.c.component->name, &e->where);
12492               break;
12493             }
12494
12495           /* A substring shall not have length zero.  */
12496           if (r->type == REF_SUBSTRING)
12497             {
12498               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12499                 {
12500                   gfc_error ("Substring at %L has length zero",
12501                              &r->u.ss.start->where);
12502                   break;
12503                 }
12504             }
12505           r = r->next;
12506         }
12507     }
12508 }
12509
12510
12511 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12512
12513 static void
12514 resolve_fntype (gfc_namespace *ns)
12515 {
12516   gfc_entry_list *el;
12517   gfc_symbol *sym;
12518
12519   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12520     return;
12521
12522   /* If there are any entries, ns->proc_name is the entry master
12523      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12524   if (ns->entries)
12525     sym = ns->entries->sym;
12526   else
12527     sym = ns->proc_name;
12528   if (sym->result == sym
12529       && sym->ts.type == BT_UNKNOWN
12530       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12531       && !sym->attr.untyped)
12532     {
12533       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12534                  sym->name, &sym->declared_at);
12535       sym->attr.untyped = 1;
12536     }
12537
12538   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12539       && !sym->attr.contained
12540       && !gfc_check_access (sym->ts.u.derived->attr.access,
12541                             sym->ts.u.derived->ns->default_access)
12542       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12543     {
12544       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12545                       "%L of PRIVATE type '%s'", sym->name,
12546                       &sym->declared_at, sym->ts.u.derived->name);
12547     }
12548
12549     if (ns->entries)
12550     for (el = ns->entries->next; el; el = el->next)
12551       {
12552         if (el->sym->result == el->sym
12553             && el->sym->ts.type == BT_UNKNOWN
12554             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12555             && !el->sym->attr.untyped)
12556           {
12557             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12558                        el->sym->name, &el->sym->declared_at);
12559             el->sym->attr.untyped = 1;
12560           }
12561       }
12562 }
12563
12564
12565 /* 12.3.2.1.1 Defined operators.  */
12566
12567 static gfc_try
12568 check_uop_procedure (gfc_symbol *sym, locus where)
12569 {
12570   gfc_formal_arglist *formal;
12571
12572   if (!sym->attr.function)
12573     {
12574       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12575                  sym->name, &where);
12576       return FAILURE;
12577     }
12578
12579   if (sym->ts.type == BT_CHARACTER
12580       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12581       && !(sym->result && sym->result->ts.u.cl
12582            && sym->result->ts.u.cl->length))
12583     {
12584       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12585                  "character length", sym->name, &where);
12586       return FAILURE;
12587     }
12588
12589   formal = sym->formal;
12590   if (!formal || !formal->sym)
12591     {
12592       gfc_error ("User operator procedure '%s' at %L must have at least "
12593                  "one argument", sym->name, &where);
12594       return FAILURE;
12595     }
12596
12597   if (formal->sym->attr.intent != INTENT_IN)
12598     {
12599       gfc_error ("First argument of operator interface at %L must be "
12600                  "INTENT(IN)", &where);
12601       return FAILURE;
12602     }
12603
12604   if (formal->sym->attr.optional)
12605     {
12606       gfc_error ("First argument of operator interface at %L cannot be "
12607                  "optional", &where);
12608       return FAILURE;
12609     }
12610
12611   formal = formal->next;
12612   if (!formal || !formal->sym)
12613     return SUCCESS;
12614
12615   if (formal->sym->attr.intent != INTENT_IN)
12616     {
12617       gfc_error ("Second argument of operator interface at %L must be "
12618                  "INTENT(IN)", &where);
12619       return FAILURE;
12620     }
12621
12622   if (formal->sym->attr.optional)
12623     {
12624       gfc_error ("Second argument of operator interface at %L cannot be "
12625                  "optional", &where);
12626       return FAILURE;
12627     }
12628
12629   if (formal->next)
12630     {
12631       gfc_error ("Operator interface at %L must have, at most, two "
12632                  "arguments", &where);
12633       return FAILURE;
12634     }
12635
12636   return SUCCESS;
12637 }
12638
12639 static void
12640 gfc_resolve_uops (gfc_symtree *symtree)
12641 {
12642   gfc_interface *itr;
12643
12644   if (symtree == NULL)
12645     return;
12646
12647   gfc_resolve_uops (symtree->left);
12648   gfc_resolve_uops (symtree->right);
12649
12650   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12651     check_uop_procedure (itr->sym, itr->sym->declared_at);
12652 }
12653
12654
12655 /* Examine all of the expressions associated with a program unit,
12656    assign types to all intermediate expressions, make sure that all
12657    assignments are to compatible types and figure out which names
12658    refer to which functions or subroutines.  It doesn't check code
12659    block, which is handled by resolve_code.  */
12660
12661 static void
12662 resolve_types (gfc_namespace *ns)
12663 {
12664   gfc_namespace *n;
12665   gfc_charlen *cl;
12666   gfc_data *d;
12667   gfc_equiv *eq;
12668   gfc_namespace* old_ns = gfc_current_ns;
12669
12670   /* Check that all IMPLICIT types are ok.  */
12671   if (!ns->seen_implicit_none)
12672     {
12673       unsigned letter;
12674       for (letter = 0; letter != GFC_LETTERS; ++letter)
12675         if (ns->set_flag[letter]
12676             && resolve_typespec_used (&ns->default_type[letter],
12677                                       &ns->implicit_loc[letter],
12678                                       NULL) == FAILURE)
12679           return;
12680     }
12681
12682   gfc_current_ns = ns;
12683
12684   resolve_entries (ns);
12685
12686   resolve_common_vars (ns->blank_common.head, false);
12687   resolve_common_blocks (ns->common_root);
12688
12689   resolve_contained_functions (ns);
12690
12691   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12692
12693   for (cl = ns->cl_list; cl; cl = cl->next)
12694     resolve_charlen (cl);
12695
12696   gfc_traverse_ns (ns, resolve_symbol);
12697
12698   resolve_fntype (ns);
12699
12700   for (n = ns->contained; n; n = n->sibling)
12701     {
12702       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12703         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12704                    "also be PURE", n->proc_name->name,
12705                    &n->proc_name->declared_at);
12706
12707       resolve_types (n);
12708     }
12709
12710   forall_flag = 0;
12711   gfc_check_interfaces (ns);
12712
12713   gfc_traverse_ns (ns, resolve_values);
12714
12715   if (ns->save_all)
12716     gfc_save_all (ns);
12717
12718   iter_stack = NULL;
12719   for (d = ns->data; d; d = d->next)
12720     resolve_data (d);
12721
12722   iter_stack = NULL;
12723   gfc_traverse_ns (ns, gfc_formalize_init_value);
12724
12725   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12726
12727   if (ns->common_root != NULL)
12728     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12729
12730   for (eq = ns->equiv; eq; eq = eq->next)
12731     resolve_equivalence (eq);
12732
12733   /* Warn about unused labels.  */
12734   if (warn_unused_label)
12735     warn_unused_fortran_label (ns->st_labels);
12736
12737   gfc_resolve_uops (ns->uop_root);
12738
12739   gfc_current_ns = old_ns;
12740 }
12741
12742
12743 /* Call resolve_code recursively.  */
12744
12745 static void
12746 resolve_codes (gfc_namespace *ns)
12747 {
12748   gfc_namespace *n;
12749   bitmap_obstack old_obstack;
12750
12751   for (n = ns->contained; n; n = n->sibling)
12752     resolve_codes (n);
12753
12754   gfc_current_ns = ns;
12755
12756   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
12757   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
12758     cs_base = NULL;
12759
12760   /* Set to an out of range value.  */
12761   current_entry_id = -1;
12762
12763   old_obstack = labels_obstack;
12764   bitmap_obstack_initialize (&labels_obstack);
12765
12766   resolve_code (ns->code, ns);
12767
12768   bitmap_obstack_release (&labels_obstack);
12769   labels_obstack = old_obstack;
12770 }
12771
12772
12773 /* This function is called after a complete program unit has been compiled.
12774    Its purpose is to examine all of the expressions associated with a program
12775    unit, assign types to all intermediate expressions, make sure that all
12776    assignments are to compatible types and figure out which names refer to
12777    which functions or subroutines.  */
12778
12779 void
12780 gfc_resolve (gfc_namespace *ns)
12781 {
12782   gfc_namespace *old_ns;
12783   code_stack *old_cs_base;
12784
12785   if (ns->resolved)
12786     return;
12787
12788   ns->resolved = -1;
12789   old_ns = gfc_current_ns;
12790   old_cs_base = cs_base;
12791
12792   resolve_types (ns);
12793   resolve_codes (ns);
12794
12795   gfc_current_ns = old_ns;
12796   cs_base = old_cs_base;
12797   ns->resolved = 1;
12798 }