OSDN Git Service

2010-07-30 Mikael Morin <mikael@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 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 /* Resolve common variables.  */
707 static void
708 resolve_common_vars (gfc_symbol *sym, bool named_common)
709 {
710   gfc_symbol *csym = sym;
711
712   for (; csym; csym = csym->common_next)
713     {
714       if (csym->value || csym->attr.data)
715         {
716           if (!csym->ns->is_block_data)
717             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
718                             "but only in BLOCK DATA initialization is "
719                             "allowed", csym->name, &csym->declared_at);
720           else if (!named_common)
721             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
722                             "in a blank COMMON but initialization is only "
723                             "allowed in named common blocks", csym->name,
724                             &csym->declared_at);
725         }
726
727       if (csym->ts.type != BT_DERIVED)
728         continue;
729
730       if (!(csym->ts.u.derived->attr.sequence
731             || csym->ts.u.derived->attr.is_bind_c))
732         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
733                        "has neither the SEQUENCE nor the BIND(C) "
734                        "attribute", csym->name, &csym->declared_at);
735       if (csym->ts.u.derived->attr.alloc_comp)
736         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
737                        "has an ultimate component that is "
738                        "allocatable", csym->name, &csym->declared_at);
739       if (gfc_has_default_initializer (csym->ts.u.derived))
740         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
741                        "may not have default initializer", csym->name,
742                        &csym->declared_at);
743
744       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
745         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
746     }
747 }
748
749 /* Resolve common blocks.  */
750 static void
751 resolve_common_blocks (gfc_symtree *common_root)
752 {
753   gfc_symbol *sym;
754
755   if (common_root == NULL)
756     return;
757
758   if (common_root->left)
759     resolve_common_blocks (common_root->left);
760   if (common_root->right)
761     resolve_common_blocks (common_root->right);
762
763   resolve_common_vars (common_root->n.common->head, true);
764
765   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
766   if (sym == NULL)
767     return;
768
769   if (sym->attr.flavor == FL_PARAMETER)
770     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
771                sym->name, &common_root->n.common->where, &sym->declared_at);
772
773   if (sym->attr.intrinsic)
774     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
775                sym->name, &common_root->n.common->where);
776   else if (sym->attr.result
777            || gfc_is_function_return_value (sym, gfc_current_ns))
778     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
779                     "that is also a function result", sym->name,
780                     &common_root->n.common->where);
781   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
782            && sym->attr.proc != PROC_ST_FUNCTION)
783     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
784                     "that is also a global procedure", sym->name,
785                     &common_root->n.common->where);
786 }
787
788
789 /* Resolve contained function types.  Because contained functions can call one
790    another, they have to be worked out before any of the contained procedures
791    can be resolved.
792
793    The good news is that if a function doesn't already have a type, the only
794    way it can get one is through an IMPLICIT type or a RESULT variable, because
795    by definition contained functions are contained namespace they're contained
796    in, not in a sibling or parent namespace.  */
797
798 static void
799 resolve_contained_functions (gfc_namespace *ns)
800 {
801   gfc_namespace *child;
802   gfc_entry_list *el;
803
804   resolve_formal_arglists (ns);
805
806   for (child = ns->contained; child; child = child->sibling)
807     {
808       /* Resolve alternate entry points first.  */
809       resolve_entries (child);
810
811       /* Then check function return types.  */
812       resolve_contained_fntype (child->proc_name, child);
813       for (el = child->entries; el; el = el->next)
814         resolve_contained_fntype (el->sym, child);
815     }
816 }
817
818
819 /* Resolve all of the elements of a structure constructor and make sure that
820    the types are correct.  */
821
822 static gfc_try
823 resolve_structure_cons (gfc_expr *expr)
824 {
825   gfc_constructor *cons;
826   gfc_component *comp;
827   gfc_try t;
828   symbol_attribute a;
829
830   t = SUCCESS;
831   cons = gfc_constructor_first (expr->value.constructor);
832   /* A constructor may have references if it is the result of substituting a
833      parameter variable.  In this case we just pull out the component we
834      want.  */
835   if (expr->ref)
836     comp = expr->ref->u.c.sym->components;
837   else
838     comp = expr->ts.u.derived->components;
839
840   /* See if the user is trying to invoke a structure constructor for one of
841      the iso_c_binding derived types.  */
842   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
843       && expr->ts.u.derived->ts.is_iso_c && cons
844       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
845     {
846       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
847                  expr->ts.u.derived->name, &(expr->where));
848       return FAILURE;
849     }
850
851   /* Return if structure constructor is c_null_(fun)prt.  */
852   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
853       && expr->ts.u.derived->ts.is_iso_c && cons
854       && cons->expr && cons->expr->expr_type == EXPR_NULL)
855     return SUCCESS;
856
857   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
858     {
859       int rank;
860
861       if (!cons->expr)
862         continue;
863
864       if (gfc_resolve_expr (cons->expr) == FAILURE)
865         {
866           t = FAILURE;
867           continue;
868         }
869
870       rank = comp->as ? comp->as->rank : 0;
871       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
872           && (comp->attr.allocatable || cons->expr->rank))
873         {
874           gfc_error ("The rank of the element in the derived type "
875                      "constructor at %L does not match that of the "
876                      "component (%d/%d)", &cons->expr->where,
877                      cons->expr->rank, rank);
878           t = FAILURE;
879         }
880
881       /* If we don't have the right type, try to convert it.  */
882
883       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
884         {
885           t = FAILURE;
886           if (strcmp (comp->name, "$extends") == 0)
887             {
888               /* Can afford to be brutal with the $extends initializer.
889                  The derived type can get lost because it is PRIVATE
890                  but it is not usage constrained by the standard.  */
891               cons->expr->ts = comp->ts;
892               t = SUCCESS;
893             }
894           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
895             gfc_error ("The element in the derived type constructor at %L, "
896                        "for pointer component '%s', is %s but should be %s",
897                        &cons->expr->where, comp->name,
898                        gfc_basic_typename (cons->expr->ts.type),
899                        gfc_basic_typename (comp->ts.type));
900           else
901             t = gfc_convert_type (cons->expr, &comp->ts, 1);
902         }
903
904       if (cons->expr->expr_type == EXPR_NULL
905           && !(comp->attr.pointer || comp->attr.allocatable
906                || comp->attr.proc_pointer
907                || (comp->ts.type == BT_CLASS
908                    && (CLASS_DATA (comp)->attr.class_pointer
909                        || CLASS_DATA (comp)->attr.allocatable))))
910         {
911           t = FAILURE;
912           gfc_error ("The NULL in the derived type constructor at %L is "
913                      "being applied to component '%s', which is neither "
914                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
915                      comp->name);
916         }
917
918       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
919         continue;
920
921       a = gfc_expr_attr (cons->expr);
922
923       if (!a.pointer && !a.target)
924         {
925           t = FAILURE;
926           gfc_error ("The element in the derived type constructor at %L, "
927                      "for pointer component '%s' should be a POINTER or "
928                      "a TARGET", &cons->expr->where, comp->name);
929         }
930
931       /* F2003, C1272 (3).  */
932       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
933           && (gfc_impure_variable (cons->expr->symtree->n.sym)
934               || gfc_is_coindexed (cons->expr)))
935         {
936           t = FAILURE;
937           gfc_error ("Invalid expression in the derived type constructor for "
938                      "pointer component '%s' at %L in PURE procedure",
939                      comp->name, &cons->expr->where);
940         }
941     }
942
943   return t;
944 }
945
946
947 /****************** Expression name resolution ******************/
948
949 /* Returns 0 if a symbol was not declared with a type or
950    attribute declaration statement, nonzero otherwise.  */
951
952 static int
953 was_declared (gfc_symbol *sym)
954 {
955   symbol_attribute a;
956
957   a = sym->attr;
958
959   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
960     return 1;
961
962   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
963       || a.optional || a.pointer || a.save || a.target || a.volatile_
964       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
965       || a.asynchronous || a.codimension)
966     return 1;
967
968   return 0;
969 }
970
971
972 /* Determine if a symbol is generic or not.  */
973
974 static int
975 generic_sym (gfc_symbol *sym)
976 {
977   gfc_symbol *s;
978
979   if (sym->attr.generic ||
980       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
981     return 1;
982
983   if (was_declared (sym) || sym->ns->parent == NULL)
984     return 0;
985
986   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
987   
988   if (s != NULL)
989     {
990       if (s == sym)
991         return 0;
992       else
993         return generic_sym (s);
994     }
995
996   return 0;
997 }
998
999
1000 /* Determine if a symbol is specific or not.  */
1001
1002 static int
1003 specific_sym (gfc_symbol *sym)
1004 {
1005   gfc_symbol *s;
1006
1007   if (sym->attr.if_source == IFSRC_IFBODY
1008       || sym->attr.proc == PROC_MODULE
1009       || sym->attr.proc == PROC_INTERNAL
1010       || sym->attr.proc == PROC_ST_FUNCTION
1011       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1012       || sym->attr.external)
1013     return 1;
1014
1015   if (was_declared (sym) || sym->ns->parent == NULL)
1016     return 0;
1017
1018   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1019
1020   return (s == NULL) ? 0 : specific_sym (s);
1021 }
1022
1023
1024 /* Figure out if the procedure is specific, generic or unknown.  */
1025
1026 typedef enum
1027 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1028 proc_type;
1029
1030 static proc_type
1031 procedure_kind (gfc_symbol *sym)
1032 {
1033   if (generic_sym (sym))
1034     return PTYPE_GENERIC;
1035
1036   if (specific_sym (sym))
1037     return PTYPE_SPECIFIC;
1038
1039   return PTYPE_UNKNOWN;
1040 }
1041
1042 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1043    is nonzero when matching actual arguments.  */
1044
1045 static int need_full_assumed_size = 0;
1046
1047 static bool
1048 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1049 {
1050   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1051       return false;
1052
1053   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1054      What should it be?  */
1055   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1056           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1057                && (e->ref->u.ar.type == AR_FULL))
1058     {
1059       gfc_error ("The upper bound in the last dimension must "
1060                  "appear in the reference to the assumed size "
1061                  "array '%s' at %L", sym->name, &e->where);
1062       return true;
1063     }
1064   return false;
1065 }
1066
1067
1068 /* Look for bad assumed size array references in argument expressions
1069   of elemental and array valued intrinsic procedures.  Since this is
1070   called from procedure resolution functions, it only recurses at
1071   operators.  */
1072
1073 static bool
1074 resolve_assumed_size_actual (gfc_expr *e)
1075 {
1076   if (e == NULL)
1077    return false;
1078
1079   switch (e->expr_type)
1080     {
1081     case EXPR_VARIABLE:
1082       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1083         return true;
1084       break;
1085
1086     case EXPR_OP:
1087       if (resolve_assumed_size_actual (e->value.op.op1)
1088           || resolve_assumed_size_actual (e->value.op.op2))
1089         return true;
1090       break;
1091
1092     default:
1093       break;
1094     }
1095   return false;
1096 }
1097
1098
1099 /* Check a generic procedure, passed as an actual argument, to see if
1100    there is a matching specific name.  If none, it is an error, and if
1101    more than one, the reference is ambiguous.  */
1102 static int
1103 count_specific_procs (gfc_expr *e)
1104 {
1105   int n;
1106   gfc_interface *p;
1107   gfc_symbol *sym;
1108         
1109   n = 0;
1110   sym = e->symtree->n.sym;
1111
1112   for (p = sym->generic; p; p = p->next)
1113     if (strcmp (sym->name, p->sym->name) == 0)
1114       {
1115         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1116                                        sym->name);
1117         n++;
1118       }
1119
1120   if (n > 1)
1121     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1122                &e->where);
1123
1124   if (n == 0)
1125     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1126                "argument at %L", sym->name, &e->where);
1127
1128   return n;
1129 }
1130
1131
1132 /* See if a call to sym could possibly be a not allowed RECURSION because of
1133    a missing RECURIVE declaration.  This means that either sym is the current
1134    context itself, or sym is the parent of a contained procedure calling its
1135    non-RECURSIVE containing procedure.
1136    This also works if sym is an ENTRY.  */
1137
1138 static bool
1139 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1140 {
1141   gfc_symbol* proc_sym;
1142   gfc_symbol* context_proc;
1143   gfc_namespace* real_context;
1144
1145   if (sym->attr.flavor == FL_PROGRAM)
1146     return false;
1147
1148   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1149
1150   /* If we've got an ENTRY, find real procedure.  */
1151   if (sym->attr.entry && sym->ns->entries)
1152     proc_sym = sym->ns->entries->sym;
1153   else
1154     proc_sym = sym;
1155
1156   /* If sym is RECURSIVE, all is well of course.  */
1157   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1158     return false;
1159
1160   /* Find the context procedure's "real" symbol if it has entries.
1161      We look for a procedure symbol, so recurse on the parents if we don't
1162      find one (like in case of a BLOCK construct).  */
1163   for (real_context = context; ; real_context = real_context->parent)
1164     {
1165       /* We should find something, eventually!  */
1166       gcc_assert (real_context);
1167
1168       context_proc = (real_context->entries ? real_context->entries->sym
1169                                             : real_context->proc_name);
1170
1171       /* In some special cases, there may not be a proc_name, like for this
1172          invalid code:
1173          real(bad_kind()) function foo () ...
1174          when checking the call to bad_kind ().
1175          In these cases, we simply return here and assume that the
1176          call is ok.  */
1177       if (!context_proc)
1178         return false;
1179
1180       if (context_proc->attr.flavor != FL_LABEL)
1181         break;
1182     }
1183
1184   /* A call from sym's body to itself is recursion, of course.  */
1185   if (context_proc == proc_sym)
1186     return true;
1187
1188   /* The same is true if context is a contained procedure and sym the
1189      containing one.  */
1190   if (context_proc->attr.contained)
1191     {
1192       gfc_symbol* parent_proc;
1193
1194       gcc_assert (context->parent);
1195       parent_proc = (context->parent->entries ? context->parent->entries->sym
1196                                               : context->parent->proc_name);
1197
1198       if (parent_proc == proc_sym)
1199         return true;
1200     }
1201
1202   return false;
1203 }
1204
1205
1206 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1207    its typespec and formal argument list.  */
1208
1209 static gfc_try
1210 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1211 {
1212   gfc_intrinsic_sym* isym;
1213   const char* symstd;
1214
1215   if (sym->formal)
1216     return SUCCESS;
1217
1218   /* We already know this one is an intrinsic, so we don't call
1219      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1220      gfc_find_subroutine directly to check whether it is a function or
1221      subroutine.  */
1222
1223   if ((isym = gfc_find_function (sym->name)))
1224     {
1225       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1226           && !sym->attr.implicit_type)
1227         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1228                       " ignored", sym->name, &sym->declared_at);
1229
1230       if (!sym->attr.function &&
1231           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1232         return FAILURE;
1233
1234       sym->ts = isym->ts;
1235     }
1236   else if ((isym = gfc_find_subroutine (sym->name)))
1237     {
1238       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1239         {
1240           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1241                       " specifier", sym->name, &sym->declared_at);
1242           return FAILURE;
1243         }
1244
1245       if (!sym->attr.subroutine &&
1246           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1247         return FAILURE;
1248     }
1249   else
1250     {
1251       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1252                  &sym->declared_at);
1253       return FAILURE;
1254     }
1255
1256   gfc_copy_formal_args_intr (sym, isym);
1257
1258   /* Check it is actually available in the standard settings.  */
1259   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1260       == FAILURE)
1261     {
1262       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1263                  " available in the current standard settings but %s.  Use"
1264                  " an appropriate -std=* option or enable -fall-intrinsics"
1265                  " in order to use it.",
1266                  sym->name, &sym->declared_at, symstd);
1267       return FAILURE;
1268     }
1269
1270   return SUCCESS;
1271 }
1272
1273
1274 /* Resolve a procedure expression, like passing it to a called procedure or as
1275    RHS for a procedure pointer assignment.  */
1276
1277 static gfc_try
1278 resolve_procedure_expression (gfc_expr* expr)
1279 {
1280   gfc_symbol* sym;
1281
1282   if (expr->expr_type != EXPR_VARIABLE)
1283     return SUCCESS;
1284   gcc_assert (expr->symtree);
1285
1286   sym = expr->symtree->n.sym;
1287
1288   if (sym->attr.intrinsic)
1289     resolve_intrinsic (sym, &expr->where);
1290
1291   if (sym->attr.flavor != FL_PROCEDURE
1292       || (sym->attr.function && sym->result == sym))
1293     return SUCCESS;
1294
1295   /* A non-RECURSIVE procedure that is used as procedure expression within its
1296      own body is in danger of being called recursively.  */
1297   if (is_illegal_recursion (sym, gfc_current_ns))
1298     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1299                  " itself recursively.  Declare it RECURSIVE or use"
1300                  " -frecursive", sym->name, &expr->where);
1301   
1302   return SUCCESS;
1303 }
1304
1305
1306 /* Resolve an actual argument list.  Most of the time, this is just
1307    resolving the expressions in the list.
1308    The exception is that we sometimes have to decide whether arguments
1309    that look like procedure arguments are really simple variable
1310    references.  */
1311
1312 static gfc_try
1313 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1314                         bool no_formal_args)
1315 {
1316   gfc_symbol *sym;
1317   gfc_symtree *parent_st;
1318   gfc_expr *e;
1319   int save_need_full_assumed_size;
1320   gfc_component *comp;
1321
1322   for (; arg; arg = arg->next)
1323     {
1324       e = arg->expr;
1325       if (e == NULL)
1326         {
1327           /* Check the label is a valid branching target.  */
1328           if (arg->label)
1329             {
1330               if (arg->label->defined == ST_LABEL_UNKNOWN)
1331                 {
1332                   gfc_error ("Label %d referenced at %L is never defined",
1333                              arg->label->value, &arg->label->where);
1334                   return FAILURE;
1335                 }
1336             }
1337           continue;
1338         }
1339
1340       if (gfc_is_proc_ptr_comp (e, &comp))
1341         {
1342           e->ts = comp->ts;
1343           if (e->expr_type == EXPR_PPC)
1344             {
1345               if (comp->as != NULL)
1346                 e->rank = comp->as->rank;
1347               e->expr_type = EXPR_FUNCTION;
1348             }
1349           if (gfc_resolve_expr (e) == FAILURE)                          
1350             return FAILURE; 
1351           goto argument_list;
1352         }
1353
1354       if (e->expr_type == EXPR_VARIABLE
1355             && e->symtree->n.sym->attr.generic
1356             && no_formal_args
1357             && count_specific_procs (e) != 1)
1358         return FAILURE;
1359
1360       if (e->ts.type != BT_PROCEDURE)
1361         {
1362           save_need_full_assumed_size = need_full_assumed_size;
1363           if (e->expr_type != EXPR_VARIABLE)
1364             need_full_assumed_size = 0;
1365           if (gfc_resolve_expr (e) != SUCCESS)
1366             return FAILURE;
1367           need_full_assumed_size = save_need_full_assumed_size;
1368           goto argument_list;
1369         }
1370
1371       /* See if the expression node should really be a variable reference.  */
1372
1373       sym = e->symtree->n.sym;
1374
1375       if (sym->attr.flavor == FL_PROCEDURE
1376           || sym->attr.intrinsic
1377           || sym->attr.external)
1378         {
1379           int actual_ok;
1380
1381           /* If a procedure is not already determined to be something else
1382              check if it is intrinsic.  */
1383           if (!sym->attr.intrinsic
1384               && !(sym->attr.external || sym->attr.use_assoc
1385                    || sym->attr.if_source == IFSRC_IFBODY)
1386               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1387             sym->attr.intrinsic = 1;
1388
1389           if (sym->attr.proc == PROC_ST_FUNCTION)
1390             {
1391               gfc_error ("Statement function '%s' at %L is not allowed as an "
1392                          "actual argument", sym->name, &e->where);
1393             }
1394
1395           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1396                                                sym->attr.subroutine);
1397           if (sym->attr.intrinsic && actual_ok == 0)
1398             {
1399               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1400                          "actual argument", sym->name, &e->where);
1401             }
1402
1403           if (sym->attr.contained && !sym->attr.use_assoc
1404               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1405             {
1406               gfc_error ("Internal procedure '%s' is not allowed as an "
1407                          "actual argument at %L", sym->name, &e->where);
1408             }
1409
1410           if (sym->attr.elemental && !sym->attr.intrinsic)
1411             {
1412               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1413                          "allowed as an actual argument at %L", sym->name,
1414                          &e->where);
1415             }
1416
1417           /* Check if a generic interface has a specific procedure
1418             with the same name before emitting an error.  */
1419           if (sym->attr.generic && count_specific_procs (e) != 1)
1420             return FAILURE;
1421           
1422           /* Just in case a specific was found for the expression.  */
1423           sym = e->symtree->n.sym;
1424
1425           /* If the symbol is the function that names the current (or
1426              parent) scope, then we really have a variable reference.  */
1427
1428           if (gfc_is_function_return_value (sym, sym->ns))
1429             goto got_variable;
1430
1431           /* If all else fails, see if we have a specific intrinsic.  */
1432           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1433             {
1434               gfc_intrinsic_sym *isym;
1435
1436               isym = gfc_find_function (sym->name);
1437               if (isym == NULL || !isym->specific)
1438                 {
1439                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1440                              "for the reference '%s' at %L", sym->name,
1441                              &e->where);
1442                   return FAILURE;
1443                 }
1444               sym->ts = isym->ts;
1445               sym->attr.intrinsic = 1;
1446               sym->attr.function = 1;
1447             }
1448
1449           if (gfc_resolve_expr (e) == FAILURE)
1450             return FAILURE;
1451           goto argument_list;
1452         }
1453
1454       /* See if the name is a module procedure in a parent unit.  */
1455
1456       if (was_declared (sym) || sym->ns->parent == NULL)
1457         goto got_variable;
1458
1459       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1460         {
1461           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1462           return FAILURE;
1463         }
1464
1465       if (parent_st == NULL)
1466         goto got_variable;
1467
1468       sym = parent_st->n.sym;
1469       e->symtree = parent_st;           /* Point to the right thing.  */
1470
1471       if (sym->attr.flavor == FL_PROCEDURE
1472           || sym->attr.intrinsic
1473           || sym->attr.external)
1474         {
1475           if (gfc_resolve_expr (e) == FAILURE)
1476             return FAILURE;
1477           goto argument_list;
1478         }
1479
1480     got_variable:
1481       e->expr_type = EXPR_VARIABLE;
1482       e->ts = sym->ts;
1483       if (sym->as != NULL)
1484         {
1485           e->rank = sym->as->rank;
1486           e->ref = gfc_get_ref ();
1487           e->ref->type = REF_ARRAY;
1488           e->ref->u.ar.type = AR_FULL;
1489           e->ref->u.ar.as = sym->as;
1490         }
1491
1492       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1493          primary.c (match_actual_arg). If above code determines that it
1494          is a  variable instead, it needs to be resolved as it was not
1495          done at the beginning of this function.  */
1496       save_need_full_assumed_size = need_full_assumed_size;
1497       if (e->expr_type != EXPR_VARIABLE)
1498         need_full_assumed_size = 0;
1499       if (gfc_resolve_expr (e) != SUCCESS)
1500         return FAILURE;
1501       need_full_assumed_size = save_need_full_assumed_size;
1502
1503     argument_list:
1504       /* Check argument list functions %VAL, %LOC and %REF.  There is
1505          nothing to do for %REF.  */
1506       if (arg->name && arg->name[0] == '%')
1507         {
1508           if (strncmp ("%VAL", arg->name, 4) == 0)
1509             {
1510               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1511                 {
1512                   gfc_error ("By-value argument at %L is not of numeric "
1513                              "type", &e->where);
1514                   return FAILURE;
1515                 }
1516
1517               if (e->rank)
1518                 {
1519                   gfc_error ("By-value argument at %L cannot be an array or "
1520                              "an array section", &e->where);
1521                 return FAILURE;
1522                 }
1523
1524               /* Intrinsics are still PROC_UNKNOWN here.  However,
1525                  since same file external procedures are not resolvable
1526                  in gfortran, it is a good deal easier to leave them to
1527                  intrinsic.c.  */
1528               if (ptype != PROC_UNKNOWN
1529                   && ptype != PROC_DUMMY
1530                   && ptype != PROC_EXTERNAL
1531                   && ptype != PROC_MODULE)
1532                 {
1533                   gfc_error ("By-value argument at %L is not allowed "
1534                              "in this context", &e->where);
1535                   return FAILURE;
1536                 }
1537             }
1538
1539           /* Statement functions have already been excluded above.  */
1540           else if (strncmp ("%LOC", arg->name, 4) == 0
1541                    && e->ts.type == BT_PROCEDURE)
1542             {
1543               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1544                 {
1545                   gfc_error ("Passing internal procedure at %L by location "
1546                              "not allowed", &e->where);
1547                   return FAILURE;
1548                 }
1549             }
1550         }
1551
1552       /* Fortran 2008, C1237.  */
1553       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1554           && gfc_has_ultimate_pointer (e))
1555         {
1556           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1557                      "component", &e->where);
1558           return FAILURE;
1559         }
1560     }
1561
1562   return SUCCESS;
1563 }
1564
1565
1566 /* Do the checks of the actual argument list that are specific to elemental
1567    procedures.  If called with c == NULL, we have a function, otherwise if
1568    expr == NULL, we have a subroutine.  */
1569
1570 static gfc_try
1571 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1572 {
1573   gfc_actual_arglist *arg0;
1574   gfc_actual_arglist *arg;
1575   gfc_symbol *esym = NULL;
1576   gfc_intrinsic_sym *isym = NULL;
1577   gfc_expr *e = NULL;
1578   gfc_intrinsic_arg *iformal = NULL;
1579   gfc_formal_arglist *eformal = NULL;
1580   bool formal_optional = false;
1581   bool set_by_optional = false;
1582   int i;
1583   int rank = 0;
1584
1585   /* Is this an elemental procedure?  */
1586   if (expr && expr->value.function.actual != NULL)
1587     {
1588       if (expr->value.function.esym != NULL
1589           && expr->value.function.esym->attr.elemental)
1590         {
1591           arg0 = expr->value.function.actual;
1592           esym = expr->value.function.esym;
1593         }
1594       else if (expr->value.function.isym != NULL
1595                && expr->value.function.isym->elemental)
1596         {
1597           arg0 = expr->value.function.actual;
1598           isym = expr->value.function.isym;
1599         }
1600       else
1601         return SUCCESS;
1602     }
1603   else if (c && c->ext.actual != NULL)
1604     {
1605       arg0 = c->ext.actual;
1606       
1607       if (c->resolved_sym)
1608         esym = c->resolved_sym;
1609       else
1610         esym = c->symtree->n.sym;
1611       gcc_assert (esym);
1612
1613       if (!esym->attr.elemental)
1614         return SUCCESS;
1615     }
1616   else
1617     return SUCCESS;
1618
1619   /* The rank of an elemental is the rank of its array argument(s).  */
1620   for (arg = arg0; arg; arg = arg->next)
1621     {
1622       if (arg->expr != NULL && arg->expr->rank > 0)
1623         {
1624           rank = arg->expr->rank;
1625           if (arg->expr->expr_type == EXPR_VARIABLE
1626               && arg->expr->symtree->n.sym->attr.optional)
1627             set_by_optional = true;
1628
1629           /* Function specific; set the result rank and shape.  */
1630           if (expr)
1631             {
1632               expr->rank = rank;
1633               if (!expr->shape && arg->expr->shape)
1634                 {
1635                   expr->shape = gfc_get_shape (rank);
1636                   for (i = 0; i < rank; i++)
1637                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1638                 }
1639             }
1640           break;
1641         }
1642     }
1643
1644   /* If it is an array, it shall not be supplied as an actual argument
1645      to an elemental procedure unless an array of the same rank is supplied
1646      as an actual argument corresponding to a nonoptional dummy argument of
1647      that elemental procedure(12.4.1.5).  */
1648   formal_optional = false;
1649   if (isym)
1650     iformal = isym->formal;
1651   else
1652     eformal = esym->formal;
1653
1654   for (arg = arg0; arg; arg = arg->next)
1655     {
1656       if (eformal)
1657         {
1658           if (eformal->sym && eformal->sym->attr.optional)
1659             formal_optional = true;
1660           eformal = eformal->next;
1661         }
1662       else if (isym && iformal)
1663         {
1664           if (iformal->optional)
1665             formal_optional = true;
1666           iformal = iformal->next;
1667         }
1668       else if (isym)
1669         formal_optional = true;
1670
1671       if (pedantic && arg->expr != NULL
1672           && arg->expr->expr_type == EXPR_VARIABLE
1673           && arg->expr->symtree->n.sym->attr.optional
1674           && formal_optional
1675           && arg->expr->rank
1676           && (set_by_optional || arg->expr->rank != rank)
1677           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1678         {
1679           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1680                        "MISSING, it cannot be the actual argument of an "
1681                        "ELEMENTAL procedure unless there is a non-optional "
1682                        "argument with the same rank (12.4.1.5)",
1683                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1684           return FAILURE;
1685         }
1686     }
1687
1688   for (arg = arg0; arg; arg = arg->next)
1689     {
1690       if (arg->expr == NULL || arg->expr->rank == 0)
1691         continue;
1692
1693       /* Being elemental, the last upper bound of an assumed size array
1694          argument must be present.  */
1695       if (resolve_assumed_size_actual (arg->expr))
1696         return FAILURE;
1697
1698       /* Elemental procedure's array actual arguments must conform.  */
1699       if (e != NULL)
1700         {
1701           if (gfc_check_conformance (arg->expr, e,
1702                                      "elemental procedure") == FAILURE)
1703             return FAILURE;
1704         }
1705       else
1706         e = arg->expr;
1707     }
1708
1709   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1710      is an array, the intent inout/out variable needs to be also an array.  */
1711   if (rank > 0 && esym && expr == NULL)
1712     for (eformal = esym->formal, arg = arg0; arg && eformal;
1713          arg = arg->next, eformal = eformal->next)
1714       if ((eformal->sym->attr.intent == INTENT_OUT
1715            || eformal->sym->attr.intent == INTENT_INOUT)
1716           && arg->expr && arg->expr->rank == 0)
1717         {
1718           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1719                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1720                      "actual argument is an array", &arg->expr->where,
1721                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1722                      : "INOUT", eformal->sym->name, esym->name);
1723           return FAILURE;
1724         }
1725   return SUCCESS;
1726 }
1727
1728
1729 /* Go through each actual argument in ACTUAL and see if it can be
1730    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1731    function being called, or NULL if not known.  */
1732
1733 static void
1734 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1735 {
1736   gfc_actual_arglist *ap;
1737   gfc_expr *expr;
1738
1739   for (ap = actual; ap; ap = ap->next)
1740     if (ap->expr
1741         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1742         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1743                                          NOT_ELEMENTAL))
1744       ap->expr->inline_noncopying_intrinsic = 1;
1745 }
1746
1747
1748 /* This function does the checking of references to global procedures
1749    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1750    77 and 95 standards.  It checks for a gsymbol for the name, making
1751    one if it does not already exist.  If it already exists, then the
1752    reference being resolved must correspond to the type of gsymbol.
1753    Otherwise, the new symbol is equipped with the attributes of the
1754    reference.  The corresponding code that is called in creating
1755    global entities is parse.c.
1756
1757    In addition, for all but -std=legacy, the gsymbols are used to
1758    check the interfaces of external procedures from the same file.
1759    The namespace of the gsymbol is resolved and then, once this is
1760    done the interface is checked.  */
1761
1762
1763 static bool
1764 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1765 {
1766   if (!gsym_ns->proc_name->attr.recursive)
1767     return true;
1768
1769   if (sym->ns == gsym_ns)
1770     return false;
1771
1772   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1773     return false;
1774
1775   return true;
1776 }
1777
1778 static bool
1779 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1780 {
1781   if (gsym_ns->entries)
1782     {
1783       gfc_entry_list *entry = gsym_ns->entries;
1784
1785       for (; entry; entry = entry->next)
1786         {
1787           if (strcmp (sym->name, entry->sym->name) == 0)
1788             {
1789               if (strcmp (gsym_ns->proc_name->name,
1790                           sym->ns->proc_name->name) == 0)
1791                 return false;
1792
1793               if (sym->ns->parent
1794                   && strcmp (gsym_ns->proc_name->name,
1795                              sym->ns->parent->proc_name->name) == 0)
1796                 return false;
1797             }
1798         }
1799     }
1800   return true;
1801 }
1802
1803 static void
1804 resolve_global_procedure (gfc_symbol *sym, locus *where,
1805                           gfc_actual_arglist **actual, int sub)
1806 {
1807   gfc_gsymbol * gsym;
1808   gfc_namespace *ns;
1809   enum gfc_symbol_type type;
1810
1811   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1812
1813   gsym = gfc_get_gsymbol (sym->name);
1814
1815   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1816     gfc_global_used (gsym, where);
1817
1818   if (gfc_option.flag_whole_file
1819         && (sym->attr.if_source == IFSRC_UNKNOWN
1820             || sym->attr.if_source == IFSRC_IFBODY)
1821         && gsym->type != GSYM_UNKNOWN
1822         && gsym->ns
1823         && gsym->ns->resolved != -1
1824         && gsym->ns->proc_name
1825         && not_in_recursive (sym, gsym->ns)
1826         && not_entry_self_reference (sym, gsym->ns))
1827     {
1828       gfc_symbol *def_sym;
1829
1830       /* Resolve the gsymbol namespace if needed.  */
1831       if (!gsym->ns->resolved)
1832         {
1833           gfc_dt_list *old_dt_list;
1834
1835           /* Stash away derived types so that the backend_decls do not
1836              get mixed up.  */
1837           old_dt_list = gfc_derived_types;
1838           gfc_derived_types = NULL;
1839
1840           gfc_resolve (gsym->ns);
1841
1842           /* Store the new derived types with the global namespace.  */
1843           if (gfc_derived_types)
1844             gsym->ns->derived_types = gfc_derived_types;
1845
1846           /* Restore the derived types of this namespace.  */
1847           gfc_derived_types = old_dt_list;
1848         }
1849
1850       /* Make sure that translation for the gsymbol occurs before
1851          the procedure currently being resolved.  */
1852       ns = gfc_global_ns_list;
1853       for (; ns && ns != gsym->ns; ns = ns->sibling)
1854         {
1855           if (ns->sibling == gsym->ns)
1856             {
1857               ns->sibling = gsym->ns->sibling;
1858               gsym->ns->sibling = gfc_global_ns_list;
1859               gfc_global_ns_list = gsym->ns;
1860               break;
1861             }
1862         }
1863
1864       def_sym = gsym->ns->proc_name;
1865       if (def_sym->attr.entry_master)
1866         {
1867           gfc_entry_list *entry;
1868           for (entry = gsym->ns->entries; entry; entry = entry->next)
1869             if (strcmp (entry->sym->name, sym->name) == 0)
1870               {
1871                 def_sym = entry->sym;
1872                 break;
1873               }
1874         }
1875
1876       /* Differences in constant character lengths.  */
1877       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
1878         {
1879           long int l1 = 0, l2 = 0;
1880           gfc_charlen *cl1 = sym->ts.u.cl;
1881           gfc_charlen *cl2 = def_sym->ts.u.cl;
1882
1883           if (cl1 != NULL
1884               && cl1->length != NULL
1885               && cl1->length->expr_type == EXPR_CONSTANT)
1886             l1 = mpz_get_si (cl1->length->value.integer);
1887
1888           if (cl2 != NULL
1889               && cl2->length != NULL
1890               && cl2->length->expr_type == EXPR_CONSTANT)
1891             l2 = mpz_get_si (cl2->length->value.integer);
1892
1893           if (l1 && l2 && l1 != l2)
1894             gfc_error ("Character length mismatch in return type of "
1895                        "function '%s' at %L (%ld/%ld)", sym->name,
1896                        &sym->declared_at, l1, l2);
1897         }
1898
1899      /* Type mismatch of function return type and expected type.  */
1900      if (sym->attr.function
1901          && !gfc_compare_types (&sym->ts, &def_sym->ts))
1902         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
1903                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
1904                    gfc_typename (&def_sym->ts));
1905
1906       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
1907         {
1908           gfc_formal_arglist *arg = def_sym->formal;
1909           for ( ; arg; arg = arg->next)
1910             if (!arg->sym)
1911               continue;
1912             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
1913             else if (arg->sym->attr.allocatable
1914                      || arg->sym->attr.asynchronous
1915                      || arg->sym->attr.optional
1916                      || arg->sym->attr.pointer
1917                      || arg->sym->attr.target
1918                      || arg->sym->attr.value
1919                      || arg->sym->attr.volatile_)
1920               {
1921                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
1922                            "has an attribute that requires an explicit "
1923                            "interface for this procedure", arg->sym->name,
1924                            sym->name, &sym->declared_at);
1925                 break;
1926               }
1927             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
1928             else if (arg->sym && arg->sym->as
1929                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
1930               {
1931                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
1932                            "argument '%s' must have an explicit interface",
1933                            sym->name, &sym->declared_at, arg->sym->name);
1934                 break;
1935               }
1936             /* F2008, 12.4.2.2 (2c)  */
1937             else if (arg->sym->attr.codimension)
1938               {
1939                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
1940                            "'%s' must have an explicit interface",
1941                            sym->name, &sym->declared_at, arg->sym->name);
1942                 break;
1943               }
1944             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
1945             else if (false) /* TODO: is a parametrized derived type  */
1946               {
1947                 gfc_error ("Procedure '%s' at %L with parametrized derived "
1948                            "type argument '%s' must have an explicit "
1949                            "interface", sym->name, &sym->declared_at,
1950                            arg->sym->name);
1951                 break;
1952               }
1953             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
1954             else if (arg->sym->ts.type == BT_CLASS)
1955               {
1956                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
1957                            "argument '%s' must have an explicit interface",
1958                            sym->name, &sym->declared_at, arg->sym->name);
1959                 break;
1960               }
1961         }
1962
1963       if (def_sym->attr.function)
1964         {
1965           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
1966           if (def_sym->as && def_sym->as->rank
1967               && (!sym->as || sym->as->rank != def_sym->as->rank))
1968             gfc_error ("The reference to function '%s' at %L either needs an "
1969                        "explicit INTERFACE or the rank is incorrect", sym->name,
1970                        where);
1971
1972           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
1973           if ((def_sym->result->attr.pointer
1974                || def_sym->result->attr.allocatable)
1975                && (sym->attr.if_source != IFSRC_IFBODY
1976                    || def_sym->result->attr.pointer
1977                         != sym->result->attr.pointer
1978                    || def_sym->result->attr.allocatable
1979                         != sym->result->attr.allocatable))
1980             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
1981                        "result must have an explicit interface", sym->name,
1982                        where);
1983
1984           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
1985           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
1986               && def_sym->ts.u.cl->length != NULL)
1987             {
1988               gfc_charlen *cl = sym->ts.u.cl;
1989
1990               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1991                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1992                 {
1993                   gfc_error ("Nonconstant character-length function '%s' at %L "
1994                              "must have an explicit interface", sym->name,
1995                              &sym->declared_at);
1996                 }
1997             }
1998         }
1999
2000       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2001       if (def_sym->attr.elemental && !sym->attr.elemental)
2002         {
2003           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2004                      "interface", sym->name, &sym->declared_at);
2005         }
2006
2007       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2008       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2009         {
2010           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2011                      "an explicit interface", sym->name, &sym->declared_at);
2012         }
2013
2014       if (gfc_option.flag_whole_file == 1
2015           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2016               && !(gfc_option.warn_std & GFC_STD_GNU)))
2017         gfc_errors_to_warnings (1);
2018
2019       if (sym->attr.if_source != IFSRC_IFBODY)  
2020         gfc_procedure_use (def_sym, actual, where);
2021
2022       gfc_errors_to_warnings (0);
2023     }
2024
2025   if (gsym->type == GSYM_UNKNOWN)
2026     {
2027       gsym->type = type;
2028       gsym->where = *where;
2029     }
2030
2031   gsym->used = 1;
2032 }
2033
2034
2035 /************* Function resolution *************/
2036
2037 /* Resolve a function call known to be generic.
2038    Section 14.1.2.4.1.  */
2039
2040 static match
2041 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2042 {
2043   gfc_symbol *s;
2044
2045   if (sym->attr.generic)
2046     {
2047       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2048       if (s != NULL)
2049         {
2050           expr->value.function.name = s->name;
2051           expr->value.function.esym = s;
2052
2053           if (s->ts.type != BT_UNKNOWN)
2054             expr->ts = s->ts;
2055           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2056             expr->ts = s->result->ts;
2057
2058           if (s->as != NULL)
2059             expr->rank = s->as->rank;
2060           else if (s->result != NULL && s->result->as != NULL)
2061             expr->rank = s->result->as->rank;
2062
2063           gfc_set_sym_referenced (expr->value.function.esym);
2064
2065           return MATCH_YES;
2066         }
2067
2068       /* TODO: Need to search for elemental references in generic
2069          interface.  */
2070     }
2071
2072   if (sym->attr.intrinsic)
2073     return gfc_intrinsic_func_interface (expr, 0);
2074
2075   return MATCH_NO;
2076 }
2077
2078
2079 static gfc_try
2080 resolve_generic_f (gfc_expr *expr)
2081 {
2082   gfc_symbol *sym;
2083   match m;
2084
2085   sym = expr->symtree->n.sym;
2086
2087   for (;;)
2088     {
2089       m = resolve_generic_f0 (expr, sym);
2090       if (m == MATCH_YES)
2091         return SUCCESS;
2092       else if (m == MATCH_ERROR)
2093         return FAILURE;
2094
2095 generic:
2096       if (sym->ns->parent == NULL)
2097         break;
2098       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2099
2100       if (sym == NULL)
2101         break;
2102       if (!generic_sym (sym))
2103         goto generic;
2104     }
2105
2106   /* Last ditch attempt.  See if the reference is to an intrinsic
2107      that possesses a matching interface.  14.1.2.4  */
2108   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2109     {
2110       gfc_error ("There is no specific function for the generic '%s' at %L",
2111                  expr->symtree->n.sym->name, &expr->where);
2112       return FAILURE;
2113     }
2114
2115   m = gfc_intrinsic_func_interface (expr, 0);
2116   if (m == MATCH_YES)
2117     return SUCCESS;
2118   if (m == MATCH_NO)
2119     gfc_error ("Generic function '%s' at %L is not consistent with a "
2120                "specific intrinsic interface", expr->symtree->n.sym->name,
2121                &expr->where);
2122
2123   return FAILURE;
2124 }
2125
2126
2127 /* Resolve a function call known to be specific.  */
2128
2129 static match
2130 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2131 {
2132   match m;
2133
2134   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2135     {
2136       if (sym->attr.dummy)
2137         {
2138           sym->attr.proc = PROC_DUMMY;
2139           goto found;
2140         }
2141
2142       sym->attr.proc = PROC_EXTERNAL;
2143       goto found;
2144     }
2145
2146   if (sym->attr.proc == PROC_MODULE
2147       || sym->attr.proc == PROC_ST_FUNCTION
2148       || sym->attr.proc == PROC_INTERNAL)
2149     goto found;
2150
2151   if (sym->attr.intrinsic)
2152     {
2153       m = gfc_intrinsic_func_interface (expr, 1);
2154       if (m == MATCH_YES)
2155         return MATCH_YES;
2156       if (m == MATCH_NO)
2157         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2158                    "with an intrinsic", sym->name, &expr->where);
2159
2160       return MATCH_ERROR;
2161     }
2162
2163   return MATCH_NO;
2164
2165 found:
2166   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2167
2168   if (sym->result)
2169     expr->ts = sym->result->ts;
2170   else
2171     expr->ts = sym->ts;
2172   expr->value.function.name = sym->name;
2173   expr->value.function.esym = sym;
2174   if (sym->as != NULL)
2175     expr->rank = sym->as->rank;
2176
2177   return MATCH_YES;
2178 }
2179
2180
2181 static gfc_try
2182 resolve_specific_f (gfc_expr *expr)
2183 {
2184   gfc_symbol *sym;
2185   match m;
2186
2187   sym = expr->symtree->n.sym;
2188
2189   for (;;)
2190     {
2191       m = resolve_specific_f0 (sym, expr);
2192       if (m == MATCH_YES)
2193         return SUCCESS;
2194       if (m == MATCH_ERROR)
2195         return FAILURE;
2196
2197       if (sym->ns->parent == NULL)
2198         break;
2199
2200       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2201
2202       if (sym == NULL)
2203         break;
2204     }
2205
2206   gfc_error ("Unable to resolve the specific function '%s' at %L",
2207              expr->symtree->n.sym->name, &expr->where);
2208
2209   return SUCCESS;
2210 }
2211
2212
2213 /* Resolve a procedure call not known to be generic nor specific.  */
2214
2215 static gfc_try
2216 resolve_unknown_f (gfc_expr *expr)
2217 {
2218   gfc_symbol *sym;
2219   gfc_typespec *ts;
2220
2221   sym = expr->symtree->n.sym;
2222
2223   if (sym->attr.dummy)
2224     {
2225       sym->attr.proc = PROC_DUMMY;
2226       expr->value.function.name = sym->name;
2227       goto set_type;
2228     }
2229
2230   /* See if we have an intrinsic function reference.  */
2231
2232   if (gfc_is_intrinsic (sym, 0, expr->where))
2233     {
2234       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2235         return SUCCESS;
2236       return FAILURE;
2237     }
2238
2239   /* The reference is to an external name.  */
2240
2241   sym->attr.proc = PROC_EXTERNAL;
2242   expr->value.function.name = sym->name;
2243   expr->value.function.esym = expr->symtree->n.sym;
2244
2245   if (sym->as != NULL)
2246     expr->rank = sym->as->rank;
2247
2248   /* Type of the expression is either the type of the symbol or the
2249      default type of the symbol.  */
2250
2251 set_type:
2252   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2253
2254   if (sym->ts.type != BT_UNKNOWN)
2255     expr->ts = sym->ts;
2256   else
2257     {
2258       ts = gfc_get_default_type (sym->name, sym->ns);
2259
2260       if (ts->type == BT_UNKNOWN)
2261         {
2262           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2263                      sym->name, &expr->where);
2264           return FAILURE;
2265         }
2266       else
2267         expr->ts = *ts;
2268     }
2269
2270   return SUCCESS;
2271 }
2272
2273
2274 /* Return true, if the symbol is an external procedure.  */
2275 static bool
2276 is_external_proc (gfc_symbol *sym)
2277 {
2278   if (!sym->attr.dummy && !sym->attr.contained
2279         && !(sym->attr.intrinsic
2280               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2281         && sym->attr.proc != PROC_ST_FUNCTION
2282         && !sym->attr.proc_pointer
2283         && !sym->attr.use_assoc
2284         && sym->name)
2285     return true;
2286
2287   return false;
2288 }
2289
2290
2291 /* Figure out if a function reference is pure or not.  Also set the name
2292    of the function for a potential error message.  Return nonzero if the
2293    function is PURE, zero if not.  */
2294 static int
2295 pure_stmt_function (gfc_expr *, gfc_symbol *);
2296
2297 static int
2298 pure_function (gfc_expr *e, const char **name)
2299 {
2300   int pure;
2301
2302   *name = NULL;
2303
2304   if (e->symtree != NULL
2305         && e->symtree->n.sym != NULL
2306         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2307     return pure_stmt_function (e, e->symtree->n.sym);
2308
2309   if (e->value.function.esym)
2310     {
2311       pure = gfc_pure (e->value.function.esym);
2312       *name = e->value.function.esym->name;
2313     }
2314   else if (e->value.function.isym)
2315     {
2316       pure = e->value.function.isym->pure
2317              || e->value.function.isym->elemental;
2318       *name = e->value.function.isym->name;
2319     }
2320   else
2321     {
2322       /* Implicit functions are not pure.  */
2323       pure = 0;
2324       *name = e->value.function.name;
2325     }
2326
2327   return pure;
2328 }
2329
2330
2331 static bool
2332 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2333                  int *f ATTRIBUTE_UNUSED)
2334 {
2335   const char *name;
2336
2337   /* Don't bother recursing into other statement functions
2338      since they will be checked individually for purity.  */
2339   if (e->expr_type != EXPR_FUNCTION
2340         || !e->symtree
2341         || e->symtree->n.sym == sym
2342         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2343     return false;
2344
2345   return pure_function (e, &name) ? false : true;
2346 }
2347
2348
2349 static int
2350 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2351 {
2352   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2353 }
2354
2355
2356 static gfc_try
2357 is_scalar_expr_ptr (gfc_expr *expr)
2358 {
2359   gfc_try retval = SUCCESS;
2360   gfc_ref *ref;
2361   int start;
2362   int end;
2363
2364   /* See if we have a gfc_ref, which means we have a substring, array
2365      reference, or a component.  */
2366   if (expr->ref != NULL)
2367     {
2368       ref = expr->ref;
2369       while (ref->next != NULL)
2370         ref = ref->next;
2371
2372       switch (ref->type)
2373         {
2374         case REF_SUBSTRING:
2375           if (ref->u.ss.length != NULL 
2376               && ref->u.ss.length->length != NULL
2377               && ref->u.ss.start
2378               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2379               && ref->u.ss.end
2380               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2381             {
2382               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2383               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2384               if (end - start + 1 != 1)
2385                 retval = FAILURE;
2386             }
2387           else
2388             retval = FAILURE;
2389           break;
2390         case REF_ARRAY:
2391           if (ref->u.ar.type == AR_ELEMENT)
2392             retval = SUCCESS;
2393           else if (ref->u.ar.type == AR_FULL)
2394             {
2395               /* The user can give a full array if the array is of size 1.  */
2396               if (ref->u.ar.as != NULL
2397                   && ref->u.ar.as->rank == 1
2398                   && ref->u.ar.as->type == AS_EXPLICIT
2399                   && ref->u.ar.as->lower[0] != NULL
2400                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2401                   && ref->u.ar.as->upper[0] != NULL
2402                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2403                 {
2404                   /* If we have a character string, we need to check if
2405                      its length is one.  */
2406                   if (expr->ts.type == BT_CHARACTER)
2407                     {
2408                       if (expr->ts.u.cl == NULL
2409                           || expr->ts.u.cl->length == NULL
2410                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2411                           != 0)
2412                         retval = FAILURE;
2413                     }
2414                   else
2415                     {
2416                       /* We have constant lower and upper bounds.  If the
2417                          difference between is 1, it can be considered a
2418                          scalar.  */
2419                       start = (int) mpz_get_si
2420                                 (ref->u.ar.as->lower[0]->value.integer);
2421                       end = (int) mpz_get_si
2422                                 (ref->u.ar.as->upper[0]->value.integer);
2423                       if (end - start + 1 != 1)
2424                         retval = FAILURE;
2425                    }
2426                 }
2427               else
2428                 retval = FAILURE;
2429             }
2430           else
2431             retval = FAILURE;
2432           break;
2433         default:
2434           retval = SUCCESS;
2435           break;
2436         }
2437     }
2438   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2439     {
2440       /* Character string.  Make sure it's of length 1.  */
2441       if (expr->ts.u.cl == NULL
2442           || expr->ts.u.cl->length == NULL
2443           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2444         retval = FAILURE;
2445     }
2446   else if (expr->rank != 0)
2447     retval = FAILURE;
2448
2449   return retval;
2450 }
2451
2452
2453 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2454    and, in the case of c_associated, set the binding label based on
2455    the arguments.  */
2456
2457 static gfc_try
2458 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2459                           gfc_symbol **new_sym)
2460 {
2461   char name[GFC_MAX_SYMBOL_LEN + 1];
2462   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2463   int optional_arg = 0;
2464   gfc_try retval = SUCCESS;
2465   gfc_symbol *args_sym;
2466   gfc_typespec *arg_ts;
2467   symbol_attribute arg_attr;
2468
2469   if (args->expr->expr_type == EXPR_CONSTANT
2470       || args->expr->expr_type == EXPR_OP
2471       || args->expr->expr_type == EXPR_NULL)
2472     {
2473       gfc_error ("Argument to '%s' at %L is not a variable",
2474                  sym->name, &(args->expr->where));
2475       return FAILURE;
2476     }
2477
2478   args_sym = args->expr->symtree->n.sym;
2479
2480   /* The typespec for the actual arg should be that stored in the expr
2481      and not necessarily that of the expr symbol (args_sym), because
2482      the actual expression could be a part-ref of the expr symbol.  */
2483   arg_ts = &(args->expr->ts);
2484   arg_attr = gfc_expr_attr (args->expr);
2485     
2486   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2487     {
2488       /* If the user gave two args then they are providing something for
2489          the optional arg (the second cptr).  Therefore, set the name and
2490          binding label to the c_associated for two cptrs.  Otherwise,
2491          set c_associated to expect one cptr.  */
2492       if (args->next)
2493         {
2494           /* two args.  */
2495           sprintf (name, "%s_2", sym->name);
2496           sprintf (binding_label, "%s_2", sym->binding_label);
2497           optional_arg = 1;
2498         }
2499       else
2500         {
2501           /* one arg.  */
2502           sprintf (name, "%s_1", sym->name);
2503           sprintf (binding_label, "%s_1", sym->binding_label);
2504           optional_arg = 0;
2505         }
2506
2507       /* Get a new symbol for the version of c_associated that
2508          will get called.  */
2509       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2510     }
2511   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2512            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2513     {
2514       sprintf (name, "%s", sym->name);
2515       sprintf (binding_label, "%s", sym->binding_label);
2516
2517       /* Error check the call.  */
2518       if (args->next != NULL)
2519         {
2520           gfc_error_now ("More actual than formal arguments in '%s' "
2521                          "call at %L", name, &(args->expr->where));
2522           retval = FAILURE;
2523         }
2524       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2525         {
2526           /* Make sure we have either the target or pointer attribute.  */
2527           if (!arg_attr.target && !arg_attr.pointer)
2528             {
2529               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2530                              "a TARGET or an associated pointer",
2531                              args_sym->name,
2532                              sym->name, &(args->expr->where));
2533               retval = FAILURE;
2534             }
2535
2536           /* See if we have interoperable type and type param.  */
2537           if (verify_c_interop (arg_ts) == SUCCESS
2538               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2539             {
2540               if (args_sym->attr.target == 1)
2541                 {
2542                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2543                      has the target attribute and is interoperable.  */
2544                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2545                      allocatable variable that has the TARGET attribute and
2546                      is not an array of zero size.  */
2547                   if (args_sym->attr.allocatable == 1)
2548                     {
2549                       if (args_sym->attr.dimension != 0 
2550                           && (args_sym->as && args_sym->as->rank == 0))
2551                         {
2552                           gfc_error_now ("Allocatable variable '%s' used as a "
2553                                          "parameter to '%s' at %L must not be "
2554                                          "an array of zero size",
2555                                          args_sym->name, sym->name,
2556                                          &(args->expr->where));
2557                           retval = FAILURE;
2558                         }
2559                     }
2560                   else
2561                     {
2562                       /* A non-allocatable target variable with C
2563                          interoperable type and type parameters must be
2564                          interoperable.  */
2565                       if (args_sym && args_sym->attr.dimension)
2566                         {
2567                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2568                             {
2569                               gfc_error ("Assumed-shape array '%s' at %L "
2570                                          "cannot be an argument to the "
2571                                          "procedure '%s' because "
2572                                          "it is not C interoperable",
2573                                          args_sym->name,
2574                                          &(args->expr->where), sym->name);
2575                               retval = FAILURE;
2576                             }
2577                           else if (args_sym->as->type == AS_DEFERRED)
2578                             {
2579                               gfc_error ("Deferred-shape array '%s' at %L "
2580                                          "cannot be an argument to the "
2581                                          "procedure '%s' because "
2582                                          "it is not C interoperable",
2583                                          args_sym->name,
2584                                          &(args->expr->where), sym->name);
2585                               retval = FAILURE;
2586                             }
2587                         }
2588                               
2589                       /* Make sure it's not a character string.  Arrays of
2590                          any type should be ok if the variable is of a C
2591                          interoperable type.  */
2592                       if (arg_ts->type == BT_CHARACTER)
2593                         if (arg_ts->u.cl != NULL
2594                             && (arg_ts->u.cl->length == NULL
2595                                 || arg_ts->u.cl->length->expr_type
2596                                    != EXPR_CONSTANT
2597                                 || mpz_cmp_si
2598                                     (arg_ts->u.cl->length->value.integer, 1)
2599                                    != 0)
2600                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2601                           {
2602                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2603                                            "at %L must have a length of 1",
2604                                            args_sym->name, sym->name,
2605                                            &(args->expr->where));
2606                             retval = FAILURE;
2607                           }
2608                     }
2609                 }
2610               else if (arg_attr.pointer
2611                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2612                 {
2613                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2614                      scalar pointer.  */
2615                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2616                                  "associated scalar POINTER", args_sym->name,
2617                                  sym->name, &(args->expr->where));
2618                   retval = FAILURE;
2619                 }
2620             }
2621           else
2622             {
2623               /* The parameter is not required to be C interoperable.  If it
2624                  is not C interoperable, it must be a nonpolymorphic scalar
2625                  with no length type parameters.  It still must have either
2626                  the pointer or target attribute, and it can be
2627                  allocatable (but must be allocated when c_loc is called).  */
2628               if (args->expr->rank != 0 
2629                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2630                 {
2631                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2632                                  "scalar", args_sym->name, sym->name,
2633                                  &(args->expr->where));
2634                   retval = FAILURE;
2635                 }
2636               else if (arg_ts->type == BT_CHARACTER 
2637                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2638                 {
2639                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2640                                  "%L must have a length of 1",
2641                                  args_sym->name, sym->name,
2642                                  &(args->expr->where));
2643                   retval = FAILURE;
2644                 }
2645               else if (arg_ts->type == BT_CLASS)
2646                 {
2647                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2648                                  "polymorphic", args_sym->name, sym->name,
2649                                  &(args->expr->where));
2650                   retval = FAILURE;
2651                 }
2652             }
2653         }
2654       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2655         {
2656           if (args_sym->attr.flavor != FL_PROCEDURE)
2657             {
2658               /* TODO: Update this error message to allow for procedure
2659                  pointers once they are implemented.  */
2660               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2661                              "procedure",
2662                              args_sym->name, sym->name,
2663                              &(args->expr->where));
2664               retval = FAILURE;
2665             }
2666           else if (args_sym->attr.is_bind_c != 1)
2667             {
2668               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2669                              "BIND(C)",
2670                              args_sym->name, sym->name,
2671                              &(args->expr->where));
2672               retval = FAILURE;
2673             }
2674         }
2675       
2676       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2677       *new_sym = sym;
2678     }
2679   else
2680     {
2681       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2682                           "iso_c_binding function: '%s'!\n", sym->name);
2683     }
2684
2685   return retval;
2686 }
2687
2688
2689 /* Resolve a function call, which means resolving the arguments, then figuring
2690    out which entity the name refers to.  */
2691 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2692    to INTENT(OUT) or INTENT(INOUT).  */
2693
2694 static gfc_try
2695 resolve_function (gfc_expr *expr)
2696 {
2697   gfc_actual_arglist *arg;
2698   gfc_symbol *sym;
2699   const char *name;
2700   gfc_try t;
2701   int temp;
2702   procedure_type p = PROC_INTRINSIC;
2703   bool no_formal_args;
2704
2705   sym = NULL;
2706   if (expr->symtree)
2707     sym = expr->symtree->n.sym;
2708
2709   /* If this is a procedure pointer component, it has already been resolved.  */
2710   if (gfc_is_proc_ptr_comp (expr, NULL))
2711     return SUCCESS;
2712   
2713   if (sym && sym->attr.intrinsic
2714       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2715     return FAILURE;
2716
2717   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2718     {
2719       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2720       return FAILURE;
2721     }
2722
2723   /* If this ia a deferred TBP with an abstract interface (which may
2724      of course be referenced), expr->value.function.esym will be set.  */
2725   if (sym && sym->attr.abstract && !expr->value.function.esym)
2726     {
2727       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2728                  sym->name, &expr->where);
2729       return FAILURE;
2730     }
2731
2732   /* Switch off assumed size checking and do this again for certain kinds
2733      of procedure, once the procedure itself is resolved.  */
2734   need_full_assumed_size++;
2735
2736   if (expr->symtree && expr->symtree->n.sym)
2737     p = expr->symtree->n.sym->attr.proc;
2738
2739   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2740     inquiry_argument = true;
2741   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2742
2743   if (resolve_actual_arglist (expr->value.function.actual,
2744                               p, no_formal_args) == FAILURE)
2745     {
2746       inquiry_argument = false;
2747       return FAILURE;
2748     }
2749
2750   inquiry_argument = false;
2751  
2752   /* Need to setup the call to the correct c_associated, depending on
2753      the number of cptrs to user gives to compare.  */
2754   if (sym && sym->attr.is_iso_c == 1)
2755     {
2756       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2757           == FAILURE)
2758         return FAILURE;
2759       
2760       /* Get the symtree for the new symbol (resolved func).
2761          the old one will be freed later, when it's no longer used.  */
2762       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2763     }
2764   
2765   /* Resume assumed_size checking.  */
2766   need_full_assumed_size--;
2767
2768   /* If the procedure is external, check for usage.  */
2769   if (sym && is_external_proc (sym))
2770     resolve_global_procedure (sym, &expr->where,
2771                               &expr->value.function.actual, 0);
2772
2773   if (sym && sym->ts.type == BT_CHARACTER
2774       && sym->ts.u.cl
2775       && sym->ts.u.cl->length == NULL
2776       && !sym->attr.dummy
2777       && expr->value.function.esym == NULL
2778       && !sym->attr.contained)
2779     {
2780       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2781       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2782                  "be used at %L since it is not a dummy argument",
2783                  sym->name, &expr->where);
2784       return FAILURE;
2785     }
2786
2787   /* See if function is already resolved.  */
2788
2789   if (expr->value.function.name != NULL)
2790     {
2791       if (expr->ts.type == BT_UNKNOWN)
2792         expr->ts = sym->ts;
2793       t = SUCCESS;
2794     }
2795   else
2796     {
2797       /* Apply the rules of section 14.1.2.  */
2798
2799       switch (procedure_kind (sym))
2800         {
2801         case PTYPE_GENERIC:
2802           t = resolve_generic_f (expr);
2803           break;
2804
2805         case PTYPE_SPECIFIC:
2806           t = resolve_specific_f (expr);
2807           break;
2808
2809         case PTYPE_UNKNOWN:
2810           t = resolve_unknown_f (expr);
2811           break;
2812
2813         default:
2814           gfc_internal_error ("resolve_function(): bad function type");
2815         }
2816     }
2817
2818   /* If the expression is still a function (it might have simplified),
2819      then we check to see if we are calling an elemental function.  */
2820
2821   if (expr->expr_type != EXPR_FUNCTION)
2822     return t;
2823
2824   temp = need_full_assumed_size;
2825   need_full_assumed_size = 0;
2826
2827   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2828     return FAILURE;
2829
2830   if (omp_workshare_flag
2831       && expr->value.function.esym
2832       && ! gfc_elemental (expr->value.function.esym))
2833     {
2834       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2835                  "in WORKSHARE construct", expr->value.function.esym->name,
2836                  &expr->where);
2837       t = FAILURE;
2838     }
2839
2840 #define GENERIC_ID expr->value.function.isym->id
2841   else if (expr->value.function.actual != NULL
2842            && expr->value.function.isym != NULL
2843            && GENERIC_ID != GFC_ISYM_LBOUND
2844            && GENERIC_ID != GFC_ISYM_LEN
2845            && GENERIC_ID != GFC_ISYM_LOC
2846            && GENERIC_ID != GFC_ISYM_PRESENT)
2847     {
2848       /* Array intrinsics must also have the last upper bound of an
2849          assumed size array argument.  UBOUND and SIZE have to be
2850          excluded from the check if the second argument is anything
2851          than a constant.  */
2852
2853       for (arg = expr->value.function.actual; arg; arg = arg->next)
2854         {
2855           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2856               && arg->next != NULL && arg->next->expr)
2857             {
2858               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2859                 break;
2860
2861               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2862                 break;
2863
2864               if ((int)mpz_get_si (arg->next->expr->value.integer)
2865                         < arg->expr->rank)
2866                 break;
2867             }
2868
2869           if (arg->expr != NULL
2870               && arg->expr->rank > 0
2871               && resolve_assumed_size_actual (arg->expr))
2872             return FAILURE;
2873         }
2874     }
2875 #undef GENERIC_ID
2876
2877   need_full_assumed_size = temp;
2878   name = NULL;
2879
2880   if (!pure_function (expr, &name) && name)
2881     {
2882       if (forall_flag)
2883         {
2884           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2885                      "FORALL %s", name, &expr->where,
2886                      forall_flag == 2 ? "mask" : "block");
2887           t = FAILURE;
2888         }
2889       else if (gfc_pure (NULL))
2890         {
2891           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2892                      "procedure within a PURE procedure", name, &expr->where);
2893           t = FAILURE;
2894         }
2895     }
2896
2897   /* Functions without the RECURSIVE attribution are not allowed to
2898    * call themselves.  */
2899   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2900     {
2901       gfc_symbol *esym;
2902       esym = expr->value.function.esym;
2903
2904       if (is_illegal_recursion (esym, gfc_current_ns))
2905       {
2906         if (esym->attr.entry && esym->ns->entries)
2907           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2908                      " function '%s' is not RECURSIVE",
2909                      esym->name, &expr->where, esym->ns->entries->sym->name);
2910         else
2911           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2912                      " is not RECURSIVE", esym->name, &expr->where);
2913
2914         t = FAILURE;
2915       }
2916     }
2917
2918   /* Character lengths of use associated functions may contains references to
2919      symbols not referenced from the current program unit otherwise.  Make sure
2920      those symbols are marked as referenced.  */
2921
2922   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2923       && expr->value.function.esym->attr.use_assoc)
2924     {
2925       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2926     }
2927
2928   if (t == SUCCESS
2929         && !((expr->value.function.esym
2930                 && expr->value.function.esym->attr.elemental)
2931                         ||
2932              (expr->value.function.isym
2933                 && expr->value.function.isym->elemental)))
2934     find_noncopying_intrinsics (expr->value.function.esym,
2935                                 expr->value.function.actual);
2936
2937   /* Make sure that the expression has a typespec that works.  */
2938   if (expr->ts.type == BT_UNKNOWN)
2939     {
2940       if (expr->symtree->n.sym->result
2941             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2942             && !expr->symtree->n.sym->result->attr.proc_pointer)
2943         expr->ts = expr->symtree->n.sym->result->ts;
2944     }
2945
2946   return t;
2947 }
2948
2949
2950 /************* Subroutine resolution *************/
2951
2952 static void
2953 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2954 {
2955   if (gfc_pure (sym))
2956     return;
2957
2958   if (forall_flag)
2959     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2960                sym->name, &c->loc);
2961   else if (gfc_pure (NULL))
2962     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2963                &c->loc);
2964 }
2965
2966
2967 static match
2968 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2969 {
2970   gfc_symbol *s;
2971
2972   if (sym->attr.generic)
2973     {
2974       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2975       if (s != NULL)
2976         {
2977           c->resolved_sym = s;
2978           pure_subroutine (c, s);
2979           return MATCH_YES;
2980         }
2981
2982       /* TODO: Need to search for elemental references in generic interface.  */
2983     }
2984
2985   if (sym->attr.intrinsic)
2986     return gfc_intrinsic_sub_interface (c, 0);
2987
2988   return MATCH_NO;
2989 }
2990
2991
2992 static gfc_try
2993 resolve_generic_s (gfc_code *c)
2994 {
2995   gfc_symbol *sym;
2996   match m;
2997
2998   sym = c->symtree->n.sym;
2999
3000   for (;;)
3001     {
3002       m = resolve_generic_s0 (c, sym);
3003       if (m == MATCH_YES)
3004         return SUCCESS;
3005       else if (m == MATCH_ERROR)
3006         return FAILURE;
3007
3008 generic:
3009       if (sym->ns->parent == NULL)
3010         break;
3011       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3012
3013       if (sym == NULL)
3014         break;
3015       if (!generic_sym (sym))
3016         goto generic;
3017     }
3018
3019   /* Last ditch attempt.  See if the reference is to an intrinsic
3020      that possesses a matching interface.  14.1.2.4  */
3021   sym = c->symtree->n.sym;
3022
3023   if (!gfc_is_intrinsic (sym, 1, c->loc))
3024     {
3025       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3026                  sym->name, &c->loc);
3027       return FAILURE;
3028     }
3029
3030   m = gfc_intrinsic_sub_interface (c, 0);
3031   if (m == MATCH_YES)
3032     return SUCCESS;
3033   if (m == MATCH_NO)
3034     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3035                "intrinsic subroutine interface", sym->name, &c->loc);
3036
3037   return FAILURE;
3038 }
3039
3040
3041 /* Set the name and binding label of the subroutine symbol in the call
3042    expression represented by 'c' to include the type and kind of the
3043    second parameter.  This function is for resolving the appropriate
3044    version of c_f_pointer() and c_f_procpointer().  For example, a
3045    call to c_f_pointer() for a default integer pointer could have a
3046    name of c_f_pointer_i4.  If no second arg exists, which is an error
3047    for these two functions, it defaults to the generic symbol's name
3048    and binding label.  */
3049
3050 static void
3051 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3052                     char *name, char *binding_label)
3053 {
3054   gfc_expr *arg = NULL;
3055   char type;
3056   int kind;
3057
3058   /* The second arg of c_f_pointer and c_f_procpointer determines
3059      the type and kind for the procedure name.  */
3060   arg = c->ext.actual->next->expr;
3061
3062   if (arg != NULL)
3063     {
3064       /* Set up the name to have the given symbol's name,
3065          plus the type and kind.  */
3066       /* a derived type is marked with the type letter 'u' */
3067       if (arg->ts.type == BT_DERIVED)
3068         {
3069           type = 'd';
3070           kind = 0; /* set the kind as 0 for now */
3071         }
3072       else
3073         {
3074           type = gfc_type_letter (arg->ts.type);
3075           kind = arg->ts.kind;
3076         }
3077
3078       if (arg->ts.type == BT_CHARACTER)
3079         /* Kind info for character strings not needed.  */
3080         kind = 0;
3081
3082       sprintf (name, "%s_%c%d", sym->name, type, kind);
3083       /* Set up the binding label as the given symbol's label plus
3084          the type and kind.  */
3085       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3086     }
3087   else
3088     {
3089       /* If the second arg is missing, set the name and label as
3090          was, cause it should at least be found, and the missing
3091          arg error will be caught by compare_parameters().  */
3092       sprintf (name, "%s", sym->name);
3093       sprintf (binding_label, "%s", sym->binding_label);
3094     }
3095    
3096   return;
3097 }
3098
3099
3100 /* Resolve a generic version of the iso_c_binding procedure given
3101    (sym) to the specific one based on the type and kind of the
3102    argument(s).  Currently, this function resolves c_f_pointer() and
3103    c_f_procpointer based on the type and kind of the second argument
3104    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3105    Upon successfully exiting, c->resolved_sym will hold the resolved
3106    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3107    otherwise.  */
3108
3109 match
3110 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3111 {
3112   gfc_symbol *new_sym;
3113   /* this is fine, since we know the names won't use the max */
3114   char name[GFC_MAX_SYMBOL_LEN + 1];
3115   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3116   /* default to success; will override if find error */
3117   match m = MATCH_YES;
3118
3119   /* Make sure the actual arguments are in the necessary order (based on the 
3120      formal args) before resolving.  */
3121   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3122
3123   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3124       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3125     {
3126       set_name_and_label (c, sym, name, binding_label);
3127       
3128       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3129         {
3130           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3131             {
3132               /* Make sure we got a third arg if the second arg has non-zero
3133                  rank.  We must also check that the type and rank are
3134                  correct since we short-circuit this check in
3135                  gfc_procedure_use() (called above to sort actual args).  */
3136               if (c->ext.actual->next->expr->rank != 0)
3137                 {
3138                   if(c->ext.actual->next->next == NULL 
3139                      || c->ext.actual->next->next->expr == NULL)
3140                     {
3141                       m = MATCH_ERROR;
3142                       gfc_error ("Missing SHAPE parameter for call to %s "
3143                                  "at %L", sym->name, &(c->loc));
3144                     }
3145                   else if (c->ext.actual->next->next->expr->ts.type
3146                            != BT_INTEGER
3147                            || c->ext.actual->next->next->expr->rank != 1)
3148                     {
3149                       m = MATCH_ERROR;
3150                       gfc_error ("SHAPE parameter for call to %s at %L must "
3151                                  "be a rank 1 INTEGER array", sym->name,
3152                                  &(c->loc));
3153                     }
3154                 }
3155             }
3156         }
3157       
3158       if (m != MATCH_ERROR)
3159         {
3160           /* the 1 means to add the optional arg to formal list */
3161           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3162          
3163           /* for error reporting, say it's declared where the original was */
3164           new_sym->declared_at = sym->declared_at;
3165         }
3166     }
3167   else
3168     {
3169       /* no differences for c_loc or c_funloc */
3170       new_sym = sym;
3171     }
3172
3173   /* set the resolved symbol */
3174   if (m != MATCH_ERROR)
3175     c->resolved_sym = new_sym;
3176   else
3177     c->resolved_sym = sym;
3178   
3179   return m;
3180 }
3181
3182
3183 /* Resolve a subroutine call known to be specific.  */
3184
3185 static match
3186 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3187 {
3188   match m;
3189
3190   if(sym->attr.is_iso_c)
3191     {
3192       m = gfc_iso_c_sub_interface (c,sym);
3193       return m;
3194     }
3195   
3196   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3197     {
3198       if (sym->attr.dummy)
3199         {
3200           sym->attr.proc = PROC_DUMMY;
3201           goto found;
3202         }
3203
3204       sym->attr.proc = PROC_EXTERNAL;
3205       goto found;
3206     }
3207
3208   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3209     goto found;
3210
3211   if (sym->attr.intrinsic)
3212     {
3213       m = gfc_intrinsic_sub_interface (c, 1);
3214       if (m == MATCH_YES)
3215         return MATCH_YES;
3216       if (m == MATCH_NO)
3217         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3218                    "with an intrinsic", sym->name, &c->loc);
3219
3220       return MATCH_ERROR;
3221     }
3222
3223   return MATCH_NO;
3224
3225 found:
3226   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3227
3228   c->resolved_sym = sym;
3229   pure_subroutine (c, sym);
3230
3231   return MATCH_YES;
3232 }
3233
3234
3235 static gfc_try
3236 resolve_specific_s (gfc_code *c)
3237 {
3238   gfc_symbol *sym;
3239   match m;
3240
3241   sym = c->symtree->n.sym;
3242
3243   for (;;)
3244     {
3245       m = resolve_specific_s0 (c, sym);
3246       if (m == MATCH_YES)
3247         return SUCCESS;
3248       if (m == MATCH_ERROR)
3249         return FAILURE;
3250
3251       if (sym->ns->parent == NULL)
3252         break;
3253
3254       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3255
3256       if (sym == NULL)
3257         break;
3258     }
3259
3260   sym = c->symtree->n.sym;
3261   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3262              sym->name, &c->loc);
3263
3264   return FAILURE;
3265 }
3266
3267
3268 /* Resolve a subroutine call not known to be generic nor specific.  */
3269
3270 static gfc_try
3271 resolve_unknown_s (gfc_code *c)
3272 {
3273   gfc_symbol *sym;
3274
3275   sym = c->symtree->n.sym;
3276
3277   if (sym->attr.dummy)
3278     {
3279       sym->attr.proc = PROC_DUMMY;
3280       goto found;
3281     }
3282
3283   /* See if we have an intrinsic function reference.  */
3284
3285   if (gfc_is_intrinsic (sym, 1, c->loc))
3286     {
3287       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3288         return SUCCESS;
3289       return FAILURE;
3290     }
3291
3292   /* The reference is to an external name.  */
3293
3294 found:
3295   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3296
3297   c->resolved_sym = sym;
3298
3299   pure_subroutine (c, sym);
3300
3301   return SUCCESS;
3302 }
3303
3304
3305 /* Resolve a subroutine call.  Although it was tempting to use the same code
3306    for functions, subroutines and functions are stored differently and this
3307    makes things awkward.  */
3308
3309 static gfc_try
3310 resolve_call (gfc_code *c)
3311 {
3312   gfc_try t;
3313   procedure_type ptype = PROC_INTRINSIC;
3314   gfc_symbol *csym, *sym;
3315   bool no_formal_args;
3316
3317   csym = c->symtree ? c->symtree->n.sym : NULL;
3318
3319   if (csym && csym->ts.type != BT_UNKNOWN)
3320     {
3321       gfc_error ("'%s' at %L has a type, which is not consistent with "
3322                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3323       return FAILURE;
3324     }
3325
3326   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3327     {
3328       gfc_symtree *st;
3329       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3330       sym = st ? st->n.sym : NULL;
3331       if (sym && csym != sym
3332               && sym->ns == gfc_current_ns
3333               && sym->attr.flavor == FL_PROCEDURE
3334               && sym->attr.contained)
3335         {
3336           sym->refs++;
3337           if (csym->attr.generic)
3338             c->symtree->n.sym = sym;
3339           else
3340             c->symtree = st;
3341           csym = c->symtree->n.sym;
3342         }
3343     }
3344
3345   /* If this ia a deferred TBP with an abstract interface
3346      (which may of course be referenced), c->expr1 will be set.  */
3347   if (csym && csym->attr.abstract && !c->expr1)
3348     {
3349       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3350                  csym->name, &c->loc);
3351       return FAILURE;
3352     }
3353
3354   /* Subroutines without the RECURSIVE attribution are not allowed to
3355    * call themselves.  */
3356   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3357     {
3358       if (csym->attr.entry && csym->ns->entries)
3359         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3360                    " subroutine '%s' is not RECURSIVE",
3361                    csym->name, &c->loc, csym->ns->entries->sym->name);
3362       else
3363         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3364                    " is not RECURSIVE", csym->name, &c->loc);
3365
3366       t = FAILURE;
3367     }
3368
3369   /* Switch off assumed size checking and do this again for certain kinds
3370      of procedure, once the procedure itself is resolved.  */
3371   need_full_assumed_size++;
3372
3373   if (csym)
3374     ptype = csym->attr.proc;
3375
3376   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3377   if (resolve_actual_arglist (c->ext.actual, ptype,
3378                               no_formal_args) == FAILURE)
3379     return FAILURE;
3380
3381   /* Resume assumed_size checking.  */
3382   need_full_assumed_size--;
3383
3384   /* If external, check for usage.  */
3385   if (csym && is_external_proc (csym))
3386     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3387
3388   t = SUCCESS;
3389   if (c->resolved_sym == NULL)
3390     {
3391       c->resolved_isym = NULL;
3392       switch (procedure_kind (csym))
3393         {
3394         case PTYPE_GENERIC:
3395           t = resolve_generic_s (c);
3396           break;
3397
3398         case PTYPE_SPECIFIC:
3399           t = resolve_specific_s (c);
3400           break;
3401
3402         case PTYPE_UNKNOWN:
3403           t = resolve_unknown_s (c);
3404           break;
3405
3406         default:
3407           gfc_internal_error ("resolve_subroutine(): bad function type");
3408         }
3409     }
3410
3411   /* Some checks of elemental subroutine actual arguments.  */
3412   if (resolve_elemental_actual (NULL, c) == FAILURE)
3413     return FAILURE;
3414
3415   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3416     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3417   return t;
3418 }
3419
3420
3421 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3422    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3423    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3424    if their shapes do not match.  If either op1->shape or op2->shape is
3425    NULL, return SUCCESS.  */
3426
3427 static gfc_try
3428 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3429 {
3430   gfc_try t;
3431   int i;
3432
3433   t = SUCCESS;
3434
3435   if (op1->shape != NULL && op2->shape != NULL)
3436     {
3437       for (i = 0; i < op1->rank; i++)
3438         {
3439           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3440            {
3441              gfc_error ("Shapes for operands at %L and %L are not conformable",
3442                          &op1->where, &op2->where);
3443              t = FAILURE;
3444              break;
3445            }
3446         }
3447     }
3448
3449   return t;
3450 }
3451
3452
3453 /* Resolve an operator expression node.  This can involve replacing the
3454    operation with a user defined function call.  */
3455
3456 static gfc_try
3457 resolve_operator (gfc_expr *e)
3458 {
3459   gfc_expr *op1, *op2;
3460   char msg[200];
3461   bool dual_locus_error;
3462   gfc_try t;
3463
3464   /* Resolve all subnodes-- give them types.  */
3465
3466   switch (e->value.op.op)
3467     {
3468     default:
3469       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3470         return FAILURE;
3471
3472     /* Fall through...  */
3473
3474     case INTRINSIC_NOT:
3475     case INTRINSIC_UPLUS:
3476     case INTRINSIC_UMINUS:
3477     case INTRINSIC_PARENTHESES:
3478       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3479         return FAILURE;
3480       break;
3481     }
3482
3483   /* Typecheck the new node.  */
3484
3485   op1 = e->value.op.op1;
3486   op2 = e->value.op.op2;
3487   dual_locus_error = false;
3488
3489   if ((op1 && op1->expr_type == EXPR_NULL)
3490       || (op2 && op2->expr_type == EXPR_NULL))
3491     {
3492       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3493       goto bad_op;
3494     }
3495
3496   switch (e->value.op.op)
3497     {
3498     case INTRINSIC_UPLUS:
3499     case INTRINSIC_UMINUS:
3500       if (op1->ts.type == BT_INTEGER
3501           || op1->ts.type == BT_REAL
3502           || op1->ts.type == BT_COMPLEX)
3503         {
3504           e->ts = op1->ts;
3505           break;
3506         }
3507
3508       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3509                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3510       goto bad_op;
3511
3512     case INTRINSIC_PLUS:
3513     case INTRINSIC_MINUS:
3514     case INTRINSIC_TIMES:
3515     case INTRINSIC_DIVIDE:
3516     case INTRINSIC_POWER:
3517       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3518         {
3519           gfc_type_convert_binary (e, 1);
3520           break;
3521         }
3522
3523       sprintf (msg,
3524                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3525                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3526                gfc_typename (&op2->ts));
3527       goto bad_op;
3528
3529     case INTRINSIC_CONCAT:
3530       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3531           && op1->ts.kind == op2->ts.kind)
3532         {
3533           e->ts.type = BT_CHARACTER;
3534           e->ts.kind = op1->ts.kind;
3535           break;
3536         }
3537
3538       sprintf (msg,
3539                _("Operands of string concatenation operator at %%L are %s/%s"),
3540                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3541       goto bad_op;
3542
3543     case INTRINSIC_AND:
3544     case INTRINSIC_OR:
3545     case INTRINSIC_EQV:
3546     case INTRINSIC_NEQV:
3547       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3548         {
3549           e->ts.type = BT_LOGICAL;
3550           e->ts.kind = gfc_kind_max (op1, op2);
3551           if (op1->ts.kind < e->ts.kind)
3552             gfc_convert_type (op1, &e->ts, 2);
3553           else if (op2->ts.kind < e->ts.kind)
3554             gfc_convert_type (op2, &e->ts, 2);
3555           break;
3556         }
3557
3558       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3559                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3560                gfc_typename (&op2->ts));
3561
3562       goto bad_op;
3563
3564     case INTRINSIC_NOT:
3565       if (op1->ts.type == BT_LOGICAL)
3566         {
3567           e->ts.type = BT_LOGICAL;
3568           e->ts.kind = op1->ts.kind;
3569           break;
3570         }
3571
3572       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3573                gfc_typename (&op1->ts));
3574       goto bad_op;
3575
3576     case INTRINSIC_GT:
3577     case INTRINSIC_GT_OS:
3578     case INTRINSIC_GE:
3579     case INTRINSIC_GE_OS:
3580     case INTRINSIC_LT:
3581     case INTRINSIC_LT_OS:
3582     case INTRINSIC_LE:
3583     case INTRINSIC_LE_OS:
3584       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3585         {
3586           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3587           goto bad_op;
3588         }
3589
3590       /* Fall through...  */
3591
3592     case INTRINSIC_EQ:
3593     case INTRINSIC_EQ_OS:
3594     case INTRINSIC_NE:
3595     case INTRINSIC_NE_OS:
3596       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3597           && op1->ts.kind == op2->ts.kind)
3598         {
3599           e->ts.type = BT_LOGICAL;
3600           e->ts.kind = gfc_default_logical_kind;
3601           break;
3602         }
3603
3604       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3605         {
3606           gfc_type_convert_binary (e, 1);
3607
3608           e->ts.type = BT_LOGICAL;
3609           e->ts.kind = gfc_default_logical_kind;
3610           break;
3611         }
3612
3613       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3614         sprintf (msg,
3615                  _("Logicals at %%L must be compared with %s instead of %s"),
3616                  (e->value.op.op == INTRINSIC_EQ 
3617                   || e->value.op.op == INTRINSIC_EQ_OS)
3618                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3619       else
3620         sprintf (msg,
3621                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3622                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3623                  gfc_typename (&op2->ts));
3624
3625       goto bad_op;
3626
3627     case INTRINSIC_USER:
3628       if (e->value.op.uop->op == NULL)
3629         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3630       else if (op2 == NULL)
3631         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3632                  e->value.op.uop->name, gfc_typename (&op1->ts));
3633       else
3634         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3635                  e->value.op.uop->name, gfc_typename (&op1->ts),
3636                  gfc_typename (&op2->ts));
3637
3638       goto bad_op;
3639
3640     case INTRINSIC_PARENTHESES:
3641       e->ts = op1->ts;
3642       if (e->ts.type == BT_CHARACTER)
3643         e->ts.u.cl = op1->ts.u.cl;
3644       break;
3645
3646     default:
3647       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3648     }
3649
3650   /* Deal with arrayness of an operand through an operator.  */
3651
3652   t = SUCCESS;
3653
3654   switch (e->value.op.op)
3655     {
3656     case INTRINSIC_PLUS:
3657     case INTRINSIC_MINUS:
3658     case INTRINSIC_TIMES:
3659     case INTRINSIC_DIVIDE:
3660     case INTRINSIC_POWER:
3661     case INTRINSIC_CONCAT:
3662     case INTRINSIC_AND:
3663     case INTRINSIC_OR:
3664     case INTRINSIC_EQV:
3665     case INTRINSIC_NEQV:
3666     case INTRINSIC_EQ:
3667     case INTRINSIC_EQ_OS:
3668     case INTRINSIC_NE:
3669     case INTRINSIC_NE_OS:
3670     case INTRINSIC_GT:
3671     case INTRINSIC_GT_OS:
3672     case INTRINSIC_GE:
3673     case INTRINSIC_GE_OS:
3674     case INTRINSIC_LT:
3675     case INTRINSIC_LT_OS:
3676     case INTRINSIC_LE:
3677     case INTRINSIC_LE_OS:
3678
3679       if (op1->rank == 0 && op2->rank == 0)
3680         e->rank = 0;
3681
3682       if (op1->rank == 0 && op2->rank != 0)
3683         {
3684           e->rank = op2->rank;
3685
3686           if (e->shape == NULL)
3687             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3688         }
3689
3690       if (op1->rank != 0 && op2->rank == 0)
3691         {
3692           e->rank = op1->rank;
3693
3694           if (e->shape == NULL)
3695             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3696         }
3697
3698       if (op1->rank != 0 && op2->rank != 0)
3699         {
3700           if (op1->rank == op2->rank)
3701             {
3702               e->rank = op1->rank;
3703               if (e->shape == NULL)
3704                 {
3705                   t = compare_shapes (op1, op2);
3706                   if (t == FAILURE)
3707                     e->shape = NULL;
3708                   else
3709                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3710                 }
3711             }
3712           else
3713             {
3714               /* Allow higher level expressions to work.  */
3715               e->rank = 0;
3716
3717               /* Try user-defined operators, and otherwise throw an error.  */
3718               dual_locus_error = true;
3719               sprintf (msg,
3720                        _("Inconsistent ranks for operator at %%L and %%L"));
3721               goto bad_op;
3722             }
3723         }
3724
3725       break;
3726
3727     case INTRINSIC_PARENTHESES:
3728     case INTRINSIC_NOT:
3729     case INTRINSIC_UPLUS:
3730     case INTRINSIC_UMINUS:
3731       /* Simply copy arrayness attribute */
3732       e->rank = op1->rank;
3733
3734       if (e->shape == NULL)
3735         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3736
3737       break;
3738
3739     default:
3740       break;
3741     }
3742
3743   /* Attempt to simplify the expression.  */
3744   if (t == SUCCESS)
3745     {
3746       t = gfc_simplify_expr (e, 0);
3747       /* Some calls do not succeed in simplification and return FAILURE
3748          even though there is no error; e.g. variable references to
3749          PARAMETER arrays.  */
3750       if (!gfc_is_constant_expr (e))
3751         t = SUCCESS;
3752     }
3753   return t;
3754
3755 bad_op:
3756
3757   {
3758     bool real_error;
3759     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3760       return SUCCESS;
3761
3762     if (real_error)
3763       return FAILURE;
3764   }
3765
3766   if (dual_locus_error)
3767     gfc_error (msg, &op1->where, &op2->where);
3768   else
3769     gfc_error (msg, &e->where);
3770
3771   return FAILURE;
3772 }
3773
3774
3775 /************** Array resolution subroutines **************/
3776
3777 typedef enum
3778 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3779 comparison;
3780
3781 /* Compare two integer expressions.  */
3782
3783 static comparison
3784 compare_bound (gfc_expr *a, gfc_expr *b)
3785 {
3786   int i;
3787
3788   if (a == NULL || a->expr_type != EXPR_CONSTANT
3789       || b == NULL || b->expr_type != EXPR_CONSTANT)
3790     return CMP_UNKNOWN;
3791
3792   /* If either of the types isn't INTEGER, we must have
3793      raised an error earlier.  */
3794
3795   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3796     return CMP_UNKNOWN;
3797
3798   i = mpz_cmp (a->value.integer, b->value.integer);
3799
3800   if (i < 0)
3801     return CMP_LT;
3802   if (i > 0)
3803     return CMP_GT;
3804   return CMP_EQ;
3805 }
3806
3807
3808 /* Compare an integer expression with an integer.  */
3809
3810 static comparison
3811 compare_bound_int (gfc_expr *a, int b)
3812 {
3813   int i;
3814
3815   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3816     return CMP_UNKNOWN;
3817
3818   if (a->ts.type != BT_INTEGER)
3819     gfc_internal_error ("compare_bound_int(): Bad expression");
3820
3821   i = mpz_cmp_si (a->value.integer, b);
3822
3823   if (i < 0)
3824     return CMP_LT;
3825   if (i > 0)
3826     return CMP_GT;
3827   return CMP_EQ;
3828 }
3829
3830
3831 /* Compare an integer expression with a mpz_t.  */
3832
3833 static comparison
3834 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3835 {
3836   int i;
3837
3838   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3839     return CMP_UNKNOWN;
3840
3841   if (a->ts.type != BT_INTEGER)
3842     gfc_internal_error ("compare_bound_int(): Bad expression");
3843
3844   i = mpz_cmp (a->value.integer, b);
3845
3846   if (i < 0)
3847     return CMP_LT;
3848   if (i > 0)
3849     return CMP_GT;
3850   return CMP_EQ;
3851 }
3852
3853
3854 /* Compute the last value of a sequence given by a triplet.  
3855    Return 0 if it wasn't able to compute the last value, or if the
3856    sequence if empty, and 1 otherwise.  */
3857
3858 static int
3859 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3860                                 gfc_expr *stride, mpz_t last)
3861 {
3862   mpz_t rem;
3863
3864   if (start == NULL || start->expr_type != EXPR_CONSTANT
3865       || end == NULL || end->expr_type != EXPR_CONSTANT
3866       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3867     return 0;
3868
3869   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3870       || (stride != NULL && stride->ts.type != BT_INTEGER))
3871     return 0;
3872
3873   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3874     {
3875       if (compare_bound (start, end) == CMP_GT)
3876         return 0;
3877       mpz_set (last, end->value.integer);
3878       return 1;
3879     }
3880
3881   if (compare_bound_int (stride, 0) == CMP_GT)
3882     {
3883       /* Stride is positive */
3884       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3885         return 0;
3886     }
3887   else
3888     {
3889       /* Stride is negative */
3890       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3891         return 0;
3892     }
3893
3894   mpz_init (rem);
3895   mpz_sub (rem, end->value.integer, start->value.integer);
3896   mpz_tdiv_r (rem, rem, stride->value.integer);
3897   mpz_sub (last, end->value.integer, rem);
3898   mpz_clear (rem);
3899
3900   return 1;
3901 }
3902
3903
3904 /* Compare a single dimension of an array reference to the array
3905    specification.  */
3906
3907 static gfc_try
3908 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3909 {
3910   mpz_t last_value;
3911
3912   if (ar->dimen_type[i] == DIMEN_STAR)
3913     {
3914       gcc_assert (ar->stride[i] == NULL);
3915       /* This implies [*] as [*:] and [*:3] are not possible.  */
3916       if (ar->start[i] == NULL)
3917         {
3918           gcc_assert (ar->end[i] == NULL);
3919           return SUCCESS;
3920         }
3921     }
3922
3923 /* Given start, end and stride values, calculate the minimum and
3924    maximum referenced indexes.  */
3925
3926   switch (ar->dimen_type[i])
3927     {
3928     case DIMEN_VECTOR:
3929       break;
3930
3931     case DIMEN_STAR:
3932     case DIMEN_ELEMENT:
3933       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3934         {
3935           if (i < as->rank)
3936             gfc_warning ("Array reference at %L is out of bounds "
3937                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
3938                          mpz_get_si (ar->start[i]->value.integer),
3939                          mpz_get_si (as->lower[i]->value.integer), i+1);
3940           else
3941             gfc_warning ("Array reference at %L is out of bounds "
3942                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
3943                          mpz_get_si (ar->start[i]->value.integer),
3944                          mpz_get_si (as->lower[i]->value.integer),
3945                          i + 1 - as->rank);
3946           return SUCCESS;
3947         }
3948       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3949         {
3950           if (i < as->rank)
3951             gfc_warning ("Array reference at %L is out of bounds "
3952                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
3953                          mpz_get_si (ar->start[i]->value.integer),
3954                          mpz_get_si (as->upper[i]->value.integer), i+1);
3955           else
3956             gfc_warning ("Array reference at %L is out of bounds "
3957                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
3958                          mpz_get_si (ar->start[i]->value.integer),
3959                          mpz_get_si (as->upper[i]->value.integer),
3960                          i + 1 - as->rank);
3961           return SUCCESS;
3962         }
3963
3964       break;
3965
3966     case DIMEN_RANGE:
3967       {
3968 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3969 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3970
3971         comparison comp_start_end = compare_bound (AR_START, AR_END);
3972
3973         /* Check for zero stride, which is not allowed.  */
3974         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3975           {
3976             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3977             return FAILURE;
3978           }
3979
3980         /* if start == len || (stride > 0 && start < len)
3981                            || (stride < 0 && start > len),
3982            then the array section contains at least one element.  In this
3983            case, there is an out-of-bounds access if
3984            (start < lower || start > upper).  */
3985         if (compare_bound (AR_START, AR_END) == CMP_EQ
3986             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3987                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3988             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3989                 && comp_start_end == CMP_GT))
3990           {
3991             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3992               {
3993                 gfc_warning ("Lower array reference at %L is out of bounds "
3994                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3995                        mpz_get_si (AR_START->value.integer),
3996                        mpz_get_si (as->lower[i]->value.integer), i+1);
3997                 return SUCCESS;
3998               }
3999             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4000               {
4001                 gfc_warning ("Lower array reference at %L is out of bounds "
4002                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4003                        mpz_get_si (AR_START->value.integer),
4004                        mpz_get_si (as->upper[i]->value.integer), i+1);
4005                 return SUCCESS;
4006               }
4007           }
4008
4009         /* If we can compute the highest index of the array section,
4010            then it also has to be between lower and upper.  */
4011         mpz_init (last_value);
4012         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4013                                             last_value))
4014           {
4015             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4016               {
4017                 gfc_warning ("Upper array reference at %L is out of bounds "
4018                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4019                        mpz_get_si (last_value),
4020                        mpz_get_si (as->lower[i]->value.integer), i+1);
4021                 mpz_clear (last_value);
4022                 return SUCCESS;
4023               }
4024             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4025               {
4026                 gfc_warning ("Upper array reference at %L is out of bounds "
4027                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4028                        mpz_get_si (last_value),
4029                        mpz_get_si (as->upper[i]->value.integer), i+1);
4030                 mpz_clear (last_value);
4031                 return SUCCESS;
4032               }
4033           }
4034         mpz_clear (last_value);
4035
4036 #undef AR_START
4037 #undef AR_END
4038       }
4039       break;
4040
4041     default:
4042       gfc_internal_error ("check_dimension(): Bad array reference");
4043     }
4044
4045   return SUCCESS;
4046 }
4047
4048
4049 /* Compare an array reference with an array specification.  */
4050
4051 static gfc_try
4052 compare_spec_to_ref (gfc_array_ref *ar)
4053 {
4054   gfc_array_spec *as;
4055   int i;
4056
4057   as = ar->as;
4058   i = as->rank - 1;
4059   /* TODO: Full array sections are only allowed as actual parameters.  */
4060   if (as->type == AS_ASSUMED_SIZE
4061       && (/*ar->type == AR_FULL
4062           ||*/ (ar->type == AR_SECTION
4063               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4064     {
4065       gfc_error ("Rightmost upper bound of assumed size array section "
4066                  "not specified at %L", &ar->where);
4067       return FAILURE;
4068     }
4069
4070   if (ar->type == AR_FULL)
4071     return SUCCESS;
4072
4073   if (as->rank != ar->dimen)
4074     {
4075       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4076                  &ar->where, ar->dimen, as->rank);
4077       return FAILURE;
4078     }
4079
4080   /* ar->codimen == 0 is a local array.  */
4081   if (as->corank != ar->codimen && ar->codimen != 0)
4082     {
4083       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4084                  &ar->where, ar->codimen, as->corank);
4085       return FAILURE;
4086     }
4087
4088   for (i = 0; i < as->rank; i++)
4089     if (check_dimension (i, ar, as) == FAILURE)
4090       return FAILURE;
4091
4092   /* Local access has no coarray spec.  */
4093   if (ar->codimen != 0)
4094     for (i = as->rank; i < as->rank + as->corank; i++)
4095       {
4096         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
4097           {
4098             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4099                        i + 1 - as->rank, &ar->where);
4100             return FAILURE;
4101           }
4102         if (check_dimension (i, ar, as) == FAILURE)
4103           return FAILURE;
4104       }
4105
4106   return SUCCESS;
4107 }
4108
4109
4110 /* Resolve one part of an array index.  */
4111
4112 static gfc_try
4113 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4114                      int force_index_integer_kind)
4115 {
4116   gfc_typespec ts;
4117
4118   if (index == NULL)
4119     return SUCCESS;
4120
4121   if (gfc_resolve_expr (index) == FAILURE)
4122     return FAILURE;
4123
4124   if (check_scalar && index->rank != 0)
4125     {
4126       gfc_error ("Array index at %L must be scalar", &index->where);
4127       return FAILURE;
4128     }
4129
4130   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4131     {
4132       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4133                  &index->where, gfc_basic_typename (index->ts.type));
4134       return FAILURE;
4135     }
4136
4137   if (index->ts.type == BT_REAL)
4138     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4139                         &index->where) == FAILURE)
4140       return FAILURE;
4141
4142   if ((index->ts.kind != gfc_index_integer_kind
4143        && force_index_integer_kind)
4144       || index->ts.type != BT_INTEGER)
4145     {
4146       gfc_clear_ts (&ts);
4147       ts.type = BT_INTEGER;
4148       ts.kind = gfc_index_integer_kind;
4149
4150       gfc_convert_type_warn (index, &ts, 2, 0);
4151     }
4152
4153   return SUCCESS;
4154 }
4155
4156 /* Resolve one part of an array index.  */
4157
4158 gfc_try
4159 gfc_resolve_index (gfc_expr *index, int check_scalar)
4160 {
4161   return gfc_resolve_index_1 (index, check_scalar, 1);
4162 }
4163
4164 /* Resolve a dim argument to an intrinsic function.  */
4165
4166 gfc_try
4167 gfc_resolve_dim_arg (gfc_expr *dim)
4168 {
4169   if (dim == NULL)
4170     return SUCCESS;
4171
4172   if (gfc_resolve_expr (dim) == FAILURE)
4173     return FAILURE;
4174
4175   if (dim->rank != 0)
4176     {
4177       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4178       return FAILURE;
4179
4180     }
4181
4182   if (dim->ts.type != BT_INTEGER)
4183     {
4184       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4185       return FAILURE;
4186     }
4187
4188   if (dim->ts.kind != gfc_index_integer_kind)
4189     {
4190       gfc_typespec ts;
4191
4192       gfc_clear_ts (&ts);
4193       ts.type = BT_INTEGER;
4194       ts.kind = gfc_index_integer_kind;
4195
4196       gfc_convert_type_warn (dim, &ts, 2, 0);
4197     }
4198
4199   return SUCCESS;
4200 }
4201
4202 /* Given an expression that contains array references, update those array
4203    references to point to the right array specifications.  While this is
4204    filled in during matching, this information is difficult to save and load
4205    in a module, so we take care of it here.
4206
4207    The idea here is that the original array reference comes from the
4208    base symbol.  We traverse the list of reference structures, setting
4209    the stored reference to references.  Component references can
4210    provide an additional array specification.  */
4211
4212 static void
4213 find_array_spec (gfc_expr *e)
4214 {
4215   gfc_array_spec *as;
4216   gfc_component *c;
4217   gfc_symbol *derived;
4218   gfc_ref *ref;
4219
4220   if (e->symtree->n.sym->ts.type == BT_CLASS)
4221     as = CLASS_DATA (e->symtree->n.sym)->as;
4222   else
4223     as = e->symtree->n.sym->as;
4224   derived = NULL;
4225
4226   for (ref = e->ref; ref; ref = ref->next)
4227     switch (ref->type)
4228       {
4229       case REF_ARRAY:
4230         if (as == NULL)
4231           gfc_internal_error ("find_array_spec(): Missing spec");
4232
4233         ref->u.ar.as = as;
4234         as = NULL;
4235         break;
4236
4237       case REF_COMPONENT:
4238         if (derived == NULL)
4239           derived = e->symtree->n.sym->ts.u.derived;
4240
4241         if (derived->attr.is_class)
4242           derived = derived->components->ts.u.derived;
4243
4244         c = derived->components;
4245
4246         for (; c; c = c->next)
4247           if (c == ref->u.c.component)
4248             {
4249               /* Track the sequence of component references.  */
4250               if (c->ts.type == BT_DERIVED)
4251                 derived = c->ts.u.derived;
4252               break;
4253             }
4254
4255         if (c == NULL)
4256           gfc_internal_error ("find_array_spec(): Component not found");
4257
4258         if (c->attr.dimension)
4259           {
4260             if (as != NULL)
4261               gfc_internal_error ("find_array_spec(): unused as(1)");
4262             as = c->as;
4263           }
4264
4265         break;
4266
4267       case REF_SUBSTRING:
4268         break;
4269       }
4270
4271   if (as != NULL)
4272     gfc_internal_error ("find_array_spec(): unused as(2)");
4273 }
4274
4275
4276 /* Resolve an array reference.  */
4277
4278 static gfc_try
4279 resolve_array_ref (gfc_array_ref *ar)
4280 {
4281   int i, check_scalar;
4282   gfc_expr *e;
4283
4284   for (i = 0; i < ar->dimen + ar->codimen; i++)
4285     {
4286       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4287
4288       /* Do not force gfc_index_integer_kind for the start.  We can
4289          do fine with any integer kind.  This avoids temporary arrays
4290          created for indexing with a vector.  */
4291       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4292         return FAILURE;
4293       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4294         return FAILURE;
4295       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4296         return FAILURE;
4297
4298       e = ar->start[i];
4299
4300       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4301         switch (e->rank)
4302           {
4303           case 0:
4304             ar->dimen_type[i] = DIMEN_ELEMENT;
4305             break;
4306
4307           case 1:
4308             ar->dimen_type[i] = DIMEN_VECTOR;
4309             if (e->expr_type == EXPR_VARIABLE
4310                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4311               ar->start[i] = gfc_get_parentheses (e);
4312             break;
4313
4314           default:
4315             gfc_error ("Array index at %L is an array of rank %d",
4316                        &ar->c_where[i], e->rank);
4317             return FAILURE;
4318           }
4319     }
4320
4321   if (ar->type == AR_FULL && ar->as->rank == 0)
4322     ar->type = AR_ELEMENT;
4323
4324   /* If the reference type is unknown, figure out what kind it is.  */
4325
4326   if (ar->type == AR_UNKNOWN)
4327     {
4328       ar->type = AR_ELEMENT;
4329       for (i = 0; i < ar->dimen; i++)
4330         if (ar->dimen_type[i] == DIMEN_RANGE
4331             || ar->dimen_type[i] == DIMEN_VECTOR)
4332           {
4333             ar->type = AR_SECTION;
4334             break;
4335           }
4336     }
4337
4338   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4339     return FAILURE;
4340
4341   return SUCCESS;
4342 }
4343
4344
4345 static gfc_try
4346 resolve_substring (gfc_ref *ref)
4347 {
4348   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4349
4350   if (ref->u.ss.start != NULL)
4351     {
4352       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4353         return FAILURE;
4354
4355       if (ref->u.ss.start->ts.type != BT_INTEGER)
4356         {
4357           gfc_error ("Substring start index at %L must be of type INTEGER",
4358                      &ref->u.ss.start->where);
4359           return FAILURE;
4360         }
4361
4362       if (ref->u.ss.start->rank != 0)
4363         {
4364           gfc_error ("Substring start index at %L must be scalar",
4365                      &ref->u.ss.start->where);
4366           return FAILURE;
4367         }
4368
4369       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4370           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4371               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4372         {
4373           gfc_error ("Substring start index at %L is less than one",
4374                      &ref->u.ss.start->where);
4375           return FAILURE;
4376         }
4377     }
4378
4379   if (ref->u.ss.end != NULL)
4380     {
4381       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4382         return FAILURE;
4383
4384       if (ref->u.ss.end->ts.type != BT_INTEGER)
4385         {
4386           gfc_error ("Substring end index at %L must be of type INTEGER",
4387                      &ref->u.ss.end->where);
4388           return FAILURE;
4389         }
4390
4391       if (ref->u.ss.end->rank != 0)
4392         {
4393           gfc_error ("Substring end index at %L must be scalar",
4394                      &ref->u.ss.end->where);
4395           return FAILURE;
4396         }
4397
4398       if (ref->u.ss.length != NULL
4399           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4400           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4401               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4402         {
4403           gfc_error ("Substring end index at %L exceeds the string length",
4404                      &ref->u.ss.start->where);
4405           return FAILURE;
4406         }
4407
4408       if (compare_bound_mpz_t (ref->u.ss.end,
4409                                gfc_integer_kinds[k].huge) == CMP_GT
4410           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4411               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4412         {
4413           gfc_error ("Substring end index at %L is too large",
4414                      &ref->u.ss.end->where);
4415           return FAILURE;
4416         }
4417     }
4418
4419   return SUCCESS;
4420 }
4421
4422
4423 /* This function supplies missing substring charlens.  */
4424
4425 void
4426 gfc_resolve_substring_charlen (gfc_expr *e)
4427 {
4428   gfc_ref *char_ref;
4429   gfc_expr *start, *end;
4430
4431   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4432     if (char_ref->type == REF_SUBSTRING)
4433       break;
4434
4435   if (!char_ref)
4436     return;
4437
4438   gcc_assert (char_ref->next == NULL);
4439
4440   if (e->ts.u.cl)
4441     {
4442       if (e->ts.u.cl->length)
4443         gfc_free_expr (e->ts.u.cl->length);
4444       else if (e->expr_type == EXPR_VARIABLE
4445                  && e->symtree->n.sym->attr.dummy)
4446         return;
4447     }
4448
4449   e->ts.type = BT_CHARACTER;
4450   e->ts.kind = gfc_default_character_kind;
4451
4452   if (!e->ts.u.cl)
4453     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4454
4455   if (char_ref->u.ss.start)
4456     start = gfc_copy_expr (char_ref->u.ss.start);
4457   else
4458     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4459
4460   if (char_ref->u.ss.end)
4461     end = gfc_copy_expr (char_ref->u.ss.end);
4462   else if (e->expr_type == EXPR_VARIABLE)
4463     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4464   else
4465     end = NULL;
4466
4467   if (!start || !end)
4468     return;
4469
4470   /* Length = (end - start +1).  */
4471   e->ts.u.cl->length = gfc_subtract (end, start);
4472   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4473                                 gfc_get_int_expr (gfc_default_integer_kind,
4474                                                   NULL, 1));
4475
4476   e->ts.u.cl->length->ts.type = BT_INTEGER;
4477   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4478
4479   /* Make sure that the length is simplified.  */
4480   gfc_simplify_expr (e->ts.u.cl->length, 1);
4481   gfc_resolve_expr (e->ts.u.cl->length);
4482 }
4483
4484
4485 /* Resolve subtype references.  */
4486
4487 static gfc_try
4488 resolve_ref (gfc_expr *expr)
4489 {
4490   int current_part_dimension, n_components, seen_part_dimension;
4491   gfc_ref *ref;
4492
4493   for (ref = expr->ref; ref; ref = ref->next)
4494     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4495       {
4496         find_array_spec (expr);
4497         break;
4498       }
4499
4500   for (ref = expr->ref; ref; ref = ref->next)
4501     switch (ref->type)
4502       {
4503       case REF_ARRAY:
4504         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4505           return FAILURE;
4506         break;
4507
4508       case REF_COMPONENT:
4509         break;
4510
4511       case REF_SUBSTRING:
4512         resolve_substring (ref);
4513         break;
4514       }
4515
4516   /* Check constraints on part references.  */
4517
4518   current_part_dimension = 0;
4519   seen_part_dimension = 0;
4520   n_components = 0;
4521
4522   for (ref = expr->ref; ref; ref = ref->next)
4523     {
4524       switch (ref->type)
4525         {
4526         case REF_ARRAY:
4527           switch (ref->u.ar.type)
4528             {
4529             case AR_FULL:
4530               /* Coarray scalar.  */
4531               if (ref->u.ar.as->rank == 0)
4532                 {
4533                   current_part_dimension = 0;
4534                   break;
4535                 }
4536               /* Fall through.  */
4537             case AR_SECTION:
4538               current_part_dimension = 1;
4539               break;
4540
4541             case AR_ELEMENT:
4542               current_part_dimension = 0;
4543               break;
4544
4545             case AR_UNKNOWN:
4546               gfc_internal_error ("resolve_ref(): Bad array reference");
4547             }
4548
4549           break;
4550
4551         case REF_COMPONENT:
4552           if (current_part_dimension || seen_part_dimension)
4553             {
4554               /* F03:C614.  */
4555               if (ref->u.c.component->attr.pointer
4556                   || ref->u.c.component->attr.proc_pointer)
4557                 {
4558                   gfc_error ("Component to the right of a part reference "
4559                              "with nonzero rank must not have the POINTER "
4560                              "attribute at %L", &expr->where);
4561                   return FAILURE;
4562                 }
4563               else if (ref->u.c.component->attr.allocatable)
4564                 {
4565                   gfc_error ("Component to the right of a part reference "
4566                              "with nonzero rank must not have the ALLOCATABLE "
4567                              "attribute at %L", &expr->where);
4568                   return FAILURE;
4569                 }
4570             }
4571
4572           n_components++;
4573           break;
4574
4575         case REF_SUBSTRING:
4576           break;
4577         }
4578
4579       if (((ref->type == REF_COMPONENT && n_components > 1)
4580            || ref->next == NULL)
4581           && current_part_dimension
4582           && seen_part_dimension)
4583         {
4584           gfc_error ("Two or more part references with nonzero rank must "
4585                      "not be specified at %L", &expr->where);
4586           return FAILURE;
4587         }
4588
4589       if (ref->type == REF_COMPONENT)
4590         {
4591           if (current_part_dimension)
4592             seen_part_dimension = 1;
4593
4594           /* reset to make sure */
4595           current_part_dimension = 0;
4596         }
4597     }
4598
4599   return SUCCESS;
4600 }
4601
4602
4603 /* Given an expression, determine its shape.  This is easier than it sounds.
4604    Leaves the shape array NULL if it is not possible to determine the shape.  */
4605
4606 static void
4607 expression_shape (gfc_expr *e)
4608 {
4609   mpz_t array[GFC_MAX_DIMENSIONS];
4610   int i;
4611
4612   if (e->rank == 0 || e->shape != NULL)
4613     return;
4614
4615   for (i = 0; i < e->rank; i++)
4616     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4617       goto fail;
4618
4619   e->shape = gfc_get_shape (e->rank);
4620
4621   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4622
4623   return;
4624
4625 fail:
4626   for (i--; i >= 0; i--)
4627     mpz_clear (array[i]);
4628 }
4629
4630
4631 /* Given a variable expression node, compute the rank of the expression by
4632    examining the base symbol and any reference structures it may have.  */
4633
4634 static void
4635 expression_rank (gfc_expr *e)
4636 {
4637   gfc_ref *ref;
4638   int i, rank;
4639
4640   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4641      could lead to serious confusion...  */
4642   gcc_assert (e->expr_type != EXPR_COMPCALL);
4643
4644   if (e->ref == NULL)
4645     {
4646       if (e->expr_type == EXPR_ARRAY)
4647         goto done;
4648       /* Constructors can have a rank different from one via RESHAPE().  */
4649
4650       if (e->symtree == NULL)
4651         {
4652           e->rank = 0;
4653           goto done;
4654         }
4655
4656       e->rank = (e->symtree->n.sym->as == NULL)
4657                 ? 0 : e->symtree->n.sym->as->rank;
4658       goto done;
4659     }
4660
4661   rank = 0;
4662
4663   for (ref = e->ref; ref; ref = ref->next)
4664     {
4665       if (ref->type != REF_ARRAY)
4666         continue;
4667
4668       if (ref->u.ar.type == AR_FULL)
4669         {
4670           rank = ref->u.ar.as->rank;
4671           break;
4672         }
4673
4674       if (ref->u.ar.type == AR_SECTION)
4675         {
4676           /* Figure out the rank of the section.  */
4677           if (rank != 0)
4678             gfc_internal_error ("expression_rank(): Two array specs");
4679
4680           for (i = 0; i < ref->u.ar.dimen; i++)
4681             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4682                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4683               rank++;
4684
4685           break;
4686         }
4687     }
4688
4689   e->rank = rank;
4690
4691 done:
4692   expression_shape (e);
4693 }
4694
4695
4696 /* Resolve a variable expression.  */
4697
4698 static gfc_try
4699 resolve_variable (gfc_expr *e)
4700 {
4701   gfc_symbol *sym;
4702   gfc_try t;
4703
4704   t = SUCCESS;
4705
4706   if (e->symtree == NULL)
4707     return FAILURE;
4708
4709   if (e->ref && resolve_ref (e) == FAILURE)
4710     return FAILURE;
4711
4712   sym = e->symtree->n.sym;
4713   if (sym->attr.flavor == FL_PROCEDURE
4714       && (!sym->attr.function
4715           || (sym->attr.function && sym->result
4716               && sym->result->attr.proc_pointer
4717               && !sym->result->attr.function)))
4718     {
4719       e->ts.type = BT_PROCEDURE;
4720       goto resolve_procedure;
4721     }
4722
4723   if (sym->ts.type != BT_UNKNOWN)
4724     gfc_variable_attr (e, &e->ts);
4725   else
4726     {
4727       /* Must be a simple variable reference.  */
4728       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4729         return FAILURE;
4730       e->ts = sym->ts;
4731     }
4732
4733   if (check_assumed_size_reference (sym, e))
4734     return FAILURE;
4735
4736   /* Deal with forward references to entries during resolve_code, to
4737      satisfy, at least partially, 12.5.2.5.  */
4738   if (gfc_current_ns->entries
4739       && current_entry_id == sym->entry_id
4740       && cs_base
4741       && cs_base->current
4742       && cs_base->current->op != EXEC_ENTRY)
4743     {
4744       gfc_entry_list *entry;
4745       gfc_formal_arglist *formal;
4746       int n;
4747       bool seen;
4748
4749       /* If the symbol is a dummy...  */
4750       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4751         {
4752           entry = gfc_current_ns->entries;
4753           seen = false;
4754
4755           /* ...test if the symbol is a parameter of previous entries.  */
4756           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4757             for (formal = entry->sym->formal; formal; formal = formal->next)
4758               {
4759                 if (formal->sym && sym->name == formal->sym->name)
4760                   seen = true;
4761               }
4762
4763           /*  If it has not been seen as a dummy, this is an error.  */
4764           if (!seen)
4765             {
4766               if (specification_expr)
4767                 gfc_error ("Variable '%s', used in a specification expression"
4768                            ", is referenced at %L before the ENTRY statement "
4769                            "in which it is a parameter",
4770                            sym->name, &cs_base->current->loc);
4771               else
4772                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4773                            "statement in which it is a parameter",
4774                            sym->name, &cs_base->current->loc);
4775               t = FAILURE;
4776             }
4777         }
4778
4779       /* Now do the same check on the specification expressions.  */
4780       specification_expr = 1;
4781       if (sym->ts.type == BT_CHARACTER
4782           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4783         t = FAILURE;
4784
4785       if (sym->as)
4786         for (n = 0; n < sym->as->rank; n++)
4787           {
4788              specification_expr = 1;
4789              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4790                t = FAILURE;
4791              specification_expr = 1;
4792              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4793                t = FAILURE;
4794           }
4795       specification_expr = 0;
4796
4797       if (t == SUCCESS)
4798         /* Update the symbol's entry level.  */
4799         sym->entry_id = current_entry_id + 1;
4800     }
4801
4802   /* If a symbol has been host_associated mark it.  This is used latter,
4803      to identify if aliasing is possible via host association.  */
4804   if (sym->attr.flavor == FL_VARIABLE
4805         && gfc_current_ns->parent
4806         && (gfc_current_ns->parent == sym->ns
4807               || (gfc_current_ns->parent->parent
4808                     && gfc_current_ns->parent->parent == sym->ns)))
4809     sym->attr.host_assoc = 1;
4810
4811 resolve_procedure:
4812   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4813     t = FAILURE;
4814
4815   /* F2008, C617 and C1229.  */
4816   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
4817       && gfc_is_coindexed (e))
4818     {
4819       gfc_ref *ref, *ref2 = NULL;
4820
4821       if (e->ts.type == BT_CLASS)
4822         {
4823           gfc_error ("Polymorphic subobject of coindexed object at %L",
4824                      &e->where);
4825           t = FAILURE;
4826         }
4827
4828       for (ref = e->ref; ref; ref = ref->next)
4829         {
4830           if (ref->type == REF_COMPONENT)
4831             ref2 = ref;
4832           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
4833             break;
4834         }
4835
4836       for ( ; ref; ref = ref->next)
4837         if (ref->type == REF_COMPONENT)
4838           break;
4839
4840       /* Expression itself is coindexed object.  */
4841       if (ref == NULL)
4842         {
4843           gfc_component *c;
4844           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
4845           for ( ; c; c = c->next)
4846             if (c->attr.allocatable && c->ts.type == BT_CLASS)
4847               {
4848                 gfc_error ("Coindexed object with polymorphic allocatable "
4849                          "subcomponent at %L", &e->where);
4850                 t = FAILURE;
4851                 break;
4852               }
4853         }
4854     }
4855
4856   return t;
4857 }
4858
4859
4860 /* Checks to see that the correct symbol has been host associated.
4861    The only situation where this arises is that in which a twice
4862    contained function is parsed after the host association is made.
4863    Therefore, on detecting this, change the symbol in the expression
4864    and convert the array reference into an actual arglist if the old
4865    symbol is a variable.  */
4866 static bool
4867 check_host_association (gfc_expr *e)
4868 {
4869   gfc_symbol *sym, *old_sym;
4870   gfc_symtree *st;
4871   int n;
4872   gfc_ref *ref;
4873   gfc_actual_arglist *arg, *tail = NULL;
4874   bool retval = e->expr_type == EXPR_FUNCTION;
4875
4876   /*  If the expression is the result of substitution in
4877       interface.c(gfc_extend_expr) because there is no way in
4878       which the host association can be wrong.  */
4879   if (e->symtree == NULL
4880         || e->symtree->n.sym == NULL
4881         || e->user_operator)
4882     return retval;
4883
4884   old_sym = e->symtree->n.sym;
4885
4886   if (gfc_current_ns->parent
4887         && old_sym->ns != gfc_current_ns)
4888     {
4889       /* Use the 'USE' name so that renamed module symbols are
4890          correctly handled.  */
4891       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4892
4893       if (sym && old_sym != sym
4894               && sym->ts.type == old_sym->ts.type
4895               && sym->attr.flavor == FL_PROCEDURE
4896               && sym->attr.contained)
4897         {
4898           /* Clear the shape, since it might not be valid.  */
4899           if (e->shape != NULL)
4900             {
4901               for (n = 0; n < e->rank; n++)
4902                 mpz_clear (e->shape[n]);
4903
4904               gfc_free (e->shape);
4905             }
4906
4907           /* Give the expression the right symtree!  */
4908           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4909           gcc_assert (st != NULL);
4910
4911           if (old_sym->attr.flavor == FL_PROCEDURE
4912                 || e->expr_type == EXPR_FUNCTION)
4913             {
4914               /* Original was function so point to the new symbol, since
4915                  the actual argument list is already attached to the
4916                  expression. */
4917               e->value.function.esym = NULL;
4918               e->symtree = st;
4919             }
4920           else
4921             {
4922               /* Original was variable so convert array references into
4923                  an actual arglist. This does not need any checking now
4924                  since gfc_resolve_function will take care of it.  */
4925               e->value.function.actual = NULL;
4926               e->expr_type = EXPR_FUNCTION;
4927               e->symtree = st;
4928
4929               /* Ambiguity will not arise if the array reference is not
4930                  the last reference.  */
4931               for (ref = e->ref; ref; ref = ref->next)
4932                 if (ref->type == REF_ARRAY && ref->next == NULL)
4933                   break;
4934
4935               gcc_assert (ref->type == REF_ARRAY);
4936
4937               /* Grab the start expressions from the array ref and
4938                  copy them into actual arguments.  */
4939               for (n = 0; n < ref->u.ar.dimen; n++)
4940                 {
4941                   arg = gfc_get_actual_arglist ();
4942                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4943                   if (e->value.function.actual == NULL)
4944                     tail = e->value.function.actual = arg;
4945                   else
4946                     {
4947                       tail->next = arg;
4948                       tail = arg;
4949                     }
4950                 }
4951
4952               /* Dump the reference list and set the rank.  */
4953               gfc_free_ref_list (e->ref);
4954               e->ref = NULL;
4955               e->rank = sym->as ? sym->as->rank : 0;
4956             }
4957
4958           gfc_resolve_expr (e);
4959           sym->refs++;
4960         }
4961     }
4962   /* This might have changed!  */
4963   return e->expr_type == EXPR_FUNCTION;
4964 }
4965
4966
4967 static void
4968 gfc_resolve_character_operator (gfc_expr *e)
4969 {
4970   gfc_expr *op1 = e->value.op.op1;
4971   gfc_expr *op2 = e->value.op.op2;
4972   gfc_expr *e1 = NULL;
4973   gfc_expr *e2 = NULL;
4974
4975   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4976
4977   if (op1->ts.u.cl && op1->ts.u.cl->length)
4978     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4979   else if (op1->expr_type == EXPR_CONSTANT)
4980     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4981                            op1->value.character.length);
4982
4983   if (op2->ts.u.cl && op2->ts.u.cl->length)
4984     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4985   else if (op2->expr_type == EXPR_CONSTANT)
4986     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4987                            op2->value.character.length);
4988
4989   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4990
4991   if (!e1 || !e2)
4992     return;
4993
4994   e->ts.u.cl->length = gfc_add (e1, e2);
4995   e->ts.u.cl->length->ts.type = BT_INTEGER;
4996   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4997   gfc_simplify_expr (e->ts.u.cl->length, 0);
4998   gfc_resolve_expr (e->ts.u.cl->length);
4999
5000   return;
5001 }
5002
5003
5004 /*  Ensure that an character expression has a charlen and, if possible, a
5005     length expression.  */
5006
5007 static void
5008 fixup_charlen (gfc_expr *e)
5009 {
5010   /* The cases fall through so that changes in expression type and the need
5011      for multiple fixes are picked up.  In all circumstances, a charlen should
5012      be available for the middle end to hang a backend_decl on.  */
5013   switch (e->expr_type)
5014     {
5015     case EXPR_OP:
5016       gfc_resolve_character_operator (e);
5017
5018     case EXPR_ARRAY:
5019       if (e->expr_type == EXPR_ARRAY)
5020         gfc_resolve_character_array_constructor (e);
5021
5022     case EXPR_SUBSTRING:
5023       if (!e->ts.u.cl && e->ref)
5024         gfc_resolve_substring_charlen (e);
5025
5026     default:
5027       if (!e->ts.u.cl)
5028         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5029
5030       break;
5031     }
5032 }
5033
5034
5035 /* Update an actual argument to include the passed-object for type-bound
5036    procedures at the right position.  */
5037
5038 static gfc_actual_arglist*
5039 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5040                      const char *name)
5041 {
5042   gcc_assert (argpos > 0);
5043
5044   if (argpos == 1)
5045     {
5046       gfc_actual_arglist* result;
5047
5048       result = gfc_get_actual_arglist ();
5049       result->expr = po;
5050       result->next = lst;
5051       if (name)
5052         result->name = name;
5053
5054       return result;
5055     }
5056
5057   if (lst)
5058     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5059   else
5060     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5061   return lst;
5062 }
5063
5064
5065 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5066
5067 static gfc_expr*
5068 extract_compcall_passed_object (gfc_expr* e)
5069 {
5070   gfc_expr* po;
5071
5072   gcc_assert (e->expr_type == EXPR_COMPCALL);
5073
5074   if (e->value.compcall.base_object)
5075     po = gfc_copy_expr (e->value.compcall.base_object);
5076   else
5077     {
5078       po = gfc_get_expr ();
5079       po->expr_type = EXPR_VARIABLE;
5080       po->symtree = e->symtree;
5081       po->ref = gfc_copy_ref (e->ref);
5082       po->where = e->where;
5083     }
5084
5085   if (gfc_resolve_expr (po) == FAILURE)
5086     return NULL;
5087
5088   return po;
5089 }
5090
5091
5092 /* Update the arglist of an EXPR_COMPCALL expression to include the
5093    passed-object.  */
5094
5095 static gfc_try
5096 update_compcall_arglist (gfc_expr* e)
5097 {
5098   gfc_expr* po;
5099   gfc_typebound_proc* tbp;
5100
5101   tbp = e->value.compcall.tbp;
5102
5103   if (tbp->error)
5104     return FAILURE;
5105
5106   po = extract_compcall_passed_object (e);
5107   if (!po)
5108     return FAILURE;
5109
5110   if (tbp->nopass || e->value.compcall.ignore_pass)
5111     {
5112       gfc_free_expr (po);
5113       return SUCCESS;
5114     }
5115
5116   gcc_assert (tbp->pass_arg_num > 0);
5117   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5118                                                   tbp->pass_arg_num,
5119                                                   tbp->pass_arg);
5120
5121   return SUCCESS;
5122 }
5123
5124
5125 /* Extract the passed object from a PPC call (a copy of it).  */
5126
5127 static gfc_expr*
5128 extract_ppc_passed_object (gfc_expr *e)
5129 {
5130   gfc_expr *po;
5131   gfc_ref **ref;
5132
5133   po = gfc_get_expr ();
5134   po->expr_type = EXPR_VARIABLE;
5135   po->symtree = e->symtree;
5136   po->ref = gfc_copy_ref (e->ref);
5137   po->where = e->where;
5138
5139   /* Remove PPC reference.  */
5140   ref = &po->ref;
5141   while ((*ref)->next)
5142     ref = &(*ref)->next;
5143   gfc_free_ref_list (*ref);
5144   *ref = NULL;
5145
5146   if (gfc_resolve_expr (po) == FAILURE)
5147     return NULL;
5148
5149   return po;
5150 }
5151
5152
5153 /* Update the actual arglist of a procedure pointer component to include the
5154    passed-object.  */
5155
5156 static gfc_try
5157 update_ppc_arglist (gfc_expr* e)
5158 {
5159   gfc_expr* po;
5160   gfc_component *ppc;
5161   gfc_typebound_proc* tb;
5162
5163   if (!gfc_is_proc_ptr_comp (e, &ppc))
5164     return FAILURE;
5165
5166   tb = ppc->tb;
5167
5168   if (tb->error)
5169     return FAILURE;
5170   else if (tb->nopass)
5171     return SUCCESS;
5172
5173   po = extract_ppc_passed_object (e);
5174   if (!po)
5175     return FAILURE;
5176
5177   if (po->rank > 0)
5178     {
5179       gfc_error ("Passed-object at %L must be scalar", &e->where);
5180       return FAILURE;
5181     }
5182
5183   gcc_assert (tb->pass_arg_num > 0);
5184   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5185                                                   tb->pass_arg_num,
5186                                                   tb->pass_arg);
5187
5188   return SUCCESS;
5189 }
5190
5191
5192 /* Check that the object a TBP is called on is valid, i.e. it must not be
5193    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5194
5195 static gfc_try
5196 check_typebound_baseobject (gfc_expr* e)
5197 {
5198   gfc_expr* base;
5199
5200   base = extract_compcall_passed_object (e);
5201   if (!base)
5202     return FAILURE;
5203
5204   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5205
5206   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5207     {
5208       gfc_error ("Base object for type-bound procedure call at %L is of"
5209                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5210       return FAILURE;
5211     }
5212
5213   /* If the procedure called is NOPASS, the base object must be scalar.  */
5214   if (e->value.compcall.tbp->nopass && base->rank > 0)
5215     {
5216       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5217                  " be scalar", &e->where);
5218       return FAILURE;
5219     }
5220
5221   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5222   if (base->rank > 0)
5223     {
5224       gfc_error ("Non-scalar base object at %L currently not implemented",
5225                  &e->where);
5226       return FAILURE;
5227     }
5228
5229   return SUCCESS;
5230 }
5231
5232
5233 /* Resolve a call to a type-bound procedure, either function or subroutine,
5234    statically from the data in an EXPR_COMPCALL expression.  The adapted
5235    arglist and the target-procedure symtree are returned.  */
5236
5237 static gfc_try
5238 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5239                           gfc_actual_arglist** actual)
5240 {
5241   gcc_assert (e->expr_type == EXPR_COMPCALL);
5242   gcc_assert (!e->value.compcall.tbp->is_generic);
5243
5244   /* Update the actual arglist for PASS.  */
5245   if (update_compcall_arglist (e) == FAILURE)
5246     return FAILURE;
5247
5248   *actual = e->value.compcall.actual;
5249   *target = e->value.compcall.tbp->u.specific;
5250
5251   gfc_free_ref_list (e->ref);
5252   e->ref = NULL;
5253   e->value.compcall.actual = NULL;
5254
5255   return SUCCESS;
5256 }
5257
5258
5259 /* Get the ultimate declared type from an expression.  In addition,
5260    return the last class/derived type reference and the copy of the
5261    reference list.  */
5262 static gfc_symbol*
5263 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5264                         gfc_expr *e)
5265 {
5266   gfc_symbol *declared;
5267   gfc_ref *ref;
5268
5269   declared = NULL;
5270   if (class_ref)
5271     *class_ref = NULL;
5272   if (new_ref)
5273     *new_ref = gfc_copy_ref (e->ref);
5274
5275   for (ref = e->ref; ref; ref = ref->next)
5276     {
5277       if (ref->type != REF_COMPONENT)
5278         continue;
5279
5280       if (ref->u.c.component->ts.type == BT_CLASS
5281             || ref->u.c.component->ts.type == BT_DERIVED)
5282         {
5283           declared = ref->u.c.component->ts.u.derived;
5284           if (class_ref)
5285             *class_ref = ref;
5286         }
5287     }
5288
5289   if (declared == NULL)
5290     declared = e->symtree->n.sym->ts.u.derived;
5291
5292   return declared;
5293 }
5294
5295
5296 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5297    which of the specific bindings (if any) matches the arglist and transform
5298    the expression into a call of that binding.  */
5299
5300 static gfc_try
5301 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5302 {
5303   gfc_typebound_proc* genproc;
5304   const char* genname;
5305   gfc_symtree *st;
5306   gfc_symbol *derived;
5307
5308   gcc_assert (e->expr_type == EXPR_COMPCALL);
5309   genname = e->value.compcall.name;
5310   genproc = e->value.compcall.tbp;
5311
5312   if (!genproc->is_generic)
5313     return SUCCESS;
5314
5315   /* Try the bindings on this type and in the inheritance hierarchy.  */
5316   for (; genproc; genproc = genproc->overridden)
5317     {
5318       gfc_tbp_generic* g;
5319
5320       gcc_assert (genproc->is_generic);
5321       for (g = genproc->u.generic; g; g = g->next)
5322         {
5323           gfc_symbol* target;
5324           gfc_actual_arglist* args;
5325           bool matches;
5326
5327           gcc_assert (g->specific);
5328
5329           if (g->specific->error)
5330             continue;
5331
5332           target = g->specific->u.specific->n.sym;
5333
5334           /* Get the right arglist by handling PASS/NOPASS.  */
5335           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5336           if (!g->specific->nopass)
5337             {
5338               gfc_expr* po;
5339               po = extract_compcall_passed_object (e);
5340               if (!po)
5341                 return FAILURE;
5342
5343               gcc_assert (g->specific->pass_arg_num > 0);
5344               gcc_assert (!g->specific->error);
5345               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5346                                           g->specific->pass_arg);
5347             }
5348           resolve_actual_arglist (args, target->attr.proc,
5349                                   is_external_proc (target) && !target->formal);
5350
5351           /* Check if this arglist matches the formal.  */
5352           matches = gfc_arglist_matches_symbol (&args, target);
5353
5354           /* Clean up and break out of the loop if we've found it.  */
5355           gfc_free_actual_arglist (args);
5356           if (matches)
5357             {
5358               e->value.compcall.tbp = g->specific;
5359               genname = g->specific_st->name;
5360               /* Pass along the name for CLASS methods, where the vtab
5361                  procedure pointer component has to be referenced.  */
5362               if (name)
5363                 *name = genname;
5364               goto success;
5365             }
5366         }
5367     }
5368
5369   /* Nothing matching found!  */
5370   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5371              " '%s' at %L", genname, &e->where);
5372   return FAILURE;
5373
5374 success:
5375   /* Make sure that we have the right specific instance for the name.  */
5376   derived = get_declared_from_expr (NULL, NULL, e);
5377
5378   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5379   if (st)
5380     e->value.compcall.tbp = st->n.tb;
5381
5382   return SUCCESS;
5383 }
5384
5385
5386 /* Resolve a call to a type-bound subroutine.  */
5387
5388 static gfc_try
5389 resolve_typebound_call (gfc_code* c, const char **name)
5390 {
5391   gfc_actual_arglist* newactual;
5392   gfc_symtree* target;
5393
5394   /* Check that's really a SUBROUTINE.  */
5395   if (!c->expr1->value.compcall.tbp->subroutine)
5396     {
5397       gfc_error ("'%s' at %L should be a SUBROUTINE",
5398                  c->expr1->value.compcall.name, &c->loc);
5399       return FAILURE;
5400     }
5401
5402   if (check_typebound_baseobject (c->expr1) == FAILURE)
5403     return FAILURE;
5404
5405   /* Pass along the name for CLASS methods, where the vtab
5406      procedure pointer component has to be referenced.  */
5407   if (name)
5408     *name = c->expr1->value.compcall.name;
5409
5410   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5411     return FAILURE;
5412
5413   /* Transform into an ordinary EXEC_CALL for now.  */
5414
5415   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5416     return FAILURE;
5417
5418   c->ext.actual = newactual;
5419   c->symtree = target;
5420   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5421
5422   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5423
5424   gfc_free_expr (c->expr1);
5425   c->expr1 = gfc_get_expr ();
5426   c->expr1->expr_type = EXPR_FUNCTION;
5427   c->expr1->symtree = target;
5428   c->expr1->where = c->loc;
5429
5430   return resolve_call (c);
5431 }
5432
5433
5434 /* Resolve a component-call expression.  */
5435 static gfc_try
5436 resolve_compcall (gfc_expr* e, const char **name)
5437 {
5438   gfc_actual_arglist* newactual;
5439   gfc_symtree* target;
5440
5441   /* Check that's really a FUNCTION.  */
5442   if (!e->value.compcall.tbp->function)
5443     {
5444       gfc_error ("'%s' at %L should be a FUNCTION",
5445                  e->value.compcall.name, &e->where);
5446       return FAILURE;
5447     }
5448
5449   /* These must not be assign-calls!  */
5450   gcc_assert (!e->value.compcall.assign);
5451
5452   if (check_typebound_baseobject (e) == FAILURE)
5453     return FAILURE;
5454
5455   /* Pass along the name for CLASS methods, where the vtab
5456      procedure pointer component has to be referenced.  */
5457   if (name)
5458     *name = e->value.compcall.name;
5459
5460   if (resolve_typebound_generic_call (e, name) == FAILURE)
5461     return FAILURE;
5462   gcc_assert (!e->value.compcall.tbp->is_generic);
5463
5464   /* Take the rank from the function's symbol.  */
5465   if (e->value.compcall.tbp->u.specific->n.sym->as)
5466     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5467
5468   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5469      arglist to the TBP's binding target.  */
5470
5471   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5472     return FAILURE;
5473
5474   e->value.function.actual = newactual;
5475   e->value.function.name = NULL;
5476   e->value.function.esym = target->n.sym;
5477   e->value.function.isym = NULL;
5478   e->symtree = target;
5479   e->ts = target->n.sym->ts;
5480   e->expr_type = EXPR_FUNCTION;
5481
5482   /* Resolution is not necessary if this is a class subroutine; this
5483      function only has to identify the specific proc. Resolution of
5484      the call will be done next in resolve_typebound_call.  */
5485   return gfc_resolve_expr (e);
5486 }
5487
5488
5489
5490 /* Resolve a typebound function, or 'method'. First separate all
5491    the non-CLASS references by calling resolve_compcall directly.  */
5492
5493 static gfc_try
5494 resolve_typebound_function (gfc_expr* e)
5495 {
5496   gfc_symbol *declared;
5497   gfc_component *c;
5498   gfc_ref *new_ref;
5499   gfc_ref *class_ref;
5500   gfc_symtree *st;
5501   const char *name;
5502   gfc_typespec ts;
5503   gfc_expr *expr;
5504
5505   st = e->symtree;
5506
5507   /* Deal with typebound operators for CLASS objects.  */
5508   expr = e->value.compcall.base_object;
5509   if (expr && expr->symtree->n.sym->ts.type == BT_CLASS
5510         && e->value.compcall.name)
5511     {
5512       /* Since the typebound operators are generic, we have to ensure
5513          that any delays in resolution are corrected and that the vtab
5514          is present.  */
5515       ts = expr->symtree->n.sym->ts;
5516       declared = ts.u.derived;
5517       c = gfc_find_component (declared, "$vptr", true, true);
5518       if (c->ts.u.derived == NULL)
5519         c->ts.u.derived = gfc_find_derived_vtab (declared);
5520
5521       if (resolve_compcall (e, &name) == FAILURE)
5522         return FAILURE;
5523
5524       /* Use the generic name if it is there.  */
5525       name = name ? name : e->value.function.esym->name;
5526       e->symtree = expr->symtree;
5527       expr->symtree->n.sym->ts.u.derived = declared;
5528       gfc_add_component_ref (e, "$vptr");
5529       gfc_add_component_ref (e, name);
5530       e->value.function.esym = NULL;
5531       return SUCCESS;
5532     }
5533
5534   if (st == NULL)
5535     return resolve_compcall (e, NULL);
5536
5537   if (resolve_ref (e) == FAILURE)
5538     return FAILURE;
5539
5540   /* Get the CLASS declared type.  */
5541   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5542
5543   /* Weed out cases of the ultimate component being a derived type.  */
5544   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5545          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5546     {
5547       gfc_free_ref_list (new_ref);
5548       return resolve_compcall (e, NULL);
5549     }
5550
5551   c = gfc_find_component (declared, "$data", true, true);
5552   declared = c->ts.u.derived;
5553
5554   /* Treat the call as if it is a typebound procedure, in order to roll
5555      out the correct name for the specific function.  */
5556   if (resolve_compcall (e, &name) == FAILURE)
5557     return FAILURE;
5558   ts = e->ts;
5559
5560   /* Then convert the expression to a procedure pointer component call.  */
5561   e->value.function.esym = NULL;
5562   e->symtree = st;
5563
5564   if (new_ref)  
5565     e->ref = new_ref;
5566
5567   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5568   gfc_add_component_ref (e, "$vptr");
5569   gfc_add_component_ref (e, name);
5570
5571   /* Recover the typespec for the expression.  This is really only
5572      necessary for generic procedures, where the additional call
5573      to gfc_add_component_ref seems to throw the collection of the
5574      correct typespec.  */
5575   e->ts = ts;
5576   return SUCCESS;
5577 }
5578
5579 /* Resolve a typebound subroutine, or 'method'. First separate all
5580    the non-CLASS references by calling resolve_typebound_call
5581    directly.  */
5582
5583 static gfc_try
5584 resolve_typebound_subroutine (gfc_code *code)
5585 {
5586   gfc_symbol *declared;
5587   gfc_component *c;
5588   gfc_ref *new_ref;
5589   gfc_ref *class_ref;
5590   gfc_symtree *st;
5591   const char *name;
5592   gfc_typespec ts;
5593   gfc_expr *expr;
5594
5595   st = code->expr1->symtree;
5596
5597   /* Deal with typebound operators for CLASS objects.  */
5598   expr = code->expr1->value.compcall.base_object;
5599   if (expr && expr->symtree->n.sym->ts.type == BT_CLASS
5600         && code->expr1->value.compcall.name)
5601     {
5602       /* Since the typebound operators are generic, we have to ensure
5603          that any delays in resolution are corrected and that the vtab
5604          is present.  */
5605       ts = expr->symtree->n.sym->ts;
5606       declared = ts.u.derived;
5607       c = gfc_find_component (declared, "$vptr", true, true);
5608       if (c->ts.u.derived == NULL)
5609         c->ts.u.derived = gfc_find_derived_vtab (declared);
5610
5611       if (resolve_typebound_call (code, &name) == FAILURE)
5612         return FAILURE;
5613
5614       /* Use the generic name if it is there.  */
5615       name = name ? name : code->expr1->value.function.esym->name;
5616       code->expr1->symtree = expr->symtree;
5617       expr->symtree->n.sym->ts.u.derived = declared;
5618       gfc_add_component_ref (code->expr1, "$vptr");
5619       gfc_add_component_ref (code->expr1, name);
5620       code->expr1->value.function.esym = NULL;
5621       return SUCCESS;
5622     }
5623
5624   if (st == NULL)
5625     return resolve_typebound_call (code, NULL);
5626
5627   if (resolve_ref (code->expr1) == FAILURE)
5628     return FAILURE;
5629
5630   /* Get the CLASS declared type.  */
5631   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5632
5633   /* Weed out cases of the ultimate component being a derived type.  */
5634   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5635          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5636     {
5637       gfc_free_ref_list (new_ref);
5638       return resolve_typebound_call (code, NULL);
5639     }
5640
5641   if (resolve_typebound_call (code, &name) == FAILURE)
5642     return FAILURE;
5643   ts = code->expr1->ts;
5644
5645   /* Then convert the expression to a procedure pointer component call.  */
5646   code->expr1->value.function.esym = NULL;
5647   code->expr1->symtree = st;
5648
5649   if (new_ref)
5650     code->expr1->ref = new_ref;
5651
5652   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5653   gfc_add_component_ref (code->expr1, "$vptr");
5654   gfc_add_component_ref (code->expr1, name);
5655
5656   /* Recover the typespec for the expression.  This is really only
5657      necessary for generic procedures, where the additional call
5658      to gfc_add_component_ref seems to throw the collection of the
5659      correct typespec.  */
5660   code->expr1->ts = ts;
5661   return SUCCESS;
5662 }
5663
5664
5665 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5666
5667 static gfc_try
5668 resolve_ppc_call (gfc_code* c)
5669 {
5670   gfc_component *comp;
5671   bool b;
5672
5673   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5674   gcc_assert (b);
5675
5676   c->resolved_sym = c->expr1->symtree->n.sym;
5677   c->expr1->expr_type = EXPR_VARIABLE;
5678
5679   if (!comp->attr.subroutine)
5680     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5681
5682   if (resolve_ref (c->expr1) == FAILURE)
5683     return FAILURE;
5684
5685   if (update_ppc_arglist (c->expr1) == FAILURE)
5686     return FAILURE;
5687
5688   c->ext.actual = c->expr1->value.compcall.actual;
5689
5690   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5691                               comp->formal == NULL) == FAILURE)
5692     return FAILURE;
5693
5694   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5695
5696   return SUCCESS;
5697 }
5698
5699
5700 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5701
5702 static gfc_try
5703 resolve_expr_ppc (gfc_expr* e)
5704 {
5705   gfc_component *comp;
5706   bool b;
5707
5708   b = gfc_is_proc_ptr_comp (e, &comp);
5709   gcc_assert (b);
5710
5711   /* Convert to EXPR_FUNCTION.  */
5712   e->expr_type = EXPR_FUNCTION;
5713   e->value.function.isym = NULL;
5714   e->value.function.actual = e->value.compcall.actual;
5715   e->ts = comp->ts;
5716   if (comp->as != NULL)
5717     e->rank = comp->as->rank;
5718
5719   if (!comp->attr.function)
5720     gfc_add_function (&comp->attr, comp->name, &e->where);
5721
5722   if (resolve_ref (e) == FAILURE)
5723     return FAILURE;
5724
5725   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5726                               comp->formal == NULL) == FAILURE)
5727     return FAILURE;
5728
5729   if (update_ppc_arglist (e) == FAILURE)
5730     return FAILURE;
5731
5732   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5733
5734   return SUCCESS;
5735 }
5736
5737
5738 static bool
5739 gfc_is_expandable_expr (gfc_expr *e)
5740 {
5741   gfc_constructor *con;
5742
5743   if (e->expr_type == EXPR_ARRAY)
5744     {
5745       /* Traverse the constructor looking for variables that are flavor
5746          parameter.  Parameters must be expanded since they are fully used at
5747          compile time.  */
5748       con = gfc_constructor_first (e->value.constructor);
5749       for (; con; con = gfc_constructor_next (con))
5750         {
5751           if (con->expr->expr_type == EXPR_VARIABLE
5752               && con->expr->symtree
5753               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5754               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5755             return true;
5756           if (con->expr->expr_type == EXPR_ARRAY
5757               && gfc_is_expandable_expr (con->expr))
5758             return true;
5759         }
5760     }
5761
5762   return false;
5763 }
5764
5765 /* Resolve an expression.  That is, make sure that types of operands agree
5766    with their operators, intrinsic operators are converted to function calls
5767    for overloaded types and unresolved function references are resolved.  */
5768
5769 gfc_try
5770 gfc_resolve_expr (gfc_expr *e)
5771 {
5772   gfc_try t;
5773   bool inquiry_save;
5774
5775   if (e == NULL)
5776     return SUCCESS;
5777
5778   /* inquiry_argument only applies to variables.  */
5779   inquiry_save = inquiry_argument;
5780   if (e->expr_type != EXPR_VARIABLE)
5781     inquiry_argument = false;
5782
5783   switch (e->expr_type)
5784     {
5785     case EXPR_OP:
5786       t = resolve_operator (e);
5787       break;
5788
5789     case EXPR_FUNCTION:
5790     case EXPR_VARIABLE:
5791
5792       if (check_host_association (e))
5793         t = resolve_function (e);
5794       else
5795         {
5796           t = resolve_variable (e);
5797           if (t == SUCCESS)
5798             expression_rank (e);
5799         }
5800
5801       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5802           && e->ref->type != REF_SUBSTRING)
5803         gfc_resolve_substring_charlen (e);
5804
5805       break;
5806
5807     case EXPR_COMPCALL:
5808       t = resolve_typebound_function (e);
5809       break;
5810
5811     case EXPR_SUBSTRING:
5812       t = resolve_ref (e);
5813       break;
5814
5815     case EXPR_CONSTANT:
5816     case EXPR_NULL:
5817       t = SUCCESS;
5818       break;
5819
5820     case EXPR_PPC:
5821       t = resolve_expr_ppc (e);
5822       break;
5823
5824     case EXPR_ARRAY:
5825       t = FAILURE;
5826       if (resolve_ref (e) == FAILURE)
5827         break;
5828
5829       t = gfc_resolve_array_constructor (e);
5830       /* Also try to expand a constructor.  */
5831       if (t == SUCCESS)
5832         {
5833           expression_rank (e);
5834           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5835             gfc_expand_constructor (e, false);
5836         }
5837
5838       /* This provides the opportunity for the length of constructors with
5839          character valued function elements to propagate the string length
5840          to the expression.  */
5841       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5842         {
5843           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5844              here rather then add a duplicate test for it above.  */ 
5845           gfc_expand_constructor (e, false);
5846           t = gfc_resolve_character_array_constructor (e);
5847         }
5848
5849       break;
5850
5851     case EXPR_STRUCTURE:
5852       t = resolve_ref (e);
5853       if (t == FAILURE)
5854         break;
5855
5856       t = resolve_structure_cons (e);
5857       if (t == FAILURE)
5858         break;
5859
5860       t = gfc_simplify_expr (e, 0);
5861       break;
5862
5863     default:
5864       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5865     }
5866
5867   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5868     fixup_charlen (e);
5869
5870   inquiry_argument = inquiry_save;
5871
5872   return t;
5873 }
5874
5875
5876 /* Resolve an expression from an iterator.  They must be scalar and have
5877    INTEGER or (optionally) REAL type.  */
5878
5879 static gfc_try
5880 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5881                            const char *name_msgid)
5882 {
5883   if (gfc_resolve_expr (expr) == FAILURE)
5884     return FAILURE;
5885
5886   if (expr->rank != 0)
5887     {
5888       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5889       return FAILURE;
5890     }
5891
5892   if (expr->ts.type != BT_INTEGER)
5893     {
5894       if (expr->ts.type == BT_REAL)
5895         {
5896           if (real_ok)
5897             return gfc_notify_std (GFC_STD_F95_DEL,
5898                                    "Deleted feature: %s at %L must be integer",
5899                                    _(name_msgid), &expr->where);
5900           else
5901             {
5902               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5903                          &expr->where);
5904               return FAILURE;
5905             }
5906         }
5907       else
5908         {
5909           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5910           return FAILURE;
5911         }
5912     }
5913   return SUCCESS;
5914 }
5915
5916
5917 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5918    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5919
5920 gfc_try
5921 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5922 {
5923   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5924       == FAILURE)
5925     return FAILURE;
5926
5927   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5928     {
5929       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5930                  &iter->var->where);
5931       return FAILURE;
5932     }
5933
5934   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5935                                  "Start expression in DO loop") == FAILURE)
5936     return FAILURE;
5937
5938   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5939                                  "End expression in DO loop") == FAILURE)
5940     return FAILURE;
5941
5942   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5943                                  "Step expression in DO loop") == FAILURE)
5944     return FAILURE;
5945
5946   if (iter->step->expr_type == EXPR_CONSTANT)
5947     {
5948       if ((iter->step->ts.type == BT_INTEGER
5949            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5950           || (iter->step->ts.type == BT_REAL
5951               && mpfr_sgn (iter->step->value.real) == 0))
5952         {
5953           gfc_error ("Step expression in DO loop at %L cannot be zero",
5954                      &iter->step->where);
5955           return FAILURE;
5956         }
5957     }
5958
5959   /* Convert start, end, and step to the same type as var.  */
5960   if (iter->start->ts.kind != iter->var->ts.kind
5961       || iter->start->ts.type != iter->var->ts.type)
5962     gfc_convert_type (iter->start, &iter->var->ts, 2);
5963
5964   if (iter->end->ts.kind != iter->var->ts.kind
5965       || iter->end->ts.type != iter->var->ts.type)
5966     gfc_convert_type (iter->end, &iter->var->ts, 2);
5967
5968   if (iter->step->ts.kind != iter->var->ts.kind
5969       || iter->step->ts.type != iter->var->ts.type)
5970     gfc_convert_type (iter->step, &iter->var->ts, 2);
5971
5972   if (iter->start->expr_type == EXPR_CONSTANT
5973       && iter->end->expr_type == EXPR_CONSTANT
5974       && iter->step->expr_type == EXPR_CONSTANT)
5975     {
5976       int sgn, cmp;
5977       if (iter->start->ts.type == BT_INTEGER)
5978         {
5979           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5980           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5981         }
5982       else
5983         {
5984           sgn = mpfr_sgn (iter->step->value.real);
5985           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5986         }
5987       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5988         gfc_warning ("DO loop at %L will be executed zero times",
5989                      &iter->step->where);
5990     }
5991
5992   return SUCCESS;
5993 }
5994
5995
5996 /* Traversal function for find_forall_index.  f == 2 signals that
5997    that variable itself is not to be checked - only the references.  */
5998
5999 static bool
6000 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6001 {
6002   if (expr->expr_type != EXPR_VARIABLE)
6003     return false;
6004   
6005   /* A scalar assignment  */
6006   if (!expr->ref || *f == 1)
6007     {
6008       if (expr->symtree->n.sym == sym)
6009         return true;
6010       else
6011         return false;
6012     }
6013
6014   if (*f == 2)
6015     *f = 1;
6016   return false;
6017 }
6018
6019
6020 /* Check whether the FORALL index appears in the expression or not.
6021    Returns SUCCESS if SYM is found in EXPR.  */
6022
6023 gfc_try
6024 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6025 {
6026   if (gfc_traverse_expr (expr, sym, forall_index, f))
6027     return SUCCESS;
6028   else
6029     return FAILURE;
6030 }
6031
6032
6033 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6034    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6035    INTEGERs, and if stride is a constant it must be nonzero.
6036    Furthermore "A subscript or stride in a forall-triplet-spec shall
6037    not contain a reference to any index-name in the
6038    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6039
6040 static void
6041 resolve_forall_iterators (gfc_forall_iterator *it)
6042 {
6043   gfc_forall_iterator *iter, *iter2;
6044
6045   for (iter = it; iter; iter = iter->next)
6046     {
6047       if (gfc_resolve_expr (iter->var) == SUCCESS
6048           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6049         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6050                    &iter->var->where);
6051
6052       if (gfc_resolve_expr (iter->start) == SUCCESS
6053           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6054         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6055                    &iter->start->where);
6056       if (iter->var->ts.kind != iter->start->ts.kind)
6057         gfc_convert_type (iter->start, &iter->var->ts, 2);
6058
6059       if (gfc_resolve_expr (iter->end) == SUCCESS
6060           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6061         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6062                    &iter->end->where);
6063       if (iter->var->ts.kind != iter->end->ts.kind)
6064         gfc_convert_type (iter->end, &iter->var->ts, 2);
6065
6066       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6067         {
6068           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6069             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6070                        &iter->stride->where, "INTEGER");
6071
6072           if (iter->stride->expr_type == EXPR_CONSTANT
6073               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6074             gfc_error ("FORALL stride expression at %L cannot be zero",
6075                        &iter->stride->where);
6076         }
6077       if (iter->var->ts.kind != iter->stride->ts.kind)
6078         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6079     }
6080
6081   for (iter = it; iter; iter = iter->next)
6082     for (iter2 = iter; iter2; iter2 = iter2->next)
6083       {
6084         if (find_forall_index (iter2->start,
6085                                iter->var->symtree->n.sym, 0) == SUCCESS
6086             || find_forall_index (iter2->end,
6087                                   iter->var->symtree->n.sym, 0) == SUCCESS
6088             || find_forall_index (iter2->stride,
6089                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6090           gfc_error ("FORALL index '%s' may not appear in triplet "
6091                      "specification at %L", iter->var->symtree->name,
6092                      &iter2->start->where);
6093       }
6094 }
6095
6096
6097 /* Given a pointer to a symbol that is a derived type, see if it's
6098    inaccessible, i.e. if it's defined in another module and the components are
6099    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6100    inaccessible components are found, nonzero otherwise.  */
6101
6102 static int
6103 derived_inaccessible (gfc_symbol *sym)
6104 {
6105   gfc_component *c;
6106
6107   if (sym->attr.use_assoc && sym->attr.private_comp)
6108     return 1;
6109
6110   for (c = sym->components; c; c = c->next)
6111     {
6112         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6113           return 1;
6114     }
6115
6116   return 0;
6117 }
6118
6119
6120 /* Resolve the argument of a deallocate expression.  The expression must be
6121    a pointer or a full array.  */
6122
6123 static gfc_try
6124 resolve_deallocate_expr (gfc_expr *e)
6125 {
6126   symbol_attribute attr;
6127   int allocatable, pointer, check_intent_in;
6128   gfc_ref *ref;
6129   gfc_symbol *sym;
6130   gfc_component *c;
6131
6132   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6133   check_intent_in = 1;
6134
6135   if (gfc_resolve_expr (e) == FAILURE)
6136     return FAILURE;
6137
6138   if (e->expr_type != EXPR_VARIABLE)
6139     goto bad;
6140
6141   sym = e->symtree->n.sym;
6142
6143   if (sym->ts.type == BT_CLASS)
6144     {
6145       allocatable = CLASS_DATA (sym)->attr.allocatable;
6146       pointer = CLASS_DATA (sym)->attr.class_pointer;
6147     }
6148   else
6149     {
6150       allocatable = sym->attr.allocatable;
6151       pointer = sym->attr.pointer;
6152     }
6153   for (ref = e->ref; ref; ref = ref->next)
6154     {
6155       if (pointer)
6156         check_intent_in = 0;
6157
6158       switch (ref->type)
6159         {
6160         case REF_ARRAY:
6161           if (ref->u.ar.type != AR_FULL)
6162             allocatable = 0;
6163           break;
6164
6165         case REF_COMPONENT:
6166           c = ref->u.c.component;
6167           if (c->ts.type == BT_CLASS)
6168             {
6169               allocatable = CLASS_DATA (c)->attr.allocatable;
6170               pointer = CLASS_DATA (c)->attr.class_pointer;
6171             }
6172           else
6173             {
6174               allocatable = c->attr.allocatable;
6175               pointer = c->attr.pointer;
6176             }
6177           break;
6178
6179         case REF_SUBSTRING:
6180           allocatable = 0;
6181           break;
6182         }
6183     }
6184
6185   attr = gfc_expr_attr (e);
6186
6187   if (allocatable == 0 && attr.pointer == 0)
6188     {
6189     bad:
6190       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6191                  &e->where);
6192       return FAILURE;
6193     }
6194
6195   if (check_intent_in && sym->attr.intent == INTENT_IN)
6196     {
6197       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
6198                  sym->name, &e->where);
6199       return FAILURE;
6200     }
6201
6202   if (e->ts.type == BT_CLASS)
6203     {
6204       /* Only deallocate the DATA component.  */
6205       gfc_add_component_ref (e, "$data");
6206     }
6207
6208   return SUCCESS;
6209 }
6210
6211
6212 /* Returns true if the expression e contains a reference to the symbol sym.  */
6213 static bool
6214 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6215 {
6216   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6217     return true;
6218
6219   return false;
6220 }
6221
6222 bool
6223 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6224 {
6225   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6226 }
6227
6228
6229 /* Given the expression node e for an allocatable/pointer of derived type to be
6230    allocated, get the expression node to be initialized afterwards (needed for
6231    derived types with default initializers, and derived types with allocatable
6232    components that need nullification.)  */
6233
6234 gfc_expr *
6235 gfc_expr_to_initialize (gfc_expr *e)
6236 {
6237   gfc_expr *result;
6238   gfc_ref *ref;
6239   int i;
6240
6241   result = gfc_copy_expr (e);
6242
6243   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6244   for (ref = result->ref; ref; ref = ref->next)
6245     if (ref->type == REF_ARRAY && ref->next == NULL)
6246       {
6247         ref->u.ar.type = AR_FULL;
6248
6249         for (i = 0; i < ref->u.ar.dimen; i++)
6250           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6251
6252         result->rank = ref->u.ar.dimen;
6253         break;
6254       }
6255
6256   return result;
6257 }
6258
6259
6260 /* Used in resolve_allocate_expr to check that a allocation-object and
6261    a source-expr are conformable.  This does not catch all possible 
6262    cases; in particular a runtime checking is needed.  */
6263
6264 static gfc_try
6265 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6266 {
6267   gfc_ref *tail;
6268   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6269   
6270   /* First compare rank.  */
6271   if (tail && e1->rank != tail->u.ar.as->rank)
6272     {
6273       gfc_error ("Source-expr at %L must be scalar or have the "
6274                  "same rank as the allocate-object at %L",
6275                  &e1->where, &e2->where);
6276       return FAILURE;
6277     }
6278
6279   if (e1->shape)
6280     {
6281       int i;
6282       mpz_t s;
6283
6284       mpz_init (s);
6285
6286       for (i = 0; i < e1->rank; i++)
6287         {
6288           if (tail->u.ar.end[i])
6289             {
6290               mpz_set (s, tail->u.ar.end[i]->value.integer);
6291               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6292               mpz_add_ui (s, s, 1);
6293             }
6294           else
6295             {
6296               mpz_set (s, tail->u.ar.start[i]->value.integer);
6297             }
6298
6299           if (mpz_cmp (e1->shape[i], s) != 0)
6300             {
6301               gfc_error ("Source-expr at %L and allocate-object at %L must "
6302                          "have the same shape", &e1->where, &e2->where);
6303               mpz_clear (s);
6304               return FAILURE;
6305             }
6306         }
6307
6308       mpz_clear (s);
6309     }
6310
6311   return SUCCESS;
6312 }
6313
6314
6315 /* Resolve the expression in an ALLOCATE statement, doing the additional
6316    checks to see whether the expression is OK or not.  The expression must
6317    have a trailing array reference that gives the size of the array.  */
6318
6319 static gfc_try
6320 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6321 {
6322   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6323   int codimension;
6324   symbol_attribute attr;
6325   gfc_ref *ref, *ref2;
6326   gfc_array_ref *ar;
6327   gfc_symbol *sym = NULL;
6328   gfc_alloc *a;
6329   gfc_component *c;
6330
6331   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6332   check_intent_in = 1;
6333
6334   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6335      checking of coarrays.  */
6336   for (ref = e->ref; ref; ref = ref->next)
6337     if (ref->next == NULL)
6338       break;
6339
6340   if (ref && ref->type == REF_ARRAY)
6341     ref->u.ar.in_allocate = true;
6342
6343   if (gfc_resolve_expr (e) == FAILURE)
6344     goto failure;
6345
6346   /* Make sure the expression is allocatable or a pointer.  If it is
6347      pointer, the next-to-last reference must be a pointer.  */
6348
6349   ref2 = NULL;
6350   if (e->symtree)
6351     sym = e->symtree->n.sym;
6352
6353   /* Check whether ultimate component is abstract and CLASS.  */
6354   is_abstract = 0;
6355
6356   if (e->expr_type != EXPR_VARIABLE)
6357     {
6358       allocatable = 0;
6359       attr = gfc_expr_attr (e);
6360       pointer = attr.pointer;
6361       dimension = attr.dimension;
6362       codimension = attr.codimension;
6363     }
6364   else
6365     {
6366       if (sym->ts.type == BT_CLASS)
6367         {
6368           allocatable = CLASS_DATA (sym)->attr.allocatable;
6369           pointer = CLASS_DATA (sym)->attr.class_pointer;
6370           dimension = CLASS_DATA (sym)->attr.dimension;
6371           codimension = CLASS_DATA (sym)->attr.codimension;
6372           is_abstract = CLASS_DATA (sym)->attr.abstract;
6373         }
6374       else
6375         {
6376           allocatable = sym->attr.allocatable;
6377           pointer = sym->attr.pointer;
6378           dimension = sym->attr.dimension;
6379           codimension = sym->attr.codimension;
6380         }
6381
6382       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6383         {
6384           if (pointer)
6385             check_intent_in = 0;
6386
6387           switch (ref->type)
6388             {
6389               case REF_ARRAY:
6390                 if (ref->next != NULL)
6391                   pointer = 0;
6392                 break;
6393
6394               case REF_COMPONENT:
6395                 /* F2008, C644.  */
6396                 if (gfc_is_coindexed (e))
6397                   {
6398                     gfc_error ("Coindexed allocatable object at %L",
6399                                &e->where);
6400                     goto failure;
6401                   }
6402
6403                 c = ref->u.c.component;
6404                 if (c->ts.type == BT_CLASS)
6405                   {
6406                     allocatable = CLASS_DATA (c)->attr.allocatable;
6407                     pointer = CLASS_DATA (c)->attr.class_pointer;
6408                     dimension = CLASS_DATA (c)->attr.dimension;
6409                     codimension = CLASS_DATA (c)->attr.codimension;
6410                     is_abstract = CLASS_DATA (c)->attr.abstract;
6411                   }
6412                 else
6413                   {
6414                     allocatable = c->attr.allocatable;
6415                     pointer = c->attr.pointer;
6416                     dimension = c->attr.dimension;
6417                     codimension = c->attr.codimension;
6418                     is_abstract = c->attr.abstract;
6419                   }
6420                 break;
6421
6422               case REF_SUBSTRING:
6423                 allocatable = 0;
6424                 pointer = 0;
6425                 break;
6426             }
6427         }
6428     }
6429
6430   if (allocatable == 0 && pointer == 0)
6431     {
6432       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6433                  &e->where);
6434       goto failure;
6435     }
6436
6437   /* Some checks for the SOURCE tag.  */
6438   if (code->expr3)
6439     {
6440       /* Check F03:C631.  */
6441       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6442         {
6443           gfc_error ("Type of entity at %L is type incompatible with "
6444                       "source-expr at %L", &e->where, &code->expr3->where);
6445           goto failure;
6446         }
6447
6448       /* Check F03:C632 and restriction following Note 6.18.  */
6449       if (code->expr3->rank > 0
6450           && conformable_arrays (code->expr3, e) == FAILURE)
6451         goto failure;
6452
6453       /* Check F03:C633.  */
6454       if (code->expr3->ts.kind != e->ts.kind)
6455         {
6456           gfc_error ("The allocate-object at %L and the source-expr at %L "
6457                       "shall have the same kind type parameter",
6458                       &e->where, &code->expr3->where);
6459           goto failure;
6460         }
6461     }
6462
6463   /* Check F08:C629.  */
6464   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6465       && !code->expr3)
6466     {
6467       gcc_assert (e->ts.type == BT_CLASS);
6468       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6469                  "type-spec or source-expr", sym->name, &e->where);
6470       goto failure;
6471     }
6472
6473   if (check_intent_in && sym->attr.intent == INTENT_IN)
6474     {
6475       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6476                  sym->name, &e->where);
6477       goto failure;
6478     }
6479     
6480   if (!code->expr3 || code->expr3->mold)
6481     {
6482       /* Add default initializer for those derived types that need them.  */
6483       gfc_expr *init_e = NULL;
6484       gfc_typespec ts;
6485
6486       if (code->ext.alloc.ts.type == BT_DERIVED)
6487         ts = code->ext.alloc.ts;
6488       else if (code->expr3)
6489         ts = code->expr3->ts;
6490       else
6491         ts = e->ts;
6492
6493       if (ts.type == BT_DERIVED)
6494         init_e = gfc_default_initializer (&ts);
6495       /* FIXME: Use default init of dynamic type (cf. PR 44541).  */
6496       else if (e->ts.type == BT_CLASS)
6497         init_e = gfc_default_initializer (&ts.u.derived->components->ts);
6498
6499       if (init_e)
6500         {
6501           gfc_code *init_st = gfc_get_code ();
6502           init_st->loc = code->loc;
6503           init_st->op = EXEC_INIT_ASSIGN;
6504           init_st->expr1 = gfc_expr_to_initialize (e);
6505           init_st->expr2 = init_e;
6506           init_st->next = code->next;
6507           code->next = init_st;
6508         }
6509     }
6510
6511   if (pointer || (dimension == 0 && codimension == 0))
6512     goto success;
6513
6514   /* Make sure the next-to-last reference node is an array specification.  */
6515
6516   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6517       || (dimension && ref2->u.ar.dimen == 0))
6518     {
6519       gfc_error ("Array specification required in ALLOCATE statement "
6520                  "at %L", &e->where);
6521       goto failure;
6522     }
6523
6524   /* Make sure that the array section reference makes sense in the
6525     context of an ALLOCATE specification.  */
6526
6527   ar = &ref2->u.ar;
6528
6529   if (codimension && ar->codimen == 0)
6530     {
6531       gfc_error ("Coarray specification required in ALLOCATE statement "
6532                  "at %L", &e->where);
6533       goto failure;
6534     }
6535
6536   for (i = 0; i < ar->dimen; i++)
6537     {
6538       if (ref2->u.ar.type == AR_ELEMENT)
6539         goto check_symbols;
6540
6541       switch (ar->dimen_type[i])
6542         {
6543         case DIMEN_ELEMENT:
6544           break;
6545
6546         case DIMEN_RANGE:
6547           if (ar->start[i] != NULL
6548               && ar->end[i] != NULL
6549               && ar->stride[i] == NULL)
6550             break;
6551
6552           /* Fall Through...  */
6553
6554         case DIMEN_UNKNOWN:
6555         case DIMEN_VECTOR:
6556         case DIMEN_STAR:
6557           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6558                      &e->where);
6559           goto failure;
6560         }
6561
6562 check_symbols:
6563       for (a = code->ext.alloc.list; a; a = a->next)
6564         {
6565           sym = a->expr->symtree->n.sym;
6566
6567           /* TODO - check derived type components.  */
6568           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6569             continue;
6570
6571           if ((ar->start[i] != NULL
6572                && gfc_find_sym_in_expr (sym, ar->start[i]))
6573               || (ar->end[i] != NULL
6574                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6575             {
6576               gfc_error ("'%s' must not appear in the array specification at "
6577                          "%L in the same ALLOCATE statement where it is "
6578                          "itself allocated", sym->name, &ar->where);
6579               goto failure;
6580             }
6581         }
6582     }
6583
6584   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6585     {
6586       if (ar->dimen_type[i] == DIMEN_ELEMENT
6587           || ar->dimen_type[i] == DIMEN_RANGE)
6588         {
6589           if (i == (ar->dimen + ar->codimen - 1))
6590             {
6591               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6592                          "statement at %L", &e->where);
6593               goto failure;
6594             }
6595           break;
6596         }
6597
6598       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6599           && ar->stride[i] == NULL)
6600         break;
6601
6602       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6603                  &e->where);
6604       goto failure;
6605     }
6606
6607   if (codimension && ar->as->rank == 0)
6608     {
6609       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6610                  "at %L", &e->where);
6611       goto failure;
6612     }
6613
6614 success:
6615   return SUCCESS;
6616
6617 failure:
6618   return FAILURE;
6619 }
6620
6621 static void
6622 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6623 {
6624   gfc_expr *stat, *errmsg, *pe, *qe;
6625   gfc_alloc *a, *p, *q;
6626
6627   stat = code->expr1 ? code->expr1 : NULL;
6628
6629   errmsg = code->expr2 ? code->expr2 : NULL;
6630
6631   /* Check the stat variable.  */
6632   if (stat)
6633     {
6634       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6635         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6636                    stat->symtree->n.sym->name, &stat->where);
6637
6638       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6639         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6640                    &stat->where);
6641
6642       if ((stat->ts.type != BT_INTEGER
6643            && !(stat->ref && (stat->ref->type == REF_ARRAY
6644                               || stat->ref->type == REF_COMPONENT)))
6645           || stat->rank > 0)
6646         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6647                    "variable", &stat->where);
6648
6649       for (p = code->ext.alloc.list; p; p = p->next)
6650         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6651           {
6652             gfc_ref *ref1, *ref2;
6653             bool found = true;
6654
6655             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
6656                  ref1 = ref1->next, ref2 = ref2->next)
6657               {
6658                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6659                   continue;
6660                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6661                   {
6662                     found = false;
6663                     break;
6664                   }
6665               }
6666
6667             if (found)
6668               {
6669                 gfc_error ("Stat-variable at %L shall not be %sd within "
6670                            "the same %s statement", &stat->where, fcn, fcn);
6671                 break;
6672               }
6673           }
6674     }
6675
6676   /* Check the errmsg variable.  */
6677   if (errmsg)
6678     {
6679       if (!stat)
6680         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6681                      &errmsg->where);
6682
6683       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6684         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6685                    errmsg->symtree->n.sym->name, &errmsg->where);
6686
6687       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6688         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6689                    &errmsg->where);
6690
6691       if ((errmsg->ts.type != BT_CHARACTER
6692            && !(errmsg->ref
6693                 && (errmsg->ref->type == REF_ARRAY
6694                     || errmsg->ref->type == REF_COMPONENT)))
6695           || errmsg->rank > 0 )
6696         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6697                    "variable", &errmsg->where);
6698
6699       for (p = code->ext.alloc.list; p; p = p->next)
6700         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6701           {
6702             gfc_ref *ref1, *ref2;
6703             bool found = true;
6704
6705             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
6706                  ref1 = ref1->next, ref2 = ref2->next)
6707               {
6708                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6709                   continue;
6710                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6711                   {
6712                     found = false;
6713                     break;
6714                   }
6715               }
6716
6717             if (found)
6718               {
6719                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
6720                            "the same %s statement", &errmsg->where, fcn, fcn);
6721                 break;
6722               }
6723           }
6724     }
6725
6726   /* Check that an allocate-object appears only once in the statement.  
6727      FIXME: Checking derived types is disabled.  */
6728   for (p = code->ext.alloc.list; p; p = p->next)
6729     {
6730       pe = p->expr;
6731       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6732            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6733         {
6734           for (q = p->next; q; q = q->next)
6735             {
6736               qe = q->expr;
6737               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6738                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6739                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6740                 gfc_error ("Allocate-object at %L also appears at %L",
6741                            &pe->where, &qe->where);
6742             }
6743         }
6744     }
6745
6746   if (strcmp (fcn, "ALLOCATE") == 0)
6747     {
6748       for (a = code->ext.alloc.list; a; a = a->next)
6749         resolve_allocate_expr (a->expr, code);
6750     }
6751   else
6752     {
6753       for (a = code->ext.alloc.list; a; a = a->next)
6754         resolve_deallocate_expr (a->expr);
6755     }
6756 }
6757
6758
6759 /************ SELECT CASE resolution subroutines ************/
6760
6761 /* Callback function for our mergesort variant.  Determines interval
6762    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6763    op1 > op2.  Assumes we're not dealing with the default case.  
6764    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6765    There are nine situations to check.  */
6766
6767 static int
6768 compare_cases (const gfc_case *op1, const gfc_case *op2)
6769 {
6770   int retval;
6771
6772   if (op1->low == NULL) /* op1 = (:L)  */
6773     {
6774       /* op2 = (:N), so overlap.  */
6775       retval = 0;
6776       /* op2 = (M:) or (M:N),  L < M  */
6777       if (op2->low != NULL
6778           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6779         retval = -1;
6780     }
6781   else if (op1->high == NULL) /* op1 = (K:)  */
6782     {
6783       /* op2 = (M:), so overlap.  */
6784       retval = 0;
6785       /* op2 = (:N) or (M:N), K > N  */
6786       if (op2->high != NULL
6787           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6788         retval = 1;
6789     }
6790   else /* op1 = (K:L)  */
6791     {
6792       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6793         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6794                  ? 1 : 0;
6795       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6796         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6797                  ? -1 : 0;
6798       else                      /* op2 = (M:N)  */
6799         {
6800           retval =  0;
6801           /* L < M  */
6802           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6803             retval =  -1;
6804           /* K > N  */
6805           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6806             retval =  1;
6807         }
6808     }
6809
6810   return retval;
6811 }
6812
6813
6814 /* Merge-sort a double linked case list, detecting overlap in the
6815    process.  LIST is the head of the double linked case list before it
6816    is sorted.  Returns the head of the sorted list if we don't see any
6817    overlap, or NULL otherwise.  */
6818
6819 static gfc_case *
6820 check_case_overlap (gfc_case *list)
6821 {
6822   gfc_case *p, *q, *e, *tail;
6823   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6824
6825   /* If the passed list was empty, return immediately.  */
6826   if (!list)
6827     return NULL;
6828
6829   overlap_seen = 0;
6830   insize = 1;
6831
6832   /* Loop unconditionally.  The only exit from this loop is a return
6833      statement, when we've finished sorting the case list.  */
6834   for (;;)
6835     {
6836       p = list;
6837       list = NULL;
6838       tail = NULL;
6839
6840       /* Count the number of merges we do in this pass.  */
6841       nmerges = 0;
6842
6843       /* Loop while there exists a merge to be done.  */
6844       while (p)
6845         {
6846           int i;
6847
6848           /* Count this merge.  */
6849           nmerges++;
6850
6851           /* Cut the list in two pieces by stepping INSIZE places
6852              forward in the list, starting from P.  */
6853           psize = 0;
6854           q = p;
6855           for (i = 0; i < insize; i++)
6856             {
6857               psize++;
6858               q = q->right;
6859               if (!q)
6860                 break;
6861             }
6862           qsize = insize;
6863
6864           /* Now we have two lists.  Merge them!  */
6865           while (psize > 0 || (qsize > 0 && q != NULL))
6866             {
6867               /* See from which the next case to merge comes from.  */
6868               if (psize == 0)
6869                 {
6870                   /* P is empty so the next case must come from Q.  */
6871                   e = q;
6872                   q = q->right;
6873                   qsize--;
6874                 }
6875               else if (qsize == 0 || q == NULL)
6876                 {
6877                   /* Q is empty.  */
6878                   e = p;
6879                   p = p->right;
6880                   psize--;
6881                 }
6882               else
6883                 {
6884                   cmp = compare_cases (p, q);
6885                   if (cmp < 0)
6886                     {
6887                       /* The whole case range for P is less than the
6888                          one for Q.  */
6889                       e = p;
6890                       p = p->right;
6891                       psize--;
6892                     }
6893                   else if (cmp > 0)
6894                     {
6895                       /* The whole case range for Q is greater than
6896                          the case range for P.  */
6897                       e = q;
6898                       q = q->right;
6899                       qsize--;
6900                     }
6901                   else
6902                     {
6903                       /* The cases overlap, or they are the same
6904                          element in the list.  Either way, we must
6905                          issue an error and get the next case from P.  */
6906                       /* FIXME: Sort P and Q by line number.  */
6907                       gfc_error ("CASE label at %L overlaps with CASE "
6908                                  "label at %L", &p->where, &q->where);
6909                       overlap_seen = 1;
6910                       e = p;
6911                       p = p->right;
6912                       psize--;
6913                     }
6914                 }
6915
6916                 /* Add the next element to the merged list.  */
6917               if (tail)
6918                 tail->right = e;
6919               else
6920                 list = e;
6921               e->left = tail;
6922               tail = e;
6923             }
6924
6925           /* P has now stepped INSIZE places along, and so has Q.  So
6926              they're the same.  */
6927           p = q;
6928         }
6929       tail->right = NULL;
6930
6931       /* If we have done only one merge or none at all, we've
6932          finished sorting the cases.  */
6933       if (nmerges <= 1)
6934         {
6935           if (!overlap_seen)
6936             return list;
6937           else
6938             return NULL;
6939         }
6940
6941       /* Otherwise repeat, merging lists twice the size.  */
6942       insize *= 2;
6943     }
6944 }
6945
6946
6947 /* Check to see if an expression is suitable for use in a CASE statement.
6948    Makes sure that all case expressions are scalar constants of the same
6949    type.  Return FAILURE if anything is wrong.  */
6950
6951 static gfc_try
6952 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6953 {
6954   if (e == NULL) return SUCCESS;
6955
6956   if (e->ts.type != case_expr->ts.type)
6957     {
6958       gfc_error ("Expression in CASE statement at %L must be of type %s",
6959                  &e->where, gfc_basic_typename (case_expr->ts.type));
6960       return FAILURE;
6961     }
6962
6963   /* C805 (R808) For a given case-construct, each case-value shall be of
6964      the same type as case-expr.  For character type, length differences
6965      are allowed, but the kind type parameters shall be the same.  */
6966
6967   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6968     {
6969       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6970                  &e->where, case_expr->ts.kind);
6971       return FAILURE;
6972     }
6973
6974   /* Convert the case value kind to that of case expression kind,
6975      if needed */
6976
6977   if (e->ts.kind != case_expr->ts.kind)
6978     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6979
6980   if (e->rank != 0)
6981     {
6982       gfc_error ("Expression in CASE statement at %L must be scalar",
6983                  &e->where);
6984       return FAILURE;
6985     }
6986
6987   return SUCCESS;
6988 }
6989
6990
6991 /* Given a completely parsed select statement, we:
6992
6993      - Validate all expressions and code within the SELECT.
6994      - Make sure that the selection expression is not of the wrong type.
6995      - Make sure that no case ranges overlap.
6996      - Eliminate unreachable cases and unreachable code resulting from
6997        removing case labels.
6998
6999    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7000    they are a hassle for code generation, and to prevent that, we just
7001    cut them out here.  This is not necessary for overlapping cases
7002    because they are illegal and we never even try to generate code.
7003
7004    We have the additional caveat that a SELECT construct could have
7005    been a computed GOTO in the source code. Fortunately we can fairly
7006    easily work around that here: The case_expr for a "real" SELECT CASE
7007    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7008    we have to do is make sure that the case_expr is a scalar integer
7009    expression.  */
7010
7011 static void
7012 resolve_select (gfc_code *code)
7013 {
7014   gfc_code *body;
7015   gfc_expr *case_expr;
7016   gfc_case *cp, *default_case, *tail, *head;
7017   int seen_unreachable;
7018   int seen_logical;
7019   int ncases;
7020   bt type;
7021   gfc_try t;
7022
7023   if (code->expr1 == NULL)
7024     {
7025       /* This was actually a computed GOTO statement.  */
7026       case_expr = code->expr2;
7027       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7028         gfc_error ("Selection expression in computed GOTO statement "
7029                    "at %L must be a scalar integer expression",
7030                    &case_expr->where);
7031
7032       /* Further checking is not necessary because this SELECT was built
7033          by the compiler, so it should always be OK.  Just move the
7034          case_expr from expr2 to expr so that we can handle computed
7035          GOTOs as normal SELECTs from here on.  */
7036       code->expr1 = code->expr2;
7037       code->expr2 = NULL;
7038       return;
7039     }
7040
7041   case_expr = code->expr1;
7042
7043   type = case_expr->ts.type;
7044   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7045     {
7046       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7047                  &case_expr->where, gfc_typename (&case_expr->ts));
7048
7049       /* Punt. Going on here just produce more garbage error messages.  */
7050       return;
7051     }
7052
7053   if (case_expr->rank != 0)
7054     {
7055       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7056                  "expression", &case_expr->where);
7057
7058       /* Punt.  */
7059       return;
7060     }
7061
7062
7063   /* Raise a warning if an INTEGER case value exceeds the range of
7064      the case-expr. Later, all expressions will be promoted to the
7065      largest kind of all case-labels.  */
7066
7067   if (type == BT_INTEGER)
7068     for (body = code->block; body; body = body->block)
7069       for (cp = body->ext.case_list; cp; cp = cp->next)
7070         {
7071           if (cp->low
7072               && gfc_check_integer_range (cp->low->value.integer,
7073                                           case_expr->ts.kind) != ARITH_OK)
7074             gfc_warning ("Expression in CASE statement at %L is "
7075                          "not in the range of %s", &cp->low->where,
7076                          gfc_typename (&case_expr->ts));
7077
7078           if (cp->high
7079               && cp->low != cp->high
7080               && gfc_check_integer_range (cp->high->value.integer,
7081                                           case_expr->ts.kind) != ARITH_OK)
7082             gfc_warning ("Expression in CASE statement at %L is "
7083                          "not in the range of %s", &cp->high->where,
7084                          gfc_typename (&case_expr->ts));
7085         }
7086
7087   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7088      of the SELECT CASE expression and its CASE values.  Walk the lists
7089      of case values, and if we find a mismatch, promote case_expr to
7090      the appropriate kind.  */
7091
7092   if (type == BT_LOGICAL || type == BT_INTEGER)
7093     {
7094       for (body = code->block; body; body = body->block)
7095         {
7096           /* Walk the case label list.  */
7097           for (cp = body->ext.case_list; cp; cp = cp->next)
7098             {
7099               /* Intercept the DEFAULT case.  It does not have a kind.  */
7100               if (cp->low == NULL && cp->high == NULL)
7101                 continue;
7102
7103               /* Unreachable case ranges are discarded, so ignore.  */
7104               if (cp->low != NULL && cp->high != NULL
7105                   && cp->low != cp->high
7106                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7107                 continue;
7108
7109               if (cp->low != NULL
7110                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7111                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7112
7113               if (cp->high != NULL
7114                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7115                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7116             }
7117          }
7118     }
7119
7120   /* Assume there is no DEFAULT case.  */
7121   default_case = NULL;
7122   head = tail = NULL;
7123   ncases = 0;
7124   seen_logical = 0;
7125
7126   for (body = code->block; body; body = body->block)
7127     {
7128       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7129       t = SUCCESS;
7130       seen_unreachable = 0;
7131
7132       /* Walk the case label list, making sure that all case labels
7133          are legal.  */
7134       for (cp = body->ext.case_list; cp; cp = cp->next)
7135         {
7136           /* Count the number of cases in the whole construct.  */
7137           ncases++;
7138
7139           /* Intercept the DEFAULT case.  */
7140           if (cp->low == NULL && cp->high == NULL)
7141             {
7142               if (default_case != NULL)
7143                 {
7144                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7145                              "by a second DEFAULT CASE at %L",
7146                              &default_case->where, &cp->where);
7147                   t = FAILURE;
7148                   break;
7149                 }
7150               else
7151                 {
7152                   default_case = cp;
7153                   continue;
7154                 }
7155             }
7156
7157           /* Deal with single value cases and case ranges.  Errors are
7158              issued from the validation function.  */
7159           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7160               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7161             {
7162               t = FAILURE;
7163               break;
7164             }
7165
7166           if (type == BT_LOGICAL
7167               && ((cp->low == NULL || cp->high == NULL)
7168                   || cp->low != cp->high))
7169             {
7170               gfc_error ("Logical range in CASE statement at %L is not "
7171                          "allowed", &cp->low->where);
7172               t = FAILURE;
7173               break;
7174             }
7175
7176           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7177             {
7178               int value;
7179               value = cp->low->value.logical == 0 ? 2 : 1;
7180               if (value & seen_logical)
7181                 {
7182                   gfc_error ("Constant logical value in CASE statement "
7183                              "is repeated at %L",
7184                              &cp->low->where);
7185                   t = FAILURE;
7186                   break;
7187                 }
7188               seen_logical |= value;
7189             }
7190
7191           if (cp->low != NULL && cp->high != NULL
7192               && cp->low != cp->high
7193               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7194             {
7195               if (gfc_option.warn_surprising)
7196                 gfc_warning ("Range specification at %L can never "
7197                              "be matched", &cp->where);
7198
7199               cp->unreachable = 1;
7200               seen_unreachable = 1;
7201             }
7202           else
7203             {
7204               /* If the case range can be matched, it can also overlap with
7205                  other cases.  To make sure it does not, we put it in a
7206                  double linked list here.  We sort that with a merge sort
7207                  later on to detect any overlapping cases.  */
7208               if (!head)
7209                 {
7210                   head = tail = cp;
7211                   head->right = head->left = NULL;
7212                 }
7213               else
7214                 {
7215                   tail->right = cp;
7216                   tail->right->left = tail;
7217                   tail = tail->right;
7218                   tail->right = NULL;
7219                 }
7220             }
7221         }
7222
7223       /* It there was a failure in the previous case label, give up
7224          for this case label list.  Continue with the next block.  */
7225       if (t == FAILURE)
7226         continue;
7227
7228       /* See if any case labels that are unreachable have been seen.
7229          If so, we eliminate them.  This is a bit of a kludge because
7230          the case lists for a single case statement (label) is a
7231          single forward linked lists.  */
7232       if (seen_unreachable)
7233       {
7234         /* Advance until the first case in the list is reachable.  */
7235         while (body->ext.case_list != NULL
7236                && body->ext.case_list->unreachable)
7237           {
7238             gfc_case *n = body->ext.case_list;
7239             body->ext.case_list = body->ext.case_list->next;
7240             n->next = NULL;
7241             gfc_free_case_list (n);
7242           }
7243
7244         /* Strip all other unreachable cases.  */
7245         if (body->ext.case_list)
7246           {
7247             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7248               {
7249                 if (cp->next->unreachable)
7250                   {
7251                     gfc_case *n = cp->next;
7252                     cp->next = cp->next->next;
7253                     n->next = NULL;
7254                     gfc_free_case_list (n);
7255                   }
7256               }
7257           }
7258       }
7259     }
7260
7261   /* See if there were overlapping cases.  If the check returns NULL,
7262      there was overlap.  In that case we don't do anything.  If head
7263      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7264      then used during code generation for SELECT CASE constructs with
7265      a case expression of a CHARACTER type.  */
7266   if (head)
7267     {
7268       head = check_case_overlap (head);
7269
7270       /* Prepend the default_case if it is there.  */
7271       if (head != NULL && default_case)
7272         {
7273           default_case->left = NULL;
7274           default_case->right = head;
7275           head->left = default_case;
7276         }
7277     }
7278
7279   /* Eliminate dead blocks that may be the result if we've seen
7280      unreachable case labels for a block.  */
7281   for (body = code; body && body->block; body = body->block)
7282     {
7283       if (body->block->ext.case_list == NULL)
7284         {
7285           /* Cut the unreachable block from the code chain.  */
7286           gfc_code *c = body->block;
7287           body->block = c->block;
7288
7289           /* Kill the dead block, but not the blocks below it.  */
7290           c->block = NULL;
7291           gfc_free_statements (c);
7292         }
7293     }
7294
7295   /* More than two cases is legal but insane for logical selects.
7296      Issue a warning for it.  */
7297   if (gfc_option.warn_surprising && type == BT_LOGICAL
7298       && ncases > 2)
7299     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7300                  &code->loc);
7301 }
7302
7303
7304 /* Check if a derived type is extensible.  */
7305
7306 bool
7307 gfc_type_is_extensible (gfc_symbol *sym)
7308 {
7309   return !(sym->attr.is_bind_c || sym->attr.sequence);
7310 }
7311
7312
7313 /* Resolve a SELECT TYPE statement.  */
7314
7315 static void
7316 resolve_select_type (gfc_code *code)
7317 {
7318   gfc_symbol *selector_type;
7319   gfc_code *body, *new_st, *if_st, *tail;
7320   gfc_code *class_is = NULL, *default_case = NULL;
7321   gfc_case *c;
7322   gfc_symtree *st;
7323   char name[GFC_MAX_SYMBOL_LEN];
7324   gfc_namespace *ns;
7325   int error = 0;
7326
7327   ns = code->ext.block.ns;
7328   gfc_resolve (ns);
7329
7330   /* Check for F03:C813.  */
7331   if (code->expr1->ts.type != BT_CLASS
7332       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7333     {
7334       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7335                  "at %L", &code->loc);
7336       return;
7337     }
7338
7339   if (code->expr2)
7340     {
7341       if (code->expr1->symtree->n.sym->attr.untyped)
7342         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7343       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7344     }
7345   else
7346     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7347
7348   /* Loop over TYPE IS / CLASS IS cases.  */
7349   for (body = code->block; body; body = body->block)
7350     {
7351       c = body->ext.case_list;
7352
7353       /* Check F03:C815.  */
7354       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7355           && !gfc_type_is_extensible (c->ts.u.derived))
7356         {
7357           gfc_error ("Derived type '%s' at %L must be extensible",
7358                      c->ts.u.derived->name, &c->where);
7359           error++;
7360           continue;
7361         }
7362
7363       /* Check F03:C816.  */
7364       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7365           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7366         {
7367           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7368                      c->ts.u.derived->name, &c->where, selector_type->name);
7369           error++;
7370           continue;
7371         }
7372
7373       /* Intercept the DEFAULT case.  */
7374       if (c->ts.type == BT_UNKNOWN)
7375         {
7376           /* Check F03:C818.  */
7377           if (default_case)
7378             {
7379               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7380                          "by a second DEFAULT CASE at %L",
7381                          &default_case->ext.case_list->where, &c->where);
7382               error++;
7383               continue;
7384             }
7385           else
7386             default_case = body;
7387         }
7388     }
7389     
7390   if (error>0)
7391     return;
7392
7393   if (code->expr2)
7394     {
7395       /* Insert assignment for selector variable.  */
7396       new_st = gfc_get_code ();
7397       new_st->op = EXEC_ASSIGN;
7398       new_st->expr1 = gfc_copy_expr (code->expr1);
7399       new_st->expr2 = gfc_copy_expr (code->expr2);
7400       ns->code = new_st;
7401     }
7402
7403   /* Put SELECT TYPE statement inside a BLOCK.  */
7404   new_st = gfc_get_code ();
7405   new_st->op = code->op;
7406   new_st->expr1 = code->expr1;
7407   new_st->expr2 = code->expr2;
7408   new_st->block = code->block;
7409   if (!ns->code)
7410     ns->code = new_st;
7411   else
7412     ns->code->next = new_st;
7413   code->op = EXEC_BLOCK;
7414   code->ext.block.assoc = NULL;
7415   code->expr1 = code->expr2 =  NULL;
7416   code->block = NULL;
7417
7418   code = new_st;
7419
7420   /* Transform to EXEC_SELECT.  */
7421   code->op = EXEC_SELECT;
7422   gfc_add_component_ref (code->expr1, "$vptr");
7423   gfc_add_component_ref (code->expr1, "$hash");
7424
7425   /* Loop over TYPE IS / CLASS IS cases.  */
7426   for (body = code->block; body; body = body->block)
7427     {
7428       c = body->ext.case_list;
7429
7430       if (c->ts.type == BT_DERIVED)
7431         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7432                                              c->ts.u.derived->hash_value);
7433
7434       else if (c->ts.type == BT_UNKNOWN)
7435         continue;
7436
7437       /* Assign temporary to selector.  */
7438       if (c->ts.type == BT_CLASS)
7439         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7440       else
7441         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7442       st = gfc_find_symtree (ns->sym_root, name);
7443       new_st = gfc_get_code ();
7444       new_st->expr1 = gfc_get_variable_expr (st);
7445       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7446       if (c->ts.type == BT_DERIVED)
7447         {
7448           new_st->op = EXEC_POINTER_ASSIGN;
7449           gfc_add_component_ref (new_st->expr2, "$data");
7450         }
7451       else
7452         new_st->op = EXEC_POINTER_ASSIGN;
7453       new_st->next = body->next;
7454       body->next = new_st;
7455     }
7456     
7457   /* Take out CLASS IS cases for separate treatment.  */
7458   body = code;
7459   while (body && body->block)
7460     {
7461       if (body->block->ext.case_list->ts.type == BT_CLASS)
7462         {
7463           /* Add to class_is list.  */
7464           if (class_is == NULL)
7465             { 
7466               class_is = body->block;
7467               tail = class_is;
7468             }
7469           else
7470             {
7471               for (tail = class_is; tail->block; tail = tail->block) ;
7472               tail->block = body->block;
7473               tail = tail->block;
7474             }
7475           /* Remove from EXEC_SELECT list.  */
7476           body->block = body->block->block;
7477           tail->block = NULL;
7478         }
7479       else
7480         body = body->block;
7481     }
7482
7483   if (class_is)
7484     {
7485       gfc_symbol *vtab;
7486       
7487       if (!default_case)
7488         {
7489           /* Add a default case to hold the CLASS IS cases.  */
7490           for (tail = code; tail->block; tail = tail->block) ;
7491           tail->block = gfc_get_code ();
7492           tail = tail->block;
7493           tail->op = EXEC_SELECT_TYPE;
7494           tail->ext.case_list = gfc_get_case ();
7495           tail->ext.case_list->ts.type = BT_UNKNOWN;
7496           tail->next = NULL;
7497           default_case = tail;
7498         }
7499
7500       /* More than one CLASS IS block?  */
7501       if (class_is->block)
7502         {
7503           gfc_code **c1,*c2;
7504           bool swapped;
7505           /* Sort CLASS IS blocks by extension level.  */
7506           do
7507             {
7508               swapped = false;
7509               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7510                 {
7511                   c2 = (*c1)->block;
7512                   /* F03:C817 (check for doubles).  */
7513                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7514                       == c2->ext.case_list->ts.u.derived->hash_value)
7515                     {
7516                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7517                                  "statement at %L", &c2->ext.case_list->where);
7518                       return;
7519                     }
7520                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7521                       < c2->ext.case_list->ts.u.derived->attr.extension)
7522                     {
7523                       /* Swap.  */
7524                       (*c1)->block = c2->block;
7525                       c2->block = *c1;
7526                       *c1 = c2;
7527                       swapped = true;
7528                     }
7529                 }
7530             }
7531           while (swapped);
7532         }
7533         
7534       /* Generate IF chain.  */
7535       if_st = gfc_get_code ();
7536       if_st->op = EXEC_IF;
7537       new_st = if_st;
7538       for (body = class_is; body; body = body->block)
7539         {
7540           new_st->block = gfc_get_code ();
7541           new_st = new_st->block;
7542           new_st->op = EXEC_IF;
7543           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7544           new_st->expr1 = gfc_get_expr ();
7545           new_st->expr1->expr_type = EXPR_FUNCTION;
7546           new_st->expr1->ts.type = BT_LOGICAL;
7547           new_st->expr1->ts.kind = 4;
7548           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7549           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7550           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7551           /* Set up arguments.  */
7552           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7553           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7554           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7555           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7556           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7557           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7558           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7559           new_st->next = body->next;
7560         }
7561         if (default_case->next)
7562           {
7563             new_st->block = gfc_get_code ();
7564             new_st = new_st->block;
7565             new_st->op = EXEC_IF;
7566             new_st->next = default_case->next;
7567           }
7568           
7569         /* Replace CLASS DEFAULT code by the IF chain.  */
7570         default_case->next = if_st;
7571     }
7572
7573   resolve_select (code);
7574
7575 }
7576
7577
7578 /* Resolve a transfer statement. This is making sure that:
7579    -- a derived type being transferred has only non-pointer components
7580    -- a derived type being transferred doesn't have private components, unless 
7581       it's being transferred from the module where the type was defined
7582    -- we're not trying to transfer a whole assumed size array.  */
7583
7584 static void
7585 resolve_transfer (gfc_code *code)
7586 {
7587   gfc_typespec *ts;
7588   gfc_symbol *sym;
7589   gfc_ref *ref;
7590   gfc_expr *exp;
7591
7592   exp = code->expr1;
7593
7594   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7595     return;
7596
7597   sym = exp->symtree->n.sym;
7598   ts = &sym->ts;
7599
7600   /* Go to actual component transferred.  */
7601   for (ref = code->expr1->ref; ref; ref = ref->next)
7602     if (ref->type == REF_COMPONENT)
7603       ts = &ref->u.c.component->ts;
7604
7605   if (ts->type == BT_DERIVED)
7606     {
7607       /* Check that transferred derived type doesn't contain POINTER
7608          components.  */
7609       if (ts->u.derived->attr.pointer_comp)
7610         {
7611           gfc_error ("Data transfer element at %L cannot have "
7612                      "POINTER components", &code->loc);
7613           return;
7614         }
7615
7616       if (ts->u.derived->attr.alloc_comp)
7617         {
7618           gfc_error ("Data transfer element at %L cannot have "
7619                      "ALLOCATABLE components", &code->loc);
7620           return;
7621         }
7622
7623       if (derived_inaccessible (ts->u.derived))
7624         {
7625           gfc_error ("Data transfer element at %L cannot have "
7626                      "PRIVATE components",&code->loc);
7627           return;
7628         }
7629     }
7630
7631   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7632       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7633     {
7634       gfc_error ("Data transfer element at %L cannot be a full reference to "
7635                  "an assumed-size array", &code->loc);
7636       return;
7637     }
7638 }
7639
7640
7641 /*********** Toplevel code resolution subroutines ***********/
7642
7643 /* Find the set of labels that are reachable from this block.  We also
7644    record the last statement in each block.  */
7645      
7646 static void
7647 find_reachable_labels (gfc_code *block)
7648 {
7649   gfc_code *c;
7650
7651   if (!block)
7652     return;
7653
7654   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7655
7656   /* Collect labels in this block.  We don't keep those corresponding
7657      to END {IF|SELECT}, these are checked in resolve_branch by going
7658      up through the code_stack.  */
7659   for (c = block; c; c = c->next)
7660     {
7661       if (c->here && c->op != EXEC_END_BLOCK)
7662         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7663     }
7664
7665   /* Merge with labels from parent block.  */
7666   if (cs_base->prev)
7667     {
7668       gcc_assert (cs_base->prev->reachable_labels);
7669       bitmap_ior_into (cs_base->reachable_labels,
7670                        cs_base->prev->reachable_labels);
7671     }
7672 }
7673
7674
7675 static void
7676 resolve_sync (gfc_code *code)
7677 {
7678   /* Check imageset. The * case matches expr1 == NULL.  */
7679   if (code->expr1)
7680     {
7681       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
7682         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
7683                    "INTEGER expression", &code->expr1->where);
7684       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
7685           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
7686         gfc_error ("Imageset argument at %L must between 1 and num_images()",
7687                    &code->expr1->where);
7688       else if (code->expr1->expr_type == EXPR_ARRAY
7689                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
7690         {
7691            gfc_constructor *cons;
7692            cons = gfc_constructor_first (code->expr1->value.constructor);
7693            for (; cons; cons = gfc_constructor_next (cons))
7694              if (cons->expr->expr_type == EXPR_CONSTANT
7695                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
7696                gfc_error ("Imageset argument at %L must between 1 and "
7697                           "num_images()", &cons->expr->where);
7698         }
7699     }
7700
7701   /* Check STAT.  */
7702   if (code->expr2
7703       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
7704           || code->expr2->expr_type != EXPR_VARIABLE))
7705     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
7706                &code->expr2->where);
7707
7708   /* Check ERRMSG.  */
7709   if (code->expr3
7710       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
7711           || code->expr3->expr_type != EXPR_VARIABLE))
7712     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
7713                &code->expr3->where);
7714 }
7715
7716
7717 /* Given a branch to a label, see if the branch is conforming.
7718    The code node describes where the branch is located.  */
7719
7720 static void
7721 resolve_branch (gfc_st_label *label, gfc_code *code)
7722 {
7723   code_stack *stack;
7724
7725   if (label == NULL)
7726     return;
7727
7728   /* Step one: is this a valid branching target?  */
7729
7730   if (label->defined == ST_LABEL_UNKNOWN)
7731     {
7732       gfc_error ("Label %d referenced at %L is never defined", label->value,
7733                  &label->where);
7734       return;
7735     }
7736
7737   if (label->defined != ST_LABEL_TARGET)
7738     {
7739       gfc_error ("Statement at %L is not a valid branch target statement "
7740                  "for the branch statement at %L", &label->where, &code->loc);
7741       return;
7742     }
7743
7744   /* Step two: make sure this branch is not a branch to itself ;-)  */
7745
7746   if (code->here == label)
7747     {
7748       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7749       return;
7750     }
7751
7752   /* Step three:  See if the label is in the same block as the
7753      branching statement.  The hard work has been done by setting up
7754      the bitmap reachable_labels.  */
7755
7756   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7757     {
7758       /* Check now whether there is a CRITICAL construct; if so, check
7759          whether the label is still visible outside of the CRITICAL block,
7760          which is invalid.  */
7761       for (stack = cs_base; stack; stack = stack->prev)
7762         if (stack->current->op == EXEC_CRITICAL
7763             && bitmap_bit_p (stack->reachable_labels, label->value))
7764           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7765                       " at %L", &code->loc, &label->where);
7766
7767       return;
7768     }
7769
7770   /* Step four:  If we haven't found the label in the bitmap, it may
7771     still be the label of the END of the enclosing block, in which
7772     case we find it by going up the code_stack.  */
7773
7774   for (stack = cs_base; stack; stack = stack->prev)
7775     {
7776       if (stack->current->next && stack->current->next->here == label)
7777         break;
7778       if (stack->current->op == EXEC_CRITICAL)
7779         {
7780           /* Note: A label at END CRITICAL does not leave the CRITICAL
7781              construct as END CRITICAL is still part of it.  */
7782           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7783                       " at %L", &code->loc, &label->where);
7784           return;
7785         }
7786     }
7787
7788   if (stack)
7789     {
7790       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7791       return;
7792     }
7793
7794   /* The label is not in an enclosing block, so illegal.  This was
7795      allowed in Fortran 66, so we allow it as extension.  No
7796      further checks are necessary in this case.  */
7797   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7798                   "as the GOTO statement at %L", &label->where,
7799                   &code->loc);
7800   return;
7801 }
7802
7803
7804 /* Check whether EXPR1 has the same shape as EXPR2.  */
7805
7806 static gfc_try
7807 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7808 {
7809   mpz_t shape[GFC_MAX_DIMENSIONS];
7810   mpz_t shape2[GFC_MAX_DIMENSIONS];
7811   gfc_try result = FAILURE;
7812   int i;
7813
7814   /* Compare the rank.  */
7815   if (expr1->rank != expr2->rank)
7816     return result;
7817
7818   /* Compare the size of each dimension.  */
7819   for (i=0; i<expr1->rank; i++)
7820     {
7821       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7822         goto ignore;
7823
7824       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7825         goto ignore;
7826
7827       if (mpz_cmp (shape[i], shape2[i]))
7828         goto over;
7829     }
7830
7831   /* When either of the two expression is an assumed size array, we
7832      ignore the comparison of dimension sizes.  */
7833 ignore:
7834   result = SUCCESS;
7835
7836 over:
7837   for (i--; i >= 0; i--)
7838     {
7839       mpz_clear (shape[i]);
7840       mpz_clear (shape2[i]);
7841     }
7842   return result;
7843 }
7844
7845
7846 /* Check whether a WHERE assignment target or a WHERE mask expression
7847    has the same shape as the outmost WHERE mask expression.  */
7848
7849 static void
7850 resolve_where (gfc_code *code, gfc_expr *mask)
7851 {
7852   gfc_code *cblock;
7853   gfc_code *cnext;
7854   gfc_expr *e = NULL;
7855
7856   cblock = code->block;
7857
7858   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7859      In case of nested WHERE, only the outmost one is stored.  */
7860   if (mask == NULL) /* outmost WHERE */
7861     e = cblock->expr1;
7862   else /* inner WHERE */
7863     e = mask;
7864
7865   while (cblock)
7866     {
7867       if (cblock->expr1)
7868         {
7869           /* Check if the mask-expr has a consistent shape with the
7870              outmost WHERE mask-expr.  */
7871           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7872             gfc_error ("WHERE mask at %L has inconsistent shape",
7873                        &cblock->expr1->where);
7874          }
7875
7876       /* the assignment statement of a WHERE statement, or the first
7877          statement in where-body-construct of a WHERE construct */
7878       cnext = cblock->next;
7879       while (cnext)
7880         {
7881           switch (cnext->op)
7882             {
7883             /* WHERE assignment statement */
7884             case EXEC_ASSIGN:
7885
7886               /* Check shape consistent for WHERE assignment target.  */
7887               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7888                gfc_error ("WHERE assignment target at %L has "
7889                           "inconsistent shape", &cnext->expr1->where);
7890               break;
7891
7892   
7893             case EXEC_ASSIGN_CALL:
7894               resolve_call (cnext);
7895               if (!cnext->resolved_sym->attr.elemental)
7896                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7897                           &cnext->ext.actual->expr->where);
7898               break;
7899
7900             /* WHERE or WHERE construct is part of a where-body-construct */
7901             case EXEC_WHERE:
7902               resolve_where (cnext, e);
7903               break;
7904
7905             default:
7906               gfc_error ("Unsupported statement inside WHERE at %L",
7907                          &cnext->loc);
7908             }
7909          /* the next statement within the same where-body-construct */
7910          cnext = cnext->next;
7911        }
7912     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7913     cblock = cblock->block;
7914   }
7915 }
7916
7917
7918 /* Resolve assignment in FORALL construct.
7919    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7920    FORALL index variables.  */
7921
7922 static void
7923 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7924 {
7925   int n;
7926
7927   for (n = 0; n < nvar; n++)
7928     {
7929       gfc_symbol *forall_index;
7930
7931       forall_index = var_expr[n]->symtree->n.sym;
7932
7933       /* Check whether the assignment target is one of the FORALL index
7934          variable.  */
7935       if ((code->expr1->expr_type == EXPR_VARIABLE)
7936           && (code->expr1->symtree->n.sym == forall_index))
7937         gfc_error ("Assignment to a FORALL index variable at %L",
7938                    &code->expr1->where);
7939       else
7940         {
7941           /* If one of the FORALL index variables doesn't appear in the
7942              assignment variable, then there could be a many-to-one
7943              assignment.  Emit a warning rather than an error because the
7944              mask could be resolving this problem.  */
7945           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7946             gfc_warning ("The FORALL with index '%s' is not used on the "
7947                          "left side of the assignment at %L and so might "
7948                          "cause multiple assignment to this object",
7949                          var_expr[n]->symtree->name, &code->expr1->where);
7950         }
7951     }
7952 }
7953
7954
7955 /* Resolve WHERE statement in FORALL construct.  */
7956
7957 static void
7958 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7959                                   gfc_expr **var_expr)
7960 {
7961   gfc_code *cblock;
7962   gfc_code *cnext;
7963
7964   cblock = code->block;
7965   while (cblock)
7966     {
7967       /* the assignment statement of a WHERE statement, or the first
7968          statement in where-body-construct of a WHERE construct */
7969       cnext = cblock->next;
7970       while (cnext)
7971         {
7972           switch (cnext->op)
7973             {
7974             /* WHERE assignment statement */
7975             case EXEC_ASSIGN:
7976               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7977               break;
7978   
7979             /* WHERE operator assignment statement */
7980             case EXEC_ASSIGN_CALL:
7981               resolve_call (cnext);
7982               if (!cnext->resolved_sym->attr.elemental)
7983                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7984                           &cnext->ext.actual->expr->where);
7985               break;
7986
7987             /* WHERE or WHERE construct is part of a where-body-construct */
7988             case EXEC_WHERE:
7989               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7990               break;
7991
7992             default:
7993               gfc_error ("Unsupported statement inside WHERE at %L",
7994                          &cnext->loc);
7995             }
7996           /* the next statement within the same where-body-construct */
7997           cnext = cnext->next;
7998         }
7999       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8000       cblock = cblock->block;
8001     }
8002 }
8003
8004
8005 /* Traverse the FORALL body to check whether the following errors exist:
8006    1. For assignment, check if a many-to-one assignment happens.
8007    2. For WHERE statement, check the WHERE body to see if there is any
8008       many-to-one assignment.  */
8009
8010 static void
8011 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8012 {
8013   gfc_code *c;
8014
8015   c = code->block->next;
8016   while (c)
8017     {
8018       switch (c->op)
8019         {
8020         case EXEC_ASSIGN:
8021         case EXEC_POINTER_ASSIGN:
8022           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8023           break;
8024
8025         case EXEC_ASSIGN_CALL:
8026           resolve_call (c);
8027           break;
8028
8029         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8030            there is no need to handle it here.  */
8031         case EXEC_FORALL:
8032           break;
8033         case EXEC_WHERE:
8034           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8035           break;
8036         default:
8037           break;
8038         }
8039       /* The next statement in the FORALL body.  */
8040       c = c->next;
8041     }
8042 }
8043
8044
8045 /* Counts the number of iterators needed inside a forall construct, including
8046    nested forall constructs. This is used to allocate the needed memory 
8047    in gfc_resolve_forall.  */
8048
8049 static int 
8050 gfc_count_forall_iterators (gfc_code *code)
8051 {
8052   int max_iters, sub_iters, current_iters;
8053   gfc_forall_iterator *fa;
8054
8055   gcc_assert(code->op == EXEC_FORALL);
8056   max_iters = 0;
8057   current_iters = 0;
8058
8059   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8060     current_iters ++;
8061   
8062   code = code->block->next;
8063
8064   while (code)
8065     {          
8066       if (code->op == EXEC_FORALL)
8067         {
8068           sub_iters = gfc_count_forall_iterators (code);
8069           if (sub_iters > max_iters)
8070             max_iters = sub_iters;
8071         }
8072       code = code->next;
8073     }
8074
8075   return current_iters + max_iters;
8076 }
8077
8078
8079 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8080    gfc_resolve_forall_body to resolve the FORALL body.  */
8081
8082 static void
8083 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8084 {
8085   static gfc_expr **var_expr;
8086   static int total_var = 0;
8087   static int nvar = 0;
8088   int old_nvar, tmp;
8089   gfc_forall_iterator *fa;
8090   int i;
8091
8092   old_nvar = nvar;
8093
8094   /* Start to resolve a FORALL construct   */
8095   if (forall_save == 0)
8096     {
8097       /* Count the total number of FORALL index in the nested FORALL
8098          construct in order to allocate the VAR_EXPR with proper size.  */
8099       total_var = gfc_count_forall_iterators (code);
8100
8101       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8102       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
8103     }
8104
8105   /* The information about FORALL iterator, including FORALL index start, end
8106      and stride. The FORALL index can not appear in start, end or stride.  */
8107   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8108     {
8109       /* Check if any outer FORALL index name is the same as the current
8110          one.  */
8111       for (i = 0; i < nvar; i++)
8112         {
8113           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8114             {
8115               gfc_error ("An outer FORALL construct already has an index "
8116                          "with this name %L", &fa->var->where);
8117             }
8118         }
8119
8120       /* Record the current FORALL index.  */
8121       var_expr[nvar] = gfc_copy_expr (fa->var);
8122
8123       nvar++;
8124
8125       /* No memory leak.  */
8126       gcc_assert (nvar <= total_var);
8127     }
8128
8129   /* Resolve the FORALL body.  */
8130   gfc_resolve_forall_body (code, nvar, var_expr);
8131
8132   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8133   gfc_resolve_blocks (code->block, ns);
8134
8135   tmp = nvar;
8136   nvar = old_nvar;
8137   /* Free only the VAR_EXPRs allocated in this frame.  */
8138   for (i = nvar; i < tmp; i++)
8139      gfc_free_expr (var_expr[i]);
8140
8141   if (nvar == 0)
8142     {
8143       /* We are in the outermost FORALL construct.  */
8144       gcc_assert (forall_save == 0);
8145
8146       /* VAR_EXPR is not needed any more.  */
8147       gfc_free (var_expr);
8148       total_var = 0;
8149     }
8150 }
8151
8152
8153 /* Resolve a BLOCK construct statement.  */
8154
8155 static void
8156 resolve_block_construct (gfc_code* code)
8157 {
8158   /* For an ASSOCIATE block, the associations (and their targets) are already
8159      resolved during gfc_resolve_symbol.  */
8160
8161   /* Resolve the BLOCK's namespace.  */
8162   gfc_resolve (code->ext.block.ns);
8163 }
8164
8165
8166 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8167    DO code nodes.  */
8168
8169 static void resolve_code (gfc_code *, gfc_namespace *);
8170
8171 void
8172 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8173 {
8174   gfc_try t;
8175
8176   for (; b; b = b->block)
8177     {
8178       t = gfc_resolve_expr (b->expr1);
8179       if (gfc_resolve_expr (b->expr2) == FAILURE)
8180         t = FAILURE;
8181
8182       switch (b->op)
8183         {
8184         case EXEC_IF:
8185           if (t == SUCCESS && b->expr1 != NULL
8186               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8187             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8188                        &b->expr1->where);
8189           break;
8190
8191         case EXEC_WHERE:
8192           if (t == SUCCESS
8193               && b->expr1 != NULL
8194               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8195             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8196                        &b->expr1->where);
8197           break;
8198
8199         case EXEC_GOTO:
8200           resolve_branch (b->label1, b);
8201           break;
8202
8203         case EXEC_BLOCK:
8204           resolve_block_construct (b);
8205           break;
8206
8207         case EXEC_SELECT:
8208         case EXEC_SELECT_TYPE:
8209         case EXEC_FORALL:
8210         case EXEC_DO:
8211         case EXEC_DO_WHILE:
8212         case EXEC_CRITICAL:
8213         case EXEC_READ:
8214         case EXEC_WRITE:
8215         case EXEC_IOLENGTH:
8216         case EXEC_WAIT:
8217           break;
8218
8219         case EXEC_OMP_ATOMIC:
8220         case EXEC_OMP_CRITICAL:
8221         case EXEC_OMP_DO:
8222         case EXEC_OMP_MASTER:
8223         case EXEC_OMP_ORDERED:
8224         case EXEC_OMP_PARALLEL:
8225         case EXEC_OMP_PARALLEL_DO:
8226         case EXEC_OMP_PARALLEL_SECTIONS:
8227         case EXEC_OMP_PARALLEL_WORKSHARE:
8228         case EXEC_OMP_SECTIONS:
8229         case EXEC_OMP_SINGLE:
8230         case EXEC_OMP_TASK:
8231         case EXEC_OMP_TASKWAIT:
8232         case EXEC_OMP_WORKSHARE:
8233           break;
8234
8235         default:
8236           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8237         }
8238
8239       resolve_code (b->next, ns);
8240     }
8241 }
8242
8243
8244 /* Does everything to resolve an ordinary assignment.  Returns true
8245    if this is an interface assignment.  */
8246 static bool
8247 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8248 {
8249   bool rval = false;
8250   gfc_expr *lhs;
8251   gfc_expr *rhs;
8252   int llen = 0;
8253   int rlen = 0;
8254   int n;
8255   gfc_ref *ref;
8256
8257   if (gfc_extend_assign (code, ns) == SUCCESS)
8258     {
8259       gfc_expr** rhsptr;
8260
8261       if (code->op == EXEC_ASSIGN_CALL)
8262         {
8263           lhs = code->ext.actual->expr;
8264           rhsptr = &code->ext.actual->next->expr;
8265         }
8266       else
8267         {
8268           gfc_actual_arglist* args;
8269           gfc_typebound_proc* tbp;
8270
8271           gcc_assert (code->op == EXEC_COMPCALL);
8272
8273           args = code->expr1->value.compcall.actual;
8274           lhs = args->expr;
8275           rhsptr = &args->next->expr;
8276
8277           tbp = code->expr1->value.compcall.tbp;
8278           gcc_assert (!tbp->is_generic);
8279         }
8280
8281       /* Make a temporary rhs when there is a default initializer
8282          and rhs is the same symbol as the lhs.  */
8283       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8284             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8285             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8286             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8287         *rhsptr = gfc_get_parentheses (*rhsptr);
8288
8289       return true;
8290     }
8291
8292   lhs = code->expr1;
8293   rhs = code->expr2;
8294
8295   if (rhs->is_boz
8296       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8297                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8298                          &code->loc) == FAILURE)
8299     return false;
8300
8301   /* Handle the case of a BOZ literal on the RHS.  */
8302   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8303     {
8304       int rc;
8305       if (gfc_option.warn_surprising)
8306         gfc_warning ("BOZ literal at %L is bitwise transferred "
8307                      "non-integer symbol '%s'", &code->loc,
8308                      lhs->symtree->n.sym->name);
8309
8310       if (!gfc_convert_boz (rhs, &lhs->ts))
8311         return false;
8312       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8313         {
8314           if (rc == ARITH_UNDERFLOW)
8315             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8316                        ". This check can be disabled with the option "
8317                        "-fno-range-check", &rhs->where);
8318           else if (rc == ARITH_OVERFLOW)
8319             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8320                        ". This check can be disabled with the option "
8321                        "-fno-range-check", &rhs->where);
8322           else if (rc == ARITH_NAN)
8323             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8324                        ". This check can be disabled with the option "
8325                        "-fno-range-check", &rhs->where);
8326           return false;
8327         }
8328     }
8329
8330
8331   if (lhs->ts.type == BT_CHARACTER
8332         && gfc_option.warn_character_truncation)
8333     {
8334       if (lhs->ts.u.cl != NULL
8335             && lhs->ts.u.cl->length != NULL
8336             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8337         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8338
8339       if (rhs->expr_type == EXPR_CONSTANT)
8340         rlen = rhs->value.character.length;
8341
8342       else if (rhs->ts.u.cl != NULL
8343                  && rhs->ts.u.cl->length != NULL
8344                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8345         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8346
8347       if (rlen && llen && rlen > llen)
8348         gfc_warning_now ("CHARACTER expression will be truncated "
8349                          "in assignment (%d/%d) at %L",
8350                          llen, rlen, &code->loc);
8351     }
8352
8353   /* Ensure that a vector index expression for the lvalue is evaluated
8354      to a temporary if the lvalue symbol is referenced in it.  */
8355   if (lhs->rank)
8356     {
8357       for (ref = lhs->ref; ref; ref= ref->next)
8358         if (ref->type == REF_ARRAY)
8359           {
8360             for (n = 0; n < ref->u.ar.dimen; n++)
8361               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8362                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8363                                            ref->u.ar.start[n]))
8364                 ref->u.ar.start[n]
8365                         = gfc_get_parentheses (ref->u.ar.start[n]);
8366           }
8367     }
8368
8369   if (gfc_pure (NULL))
8370     {
8371       if (gfc_impure_variable (lhs->symtree->n.sym))
8372         {
8373           gfc_error ("Cannot assign to variable '%s' in PURE "
8374                      "procedure at %L",
8375                       lhs->symtree->n.sym->name,
8376                       &lhs->where);
8377           return rval;
8378         }
8379
8380       if (lhs->ts.type == BT_DERIVED
8381             && lhs->expr_type == EXPR_VARIABLE
8382             && lhs->ts.u.derived->attr.pointer_comp
8383             && rhs->expr_type == EXPR_VARIABLE
8384             && (gfc_impure_variable (rhs->symtree->n.sym)
8385                 || gfc_is_coindexed (rhs)))
8386         {
8387           /* F2008, C1283.  */
8388           if (gfc_is_coindexed (rhs))
8389             gfc_error ("Coindexed expression at %L is assigned to "
8390                         "a derived type variable with a POINTER "
8391                         "component in a PURE procedure",
8392                         &rhs->where);
8393           else
8394             gfc_error ("The impure variable at %L is assigned to "
8395                         "a derived type variable with a POINTER "
8396                         "component in a PURE procedure (12.6)",
8397                         &rhs->where);
8398           return rval;
8399         }
8400
8401       /* Fortran 2008, C1283.  */
8402       if (gfc_is_coindexed (lhs))
8403         {
8404           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8405                      "procedure", &rhs->where);
8406           return rval;
8407         }
8408     }
8409
8410   /* F03:7.4.1.2.  */
8411   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8412      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8413   if (lhs->ts.type == BT_CLASS)
8414     {
8415       gfc_error ("Variable must not be polymorphic in assignment at %L",
8416                  &lhs->where);
8417       return false;
8418     }
8419
8420   /* F2008, Section 7.2.1.2.  */
8421   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8422     {
8423       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8424                  "component in assignment at %L", &lhs->where);
8425       return false;
8426     }
8427
8428   gfc_check_assign (lhs, rhs, 1);
8429   return false;
8430 }
8431
8432
8433 /* Given a block of code, recursively resolve everything pointed to by this
8434    code block.  */
8435
8436 static void
8437 resolve_code (gfc_code *code, gfc_namespace *ns)
8438 {
8439   int omp_workshare_save;
8440   int forall_save;
8441   code_stack frame;
8442   gfc_try t;
8443
8444   frame.prev = cs_base;
8445   frame.head = code;
8446   cs_base = &frame;
8447
8448   find_reachable_labels (code);
8449
8450   for (; code; code = code->next)
8451     {
8452       frame.current = code;
8453       forall_save = forall_flag;
8454
8455       if (code->op == EXEC_FORALL)
8456         {
8457           forall_flag = 1;
8458           gfc_resolve_forall (code, ns, forall_save);
8459           forall_flag = 2;
8460         }
8461       else if (code->block)
8462         {
8463           omp_workshare_save = -1;
8464           switch (code->op)
8465             {
8466             case EXEC_OMP_PARALLEL_WORKSHARE:
8467               omp_workshare_save = omp_workshare_flag;
8468               omp_workshare_flag = 1;
8469               gfc_resolve_omp_parallel_blocks (code, ns);
8470               break;
8471             case EXEC_OMP_PARALLEL:
8472             case EXEC_OMP_PARALLEL_DO:
8473             case EXEC_OMP_PARALLEL_SECTIONS:
8474             case EXEC_OMP_TASK:
8475               omp_workshare_save = omp_workshare_flag;
8476               omp_workshare_flag = 0;
8477               gfc_resolve_omp_parallel_blocks (code, ns);
8478               break;
8479             case EXEC_OMP_DO:
8480               gfc_resolve_omp_do_blocks (code, ns);
8481               break;
8482             case EXEC_SELECT_TYPE:
8483               gfc_current_ns = code->ext.block.ns;
8484               gfc_resolve_blocks (code->block, gfc_current_ns);
8485               gfc_current_ns = ns;
8486               break;
8487             case EXEC_OMP_WORKSHARE:
8488               omp_workshare_save = omp_workshare_flag;
8489               omp_workshare_flag = 1;
8490               /* FALLTHROUGH */
8491             default:
8492               gfc_resolve_blocks (code->block, ns);
8493               break;
8494             }
8495
8496           if (omp_workshare_save != -1)
8497             omp_workshare_flag = omp_workshare_save;
8498         }
8499
8500       t = SUCCESS;
8501       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8502         t = gfc_resolve_expr (code->expr1);
8503       forall_flag = forall_save;
8504
8505       if (gfc_resolve_expr (code->expr2) == FAILURE)
8506         t = FAILURE;
8507
8508       if (code->op == EXEC_ALLOCATE
8509           && gfc_resolve_expr (code->expr3) == FAILURE)
8510         t = FAILURE;
8511
8512       switch (code->op)
8513         {
8514         case EXEC_NOP:
8515         case EXEC_END_BLOCK:
8516         case EXEC_CYCLE:
8517         case EXEC_PAUSE:
8518         case EXEC_STOP:
8519         case EXEC_ERROR_STOP:
8520         case EXEC_EXIT:
8521         case EXEC_CONTINUE:
8522         case EXEC_DT_END:
8523         case EXEC_ASSIGN_CALL:
8524         case EXEC_CRITICAL:
8525           break;
8526
8527         case EXEC_SYNC_ALL:
8528         case EXEC_SYNC_IMAGES:
8529         case EXEC_SYNC_MEMORY:
8530           resolve_sync (code);
8531           break;
8532
8533         case EXEC_ENTRY:
8534           /* Keep track of which entry we are up to.  */
8535           current_entry_id = code->ext.entry->id;
8536           break;
8537
8538         case EXEC_WHERE:
8539           resolve_where (code, NULL);
8540           break;
8541
8542         case EXEC_GOTO:
8543           if (code->expr1 != NULL)
8544             {
8545               if (code->expr1->ts.type != BT_INTEGER)
8546                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8547                            "INTEGER variable", &code->expr1->where);
8548               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8549                 gfc_error ("Variable '%s' has not been assigned a target "
8550                            "label at %L", code->expr1->symtree->n.sym->name,
8551                            &code->expr1->where);
8552             }
8553           else
8554             resolve_branch (code->label1, code);
8555           break;
8556
8557         case EXEC_RETURN:
8558           if (code->expr1 != NULL
8559                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8560             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8561                        "INTEGER return specifier", &code->expr1->where);
8562           break;
8563
8564         case EXEC_INIT_ASSIGN:
8565         case EXEC_END_PROCEDURE:
8566           break;
8567
8568         case EXEC_ASSIGN:
8569           if (t == FAILURE)
8570             break;
8571
8572           if (resolve_ordinary_assign (code, ns))
8573             {
8574               if (code->op == EXEC_COMPCALL)
8575                 goto compcall;
8576               else
8577                 goto call;
8578             }
8579           break;
8580
8581         case EXEC_LABEL_ASSIGN:
8582           if (code->label1->defined == ST_LABEL_UNKNOWN)
8583             gfc_error ("Label %d referenced at %L is never defined",
8584                        code->label1->value, &code->label1->where);
8585           if (t == SUCCESS
8586               && (code->expr1->expr_type != EXPR_VARIABLE
8587                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8588                   || code->expr1->symtree->n.sym->ts.kind
8589                      != gfc_default_integer_kind
8590                   || code->expr1->symtree->n.sym->as != NULL))
8591             gfc_error ("ASSIGN statement at %L requires a scalar "
8592                        "default INTEGER variable", &code->expr1->where);
8593           break;
8594
8595         case EXEC_POINTER_ASSIGN:
8596           if (t == FAILURE)
8597             break;
8598
8599           gfc_check_pointer_assign (code->expr1, code->expr2);
8600           break;
8601
8602         case EXEC_ARITHMETIC_IF:
8603           if (t == SUCCESS
8604               && code->expr1->ts.type != BT_INTEGER
8605               && code->expr1->ts.type != BT_REAL)
8606             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8607                        "expression", &code->expr1->where);
8608
8609           resolve_branch (code->label1, code);
8610           resolve_branch (code->label2, code);
8611           resolve_branch (code->label3, code);
8612           break;
8613
8614         case EXEC_IF:
8615           if (t == SUCCESS && code->expr1 != NULL
8616               && (code->expr1->ts.type != BT_LOGICAL
8617                   || code->expr1->rank != 0))
8618             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8619                        &code->expr1->where);
8620           break;
8621
8622         case EXEC_CALL:
8623         call:
8624           resolve_call (code);
8625           break;
8626
8627         case EXEC_COMPCALL:
8628         compcall:
8629           resolve_typebound_subroutine (code);
8630           break;
8631
8632         case EXEC_CALL_PPC:
8633           resolve_ppc_call (code);
8634           break;
8635
8636         case EXEC_SELECT:
8637           /* Select is complicated. Also, a SELECT construct could be
8638              a transformed computed GOTO.  */
8639           resolve_select (code);
8640           break;
8641
8642         case EXEC_SELECT_TYPE:
8643           resolve_select_type (code);
8644           break;
8645
8646         case EXEC_BLOCK:
8647           gfc_resolve (code->ext.block.ns);
8648           break;
8649
8650         case EXEC_DO:
8651           if (code->ext.iterator != NULL)
8652             {
8653               gfc_iterator *iter = code->ext.iterator;
8654               if (gfc_resolve_iterator (iter, true) != FAILURE)
8655                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8656             }
8657           break;
8658
8659         case EXEC_DO_WHILE:
8660           if (code->expr1 == NULL)
8661             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8662           if (t == SUCCESS
8663               && (code->expr1->rank != 0
8664                   || code->expr1->ts.type != BT_LOGICAL))
8665             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8666                        "a scalar LOGICAL expression", &code->expr1->where);
8667           break;
8668
8669         case EXEC_ALLOCATE:
8670           if (t == SUCCESS)
8671             resolve_allocate_deallocate (code, "ALLOCATE");
8672
8673           break;
8674
8675         case EXEC_DEALLOCATE:
8676           if (t == SUCCESS)
8677             resolve_allocate_deallocate (code, "DEALLOCATE");
8678
8679           break;
8680
8681         case EXEC_OPEN:
8682           if (gfc_resolve_open (code->ext.open) == FAILURE)
8683             break;
8684
8685           resolve_branch (code->ext.open->err, code);
8686           break;
8687
8688         case EXEC_CLOSE:
8689           if (gfc_resolve_close (code->ext.close) == FAILURE)
8690             break;
8691
8692           resolve_branch (code->ext.close->err, code);
8693           break;
8694
8695         case EXEC_BACKSPACE:
8696         case EXEC_ENDFILE:
8697         case EXEC_REWIND:
8698         case EXEC_FLUSH:
8699           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8700             break;
8701
8702           resolve_branch (code->ext.filepos->err, code);
8703           break;
8704
8705         case EXEC_INQUIRE:
8706           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8707               break;
8708
8709           resolve_branch (code->ext.inquire->err, code);
8710           break;
8711
8712         case EXEC_IOLENGTH:
8713           gcc_assert (code->ext.inquire != NULL);
8714           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8715             break;
8716
8717           resolve_branch (code->ext.inquire->err, code);
8718           break;
8719
8720         case EXEC_WAIT:
8721           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8722             break;
8723
8724           resolve_branch (code->ext.wait->err, code);
8725           resolve_branch (code->ext.wait->end, code);
8726           resolve_branch (code->ext.wait->eor, code);
8727           break;
8728
8729         case EXEC_READ:
8730         case EXEC_WRITE:
8731           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8732             break;
8733
8734           resolve_branch (code->ext.dt->err, code);
8735           resolve_branch (code->ext.dt->end, code);
8736           resolve_branch (code->ext.dt->eor, code);
8737           break;
8738
8739         case EXEC_TRANSFER:
8740           resolve_transfer (code);
8741           break;
8742
8743         case EXEC_FORALL:
8744           resolve_forall_iterators (code->ext.forall_iterator);
8745
8746           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8747             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8748                        "expression", &code->expr1->where);
8749           break;
8750
8751         case EXEC_OMP_ATOMIC:
8752         case EXEC_OMP_BARRIER:
8753         case EXEC_OMP_CRITICAL:
8754         case EXEC_OMP_FLUSH:
8755         case EXEC_OMP_DO:
8756         case EXEC_OMP_MASTER:
8757         case EXEC_OMP_ORDERED:
8758         case EXEC_OMP_SECTIONS:
8759         case EXEC_OMP_SINGLE:
8760         case EXEC_OMP_TASKWAIT:
8761         case EXEC_OMP_WORKSHARE:
8762           gfc_resolve_omp_directive (code, ns);
8763           break;
8764
8765         case EXEC_OMP_PARALLEL:
8766         case EXEC_OMP_PARALLEL_DO:
8767         case EXEC_OMP_PARALLEL_SECTIONS:
8768         case EXEC_OMP_PARALLEL_WORKSHARE:
8769         case EXEC_OMP_TASK:
8770           omp_workshare_save = omp_workshare_flag;
8771           omp_workshare_flag = 0;
8772           gfc_resolve_omp_directive (code, ns);
8773           omp_workshare_flag = omp_workshare_save;
8774           break;
8775
8776         default:
8777           gfc_internal_error ("resolve_code(): Bad statement code");
8778         }
8779     }
8780
8781   cs_base = frame.prev;
8782 }
8783
8784
8785 /* Resolve initial values and make sure they are compatible with
8786    the variable.  */
8787
8788 static void
8789 resolve_values (gfc_symbol *sym)
8790 {
8791   if (sym->value == NULL)
8792     return;
8793
8794   if (gfc_resolve_expr (sym->value) == FAILURE)
8795     return;
8796
8797   gfc_check_assign_symbol (sym, sym->value);
8798 }
8799
8800
8801 /* Verify the binding labels for common blocks that are BIND(C).  The label
8802    for a BIND(C) common block must be identical in all scoping units in which
8803    the common block is declared.  Further, the binding label can not collide
8804    with any other global entity in the program.  */
8805
8806 static void
8807 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8808 {
8809   if (comm_block_tree->n.common->is_bind_c == 1)
8810     {
8811       gfc_gsymbol *binding_label_gsym;
8812       gfc_gsymbol *comm_name_gsym;
8813
8814       /* See if a global symbol exists by the common block's name.  It may
8815          be NULL if the common block is use-associated.  */
8816       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8817                                          comm_block_tree->n.common->name);
8818       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8819         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8820                    "with the global entity '%s' at %L",
8821                    comm_block_tree->n.common->binding_label,
8822                    comm_block_tree->n.common->name,
8823                    &(comm_block_tree->n.common->where),
8824                    comm_name_gsym->name, &(comm_name_gsym->where));
8825       else if (comm_name_gsym != NULL
8826                && strcmp (comm_name_gsym->name,
8827                           comm_block_tree->n.common->name) == 0)
8828         {
8829           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8830              as expected.  */
8831           if (comm_name_gsym->binding_label == NULL)
8832             /* No binding label for common block stored yet; save this one.  */
8833             comm_name_gsym->binding_label =
8834               comm_block_tree->n.common->binding_label;
8835           else
8836             if (strcmp (comm_name_gsym->binding_label,
8837                         comm_block_tree->n.common->binding_label) != 0)
8838               {
8839                 /* Common block names match but binding labels do not.  */
8840                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8841                            "does not match the binding label '%s' for common "
8842                            "block '%s' at %L",
8843                            comm_block_tree->n.common->binding_label,
8844                            comm_block_tree->n.common->name,
8845                            &(comm_block_tree->n.common->where),
8846                            comm_name_gsym->binding_label,
8847                            comm_name_gsym->name,
8848                            &(comm_name_gsym->where));
8849                 return;
8850               }
8851         }
8852
8853       /* There is no binding label (NAME="") so we have nothing further to
8854          check and nothing to add as a global symbol for the label.  */
8855       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8856         return;
8857       
8858       binding_label_gsym =
8859         gfc_find_gsymbol (gfc_gsym_root,
8860                           comm_block_tree->n.common->binding_label);
8861       if (binding_label_gsym == NULL)
8862         {
8863           /* Need to make a global symbol for the binding label to prevent
8864              it from colliding with another.  */
8865           binding_label_gsym =
8866             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8867           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8868           binding_label_gsym->type = GSYM_COMMON;
8869         }
8870       else
8871         {
8872           /* If comm_name_gsym is NULL, the name common block is use
8873              associated and the name could be colliding.  */
8874           if (binding_label_gsym->type != GSYM_COMMON)
8875             gfc_error ("Binding label '%s' for common block '%s' at %L "
8876                        "collides with the global entity '%s' at %L",
8877                        comm_block_tree->n.common->binding_label,
8878                        comm_block_tree->n.common->name,
8879                        &(comm_block_tree->n.common->where),
8880                        binding_label_gsym->name,
8881                        &(binding_label_gsym->where));
8882           else if (comm_name_gsym != NULL
8883                    && (strcmp (binding_label_gsym->name,
8884                                comm_name_gsym->binding_label) != 0)
8885                    && (strcmp (binding_label_gsym->sym_name,
8886                                comm_name_gsym->name) != 0))
8887             gfc_error ("Binding label '%s' for common block '%s' at %L "
8888                        "collides with global entity '%s' at %L",
8889                        binding_label_gsym->name, binding_label_gsym->sym_name,
8890                        &(comm_block_tree->n.common->where),
8891                        comm_name_gsym->name, &(comm_name_gsym->where));
8892         }
8893     }
8894   
8895   return;
8896 }
8897
8898
8899 /* Verify any BIND(C) derived types in the namespace so we can report errors
8900    for them once, rather than for each variable declared of that type.  */
8901
8902 static void
8903 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8904 {
8905   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8906       && derived_sym->attr.is_bind_c == 1)
8907     verify_bind_c_derived_type (derived_sym);
8908   
8909   return;
8910 }
8911
8912
8913 /* Verify that any binding labels used in a given namespace do not collide 
8914    with the names or binding labels of any global symbols.  */
8915
8916 static void
8917 gfc_verify_binding_labels (gfc_symbol *sym)
8918 {
8919   int has_error = 0;
8920   
8921   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8922       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8923     {
8924       gfc_gsymbol *bind_c_sym;
8925
8926       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8927       if (bind_c_sym != NULL 
8928           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8929         {
8930           if (sym->attr.if_source == IFSRC_DECL 
8931               && (bind_c_sym->type != GSYM_SUBROUTINE 
8932                   && bind_c_sym->type != GSYM_FUNCTION) 
8933               && ((sym->attr.contained == 1 
8934                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8935                   || (sym->attr.use_assoc == 1 
8936                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8937             {
8938               /* Make sure global procedures don't collide with anything.  */
8939               gfc_error ("Binding label '%s' at %L collides with the global "
8940                          "entity '%s' at %L", sym->binding_label,
8941                          &(sym->declared_at), bind_c_sym->name,
8942                          &(bind_c_sym->where));
8943               has_error = 1;
8944             }
8945           else if (sym->attr.contained == 0 
8946                    && (sym->attr.if_source == IFSRC_IFBODY 
8947                        && sym->attr.flavor == FL_PROCEDURE) 
8948                    && (bind_c_sym->sym_name != NULL 
8949                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8950             {
8951               /* Make sure procedures in interface bodies don't collide.  */
8952               gfc_error ("Binding label '%s' in interface body at %L collides "
8953                          "with the global entity '%s' at %L",
8954                          sym->binding_label,
8955                          &(sym->declared_at), bind_c_sym->name,
8956                          &(bind_c_sym->where));
8957               has_error = 1;
8958             }
8959           else if (sym->attr.contained == 0 
8960                    && sym->attr.if_source == IFSRC_UNKNOWN)
8961             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8962                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8963                 || sym->attr.use_assoc == 0)
8964               {
8965                 gfc_error ("Binding label '%s' at %L collides with global "
8966                            "entity '%s' at %L", sym->binding_label,
8967                            &(sym->declared_at), bind_c_sym->name,
8968                            &(bind_c_sym->where));
8969                 has_error = 1;
8970               }
8971
8972           if (has_error != 0)
8973             /* Clear the binding label to prevent checking multiple times.  */
8974             sym->binding_label[0] = '\0';
8975         }
8976       else if (bind_c_sym == NULL)
8977         {
8978           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8979           bind_c_sym->where = sym->declared_at;
8980           bind_c_sym->sym_name = sym->name;
8981
8982           if (sym->attr.use_assoc == 1)
8983             bind_c_sym->mod_name = sym->module;
8984           else
8985             if (sym->ns->proc_name != NULL)
8986               bind_c_sym->mod_name = sym->ns->proc_name->name;
8987
8988           if (sym->attr.contained == 0)
8989             {
8990               if (sym->attr.subroutine)
8991                 bind_c_sym->type = GSYM_SUBROUTINE;
8992               else if (sym->attr.function)
8993                 bind_c_sym->type = GSYM_FUNCTION;
8994             }
8995         }
8996     }
8997   return;
8998 }
8999
9000
9001 /* Resolve an index expression.  */
9002
9003 static gfc_try
9004 resolve_index_expr (gfc_expr *e)
9005 {
9006   if (gfc_resolve_expr (e) == FAILURE)
9007     return FAILURE;
9008
9009   if (gfc_simplify_expr (e, 0) == FAILURE)
9010     return FAILURE;
9011
9012   if (gfc_specification_expr (e) == FAILURE)
9013     return FAILURE;
9014
9015   return SUCCESS;
9016 }
9017
9018 /* Resolve a charlen structure.  */
9019
9020 static gfc_try
9021 resolve_charlen (gfc_charlen *cl)
9022 {
9023   int i, k;
9024
9025   if (cl->resolved)
9026     return SUCCESS;
9027
9028   cl->resolved = 1;
9029
9030   specification_expr = 1;
9031
9032   if (resolve_index_expr (cl->length) == FAILURE)
9033     {
9034       specification_expr = 0;
9035       return FAILURE;
9036     }
9037
9038   /* "If the character length parameter value evaluates to a negative
9039      value, the length of character entities declared is zero."  */
9040   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9041     {
9042       if (gfc_option.warn_surprising)
9043         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9044                          " the length has been set to zero",
9045                          &cl->length->where, i);
9046       gfc_replace_expr (cl->length,
9047                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9048     }
9049
9050   /* Check that the character length is not too large.  */
9051   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9052   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9053       && cl->length->ts.type == BT_INTEGER
9054       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9055     {
9056       gfc_error ("String length at %L is too large", &cl->length->where);
9057       return FAILURE;
9058     }
9059
9060   return SUCCESS;
9061 }
9062
9063
9064 /* Test for non-constant shape arrays.  */
9065
9066 static bool
9067 is_non_constant_shape_array (gfc_symbol *sym)
9068 {
9069   gfc_expr *e;
9070   int i;
9071   bool not_constant;
9072
9073   not_constant = false;
9074   if (sym->as != NULL)
9075     {
9076       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9077          has not been simplified; parameter array references.  Do the
9078          simplification now.  */
9079       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9080         {
9081           e = sym->as->lower[i];
9082           if (e && (resolve_index_expr (e) == FAILURE
9083                     || !gfc_is_constant_expr (e)))
9084             not_constant = true;
9085           e = sym->as->upper[i];
9086           if (e && (resolve_index_expr (e) == FAILURE
9087                     || !gfc_is_constant_expr (e)))
9088             not_constant = true;
9089         }
9090     }
9091   return not_constant;
9092 }
9093
9094 /* Given a symbol and an initialization expression, add code to initialize
9095    the symbol to the function entry.  */
9096 static void
9097 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9098 {
9099   gfc_expr *lval;
9100   gfc_code *init_st;
9101   gfc_namespace *ns = sym->ns;
9102
9103   /* Search for the function namespace if this is a contained
9104      function without an explicit result.  */
9105   if (sym->attr.function && sym == sym->result
9106       && sym->name != sym->ns->proc_name->name)
9107     {
9108       ns = ns->contained;
9109       for (;ns; ns = ns->sibling)
9110         if (strcmp (ns->proc_name->name, sym->name) == 0)
9111           break;
9112     }
9113
9114   if (ns == NULL)
9115     {
9116       gfc_free_expr (init);
9117       return;
9118     }
9119
9120   /* Build an l-value expression for the result.  */
9121   lval = gfc_lval_expr_from_sym (sym);
9122
9123   /* Add the code at scope entry.  */
9124   init_st = gfc_get_code ();
9125   init_st->next = ns->code;
9126   ns->code = init_st;
9127
9128   /* Assign the default initializer to the l-value.  */
9129   init_st->loc = sym->declared_at;
9130   init_st->op = EXEC_INIT_ASSIGN;
9131   init_st->expr1 = lval;
9132   init_st->expr2 = init;
9133 }
9134
9135 /* Assign the default initializer to a derived type variable or result.  */
9136
9137 static void
9138 apply_default_init (gfc_symbol *sym)
9139 {
9140   gfc_expr *init = NULL;
9141
9142   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9143     return;
9144
9145   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9146     init = gfc_default_initializer (&sym->ts);
9147
9148   if (init == NULL)
9149     return;
9150
9151   build_init_assign (sym, init);
9152 }
9153
9154 /* Build an initializer for a local integer, real, complex, logical, or
9155    character variable, based on the command line flags finit-local-zero,
9156    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9157    null if the symbol should not have a default initialization.  */
9158 static gfc_expr *
9159 build_default_init_expr (gfc_symbol *sym)
9160 {
9161   int char_len;
9162   gfc_expr *init_expr;
9163   int i;
9164
9165   /* These symbols should never have a default initialization.  */
9166   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9167       || sym->attr.external
9168       || sym->attr.dummy
9169       || sym->attr.pointer
9170       || sym->attr.in_equivalence
9171       || sym->attr.in_common
9172       || sym->attr.data
9173       || sym->module
9174       || sym->attr.cray_pointee
9175       || sym->attr.cray_pointer)
9176     return NULL;
9177
9178   /* Now we'll try to build an initializer expression.  */
9179   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9180                                      &sym->declared_at);
9181
9182   /* We will only initialize integers, reals, complex, logicals, and
9183      characters, and only if the corresponding command-line flags
9184      were set.  Otherwise, we free init_expr and return null.  */
9185   switch (sym->ts.type)
9186     {    
9187     case BT_INTEGER:
9188       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9189         mpz_set_si (init_expr->value.integer, 
9190                          gfc_option.flag_init_integer_value);
9191       else
9192         {
9193           gfc_free_expr (init_expr);
9194           init_expr = NULL;
9195         }
9196       break;
9197
9198     case BT_REAL:
9199       switch (gfc_option.flag_init_real)
9200         {
9201         case GFC_INIT_REAL_SNAN:
9202           init_expr->is_snan = 1;
9203           /* Fall through.  */
9204         case GFC_INIT_REAL_NAN:
9205           mpfr_set_nan (init_expr->value.real);
9206           break;
9207
9208         case GFC_INIT_REAL_INF:
9209           mpfr_set_inf (init_expr->value.real, 1);
9210           break;
9211
9212         case GFC_INIT_REAL_NEG_INF:
9213           mpfr_set_inf (init_expr->value.real, -1);
9214           break;
9215
9216         case GFC_INIT_REAL_ZERO:
9217           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9218           break;
9219
9220         default:
9221           gfc_free_expr (init_expr);
9222           init_expr = NULL;
9223           break;
9224         }
9225       break;
9226           
9227     case BT_COMPLEX:
9228       switch (gfc_option.flag_init_real)
9229         {
9230         case GFC_INIT_REAL_SNAN:
9231           init_expr->is_snan = 1;
9232           /* Fall through.  */
9233         case GFC_INIT_REAL_NAN:
9234           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9235           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9236           break;
9237
9238         case GFC_INIT_REAL_INF:
9239           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9240           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9241           break;
9242
9243         case GFC_INIT_REAL_NEG_INF:
9244           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9245           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9246           break;
9247
9248         case GFC_INIT_REAL_ZERO:
9249           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9250           break;
9251
9252         default:
9253           gfc_free_expr (init_expr);
9254           init_expr = NULL;
9255           break;
9256         }
9257       break;
9258           
9259     case BT_LOGICAL:
9260       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9261         init_expr->value.logical = 0;
9262       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9263         init_expr->value.logical = 1;
9264       else
9265         {
9266           gfc_free_expr (init_expr);
9267           init_expr = NULL;
9268         }
9269       break;
9270           
9271     case BT_CHARACTER:
9272       /* For characters, the length must be constant in order to 
9273          create a default initializer.  */
9274       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9275           && sym->ts.u.cl->length
9276           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9277         {
9278           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9279           init_expr->value.character.length = char_len;
9280           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9281           for (i = 0; i < char_len; i++)
9282             init_expr->value.character.string[i]
9283               = (unsigned char) gfc_option.flag_init_character_value;
9284         }
9285       else
9286         {
9287           gfc_free_expr (init_expr);
9288           init_expr = NULL;
9289         }
9290       break;
9291           
9292     default:
9293      gfc_free_expr (init_expr);
9294      init_expr = NULL;
9295     }
9296   return init_expr;
9297 }
9298
9299 /* Add an initialization expression to a local variable.  */
9300 static void
9301 apply_default_init_local (gfc_symbol *sym)
9302 {
9303   gfc_expr *init = NULL;
9304
9305   /* The symbol should be a variable or a function return value.  */
9306   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9307       || (sym->attr.function && sym->result != sym))
9308     return;
9309
9310   /* Try to build the initializer expression.  If we can't initialize
9311      this symbol, then init will be NULL.  */
9312   init = build_default_init_expr (sym);
9313   if (init == NULL)
9314     return;
9315
9316   /* For saved variables, we don't want to add an initializer at 
9317      function entry, so we just add a static initializer.  */
9318   if (sym->attr.save || sym->ns->save_all 
9319       || gfc_option.flag_max_stack_var_size == 0)
9320     {
9321       /* Don't clobber an existing initializer!  */
9322       gcc_assert (sym->value == NULL);
9323       sym->value = init;
9324       return;
9325     }
9326
9327   build_init_assign (sym, init);
9328 }
9329
9330 /* Resolution of common features of flavors variable and procedure.  */
9331
9332 static gfc_try
9333 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9334 {
9335   /* Constraints on deferred shape variable.  */
9336   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9337     {
9338       if (sym->attr.allocatable)
9339         {
9340           if (sym->attr.dimension)
9341             {
9342               gfc_error ("Allocatable array '%s' at %L must have "
9343                          "a deferred shape", sym->name, &sym->declared_at);
9344               return FAILURE;
9345             }
9346           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9347                                    "may not be ALLOCATABLE", sym->name,
9348                                    &sym->declared_at) == FAILURE)
9349             return FAILURE;
9350         }
9351
9352       if (sym->attr.pointer && sym->attr.dimension)
9353         {
9354           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9355                      sym->name, &sym->declared_at);
9356           return FAILURE;
9357         }
9358
9359     }
9360   else
9361     {
9362       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9363           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
9364         {
9365           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9366                      sym->name, &sym->declared_at);
9367           return FAILURE;
9368          }
9369     }
9370
9371   /* Constraints on polymorphic variables.  */
9372   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9373     {
9374       /* F03:C502.  */
9375       if (sym->attr.class_ok
9376           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9377         {
9378           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9379                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9380                      &sym->declared_at);
9381           return FAILURE;
9382         }
9383
9384       /* F03:C509.  */
9385       /* Assume that use associated symbols were checked in the module ns.  */ 
9386       if (!sym->attr.class_ok && !sym->attr.use_assoc)
9387         {
9388           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9389                      "or pointer", sym->name, &sym->declared_at);
9390           return FAILURE;
9391         }
9392     }
9393     
9394   return SUCCESS;
9395 }
9396
9397
9398 /* Additional checks for symbols with flavor variable and derived
9399    type.  To be called from resolve_fl_variable.  */
9400
9401 static gfc_try
9402 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9403 {
9404   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9405
9406   /* Check to see if a derived type is blocked from being host
9407      associated by the presence of another class I symbol in the same
9408      namespace.  14.6.1.3 of the standard and the discussion on
9409      comp.lang.fortran.  */
9410   if (sym->ns != sym->ts.u.derived->ns
9411       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9412     {
9413       gfc_symbol *s;
9414       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9415       if (s && s->attr.flavor != FL_DERIVED)
9416         {
9417           gfc_error ("The type '%s' cannot be host associated at %L "
9418                      "because it is blocked by an incompatible object "
9419                      "of the same name declared at %L",
9420                      sym->ts.u.derived->name, &sym->declared_at,
9421                      &s->declared_at);
9422           return FAILURE;
9423         }
9424     }
9425
9426   /* 4th constraint in section 11.3: "If an object of a type for which
9427      component-initialization is specified (R429) appears in the
9428      specification-part of a module and does not have the ALLOCATABLE
9429      or POINTER attribute, the object shall have the SAVE attribute."
9430
9431      The check for initializers is performed with
9432      gfc_has_default_initializer because gfc_default_initializer generates
9433      a hidden default for allocatable components.  */
9434   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9435       && sym->ns->proc_name->attr.flavor == FL_MODULE
9436       && !sym->ns->save_all && !sym->attr.save
9437       && !sym->attr.pointer && !sym->attr.allocatable
9438       && gfc_has_default_initializer (sym->ts.u.derived)
9439       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9440                          "module variable '%s' at %L, needed due to "
9441                          "the default initialization", sym->name,
9442                          &sym->declared_at) == FAILURE)
9443     return FAILURE;
9444
9445   /* Assign default initializer.  */
9446   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9447       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9448     {
9449       sym->value = gfc_default_initializer (&sym->ts);
9450     }
9451
9452   return SUCCESS;
9453 }
9454
9455
9456 /* Resolve symbols with flavor variable.  */
9457
9458 static gfc_try
9459 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9460 {
9461   int no_init_flag, automatic_flag;
9462   gfc_expr *e;
9463   const char *auto_save_msg;
9464
9465   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9466                   "SAVE attribute";
9467
9468   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9469     return FAILURE;
9470
9471   /* Set this flag to check that variables are parameters of all entries.
9472      This check is effected by the call to gfc_resolve_expr through
9473      is_non_constant_shape_array.  */
9474   specification_expr = 1;
9475
9476   if (sym->ns->proc_name
9477       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9478           || sym->ns->proc_name->attr.is_main_program)
9479       && !sym->attr.use_assoc
9480       && !sym->attr.allocatable
9481       && !sym->attr.pointer
9482       && is_non_constant_shape_array (sym))
9483     {
9484       /* The shape of a main program or module array needs to be
9485          constant.  */
9486       gfc_error ("The module or main program array '%s' at %L must "
9487                  "have constant shape", sym->name, &sym->declared_at);
9488       specification_expr = 0;
9489       return FAILURE;
9490     }
9491
9492   if (sym->ts.type == BT_CHARACTER)
9493     {
9494       /* Make sure that character string variables with assumed length are
9495          dummy arguments.  */
9496       e = sym->ts.u.cl->length;
9497       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9498         {
9499           gfc_error ("Entity with assumed character length at %L must be a "
9500                      "dummy argument or a PARAMETER", &sym->declared_at);
9501           return FAILURE;
9502         }
9503
9504       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9505         {
9506           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9507           return FAILURE;
9508         }
9509
9510       if (!gfc_is_constant_expr (e)
9511           && !(e->expr_type == EXPR_VARIABLE
9512                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9513           && sym->ns->proc_name
9514           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9515               || sym->ns->proc_name->attr.is_main_program)
9516           && !sym->attr.use_assoc)
9517         {
9518           gfc_error ("'%s' at %L must have constant character length "
9519                      "in this context", sym->name, &sym->declared_at);
9520           return FAILURE;
9521         }
9522     }
9523
9524   if (sym->value == NULL && sym->attr.referenced)
9525     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9526
9527   /* Determine if the symbol may not have an initializer.  */
9528   no_init_flag = automatic_flag = 0;
9529   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9530       || sym->attr.intrinsic || sym->attr.result)
9531     no_init_flag = 1;
9532   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9533            && is_non_constant_shape_array (sym))
9534     {
9535       no_init_flag = automatic_flag = 1;
9536
9537       /* Also, they must not have the SAVE attribute.
9538          SAVE_IMPLICIT is checked below.  */
9539       if (sym->attr.save == SAVE_EXPLICIT)
9540         {
9541           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9542           return FAILURE;
9543         }
9544     }
9545
9546   /* Ensure that any initializer is simplified.  */
9547   if (sym->value)
9548     gfc_simplify_expr (sym->value, 1);
9549
9550   /* Reject illegal initializers.  */
9551   if (!sym->mark && sym->value)
9552     {
9553       if (sym->attr.allocatable)
9554         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9555                    sym->name, &sym->declared_at);
9556       else if (sym->attr.external)
9557         gfc_error ("External '%s' at %L cannot have an initializer",
9558                    sym->name, &sym->declared_at);
9559       else if (sym->attr.dummy
9560         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9561         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9562                    sym->name, &sym->declared_at);
9563       else if (sym->attr.intrinsic)
9564         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9565                    sym->name, &sym->declared_at);
9566       else if (sym->attr.result)
9567         gfc_error ("Function result '%s' at %L cannot have an initializer",
9568                    sym->name, &sym->declared_at);
9569       else if (automatic_flag)
9570         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9571                    sym->name, &sym->declared_at);
9572       else
9573         goto no_init_error;
9574       return FAILURE;
9575     }
9576
9577 no_init_error:
9578   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9579     return resolve_fl_variable_derived (sym, no_init_flag);
9580
9581   return SUCCESS;
9582 }
9583
9584
9585 /* Resolve a procedure.  */
9586
9587 static gfc_try
9588 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9589 {
9590   gfc_formal_arglist *arg;
9591
9592   if (sym->attr.function
9593       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9594     return FAILURE;
9595
9596   if (sym->ts.type == BT_CHARACTER)
9597     {
9598       gfc_charlen *cl = sym->ts.u.cl;
9599
9600       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9601              && resolve_charlen (cl) == FAILURE)
9602         return FAILURE;
9603
9604       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9605           && sym->attr.proc == PROC_ST_FUNCTION)
9606         {
9607           gfc_error ("Character-valued statement function '%s' at %L must "
9608                      "have constant length", sym->name, &sym->declared_at);
9609           return FAILURE;
9610         }
9611     }
9612
9613   /* Ensure that derived type for are not of a private type.  Internal
9614      module procedures are excluded by 2.2.3.3 - i.e., they are not
9615      externally accessible and can access all the objects accessible in
9616      the host.  */
9617   if (!(sym->ns->parent
9618         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9619       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9620     {
9621       gfc_interface *iface;
9622
9623       for (arg = sym->formal; arg; arg = arg->next)
9624         {
9625           if (arg->sym
9626               && arg->sym->ts.type == BT_DERIVED
9627               && !arg->sym->ts.u.derived->attr.use_assoc
9628               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9629                                     arg->sym->ts.u.derived->ns->default_access)
9630               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9631                                  "PRIVATE type and cannot be a dummy argument"
9632                                  " of '%s', which is PUBLIC at %L",
9633                                  arg->sym->name, sym->name, &sym->declared_at)
9634                  == FAILURE)
9635             {
9636               /* Stop this message from recurring.  */
9637               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9638               return FAILURE;
9639             }
9640         }
9641
9642       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9643          PRIVATE to the containing module.  */
9644       for (iface = sym->generic; iface; iface = iface->next)
9645         {
9646           for (arg = iface->sym->formal; arg; arg = arg->next)
9647             {
9648               if (arg->sym
9649                   && arg->sym->ts.type == BT_DERIVED
9650                   && !arg->sym->ts.u.derived->attr.use_assoc
9651                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9652                                         arg->sym->ts.u.derived->ns->default_access)
9653                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9654                                      "'%s' in PUBLIC interface '%s' at %L "
9655                                      "takes dummy arguments of '%s' which is "
9656                                      "PRIVATE", iface->sym->name, sym->name,
9657                                      &iface->sym->declared_at,
9658                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9659                 {
9660                   /* Stop this message from recurring.  */
9661                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9662                   return FAILURE;
9663                 }
9664              }
9665         }
9666
9667       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9668          PRIVATE to the containing module.  */
9669       for (iface = sym->generic; iface; iface = iface->next)
9670         {
9671           for (arg = iface->sym->formal; arg; arg = arg->next)
9672             {
9673               if (arg->sym
9674                   && arg->sym->ts.type == BT_DERIVED
9675                   && !arg->sym->ts.u.derived->attr.use_assoc
9676                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9677                                         arg->sym->ts.u.derived->ns->default_access)
9678                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9679                                      "'%s' in PUBLIC interface '%s' at %L "
9680                                      "takes dummy arguments of '%s' which is "
9681                                      "PRIVATE", iface->sym->name, sym->name,
9682                                      &iface->sym->declared_at,
9683                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9684                 {
9685                   /* Stop this message from recurring.  */
9686                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9687                   return FAILURE;
9688                 }
9689              }
9690         }
9691     }
9692
9693   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9694       && !sym->attr.proc_pointer)
9695     {
9696       gfc_error ("Function '%s' at %L cannot have an initializer",
9697                  sym->name, &sym->declared_at);
9698       return FAILURE;
9699     }
9700
9701   /* An external symbol may not have an initializer because it is taken to be
9702      a procedure. Exception: Procedure Pointers.  */
9703   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9704     {
9705       gfc_error ("External object '%s' at %L may not have an initializer",
9706                  sym->name, &sym->declared_at);
9707       return FAILURE;
9708     }
9709
9710   /* An elemental function is required to return a scalar 12.7.1  */
9711   if (sym->attr.elemental && sym->attr.function && sym->as)
9712     {
9713       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9714                  "result", sym->name, &sym->declared_at);
9715       /* Reset so that the error only occurs once.  */
9716       sym->attr.elemental = 0;
9717       return FAILURE;
9718     }
9719
9720   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9721      char-len-param shall not be array-valued, pointer-valued, recursive
9722      or pure.  ....snip... A character value of * may only be used in the
9723      following ways: (i) Dummy arg of procedure - dummy associates with
9724      actual length; (ii) To declare a named constant; or (iii) External
9725      function - but length must be declared in calling scoping unit.  */
9726   if (sym->attr.function
9727       && sym->ts.type == BT_CHARACTER
9728       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9729     {
9730       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9731           || (sym->attr.recursive) || (sym->attr.pure))
9732         {
9733           if (sym->as && sym->as->rank)
9734             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9735                        "array-valued", sym->name, &sym->declared_at);
9736
9737           if (sym->attr.pointer)
9738             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9739                        "pointer-valued", sym->name, &sym->declared_at);
9740
9741           if (sym->attr.pure)
9742             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9743                        "pure", sym->name, &sym->declared_at);
9744
9745           if (sym->attr.recursive)
9746             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9747                        "recursive", sym->name, &sym->declared_at);
9748
9749           return FAILURE;
9750         }
9751
9752       /* Appendix B.2 of the standard.  Contained functions give an
9753          error anyway.  Fixed-form is likely to be F77/legacy.  */
9754       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9755         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9756                         "CHARACTER(*) function '%s' at %L",
9757                         sym->name, &sym->declared_at);
9758     }
9759
9760   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9761     {
9762       gfc_formal_arglist *curr_arg;
9763       int has_non_interop_arg = 0;
9764
9765       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9766                              sym->common_block) == FAILURE)
9767         {
9768           /* Clear these to prevent looking at them again if there was an
9769              error.  */
9770           sym->attr.is_bind_c = 0;
9771           sym->attr.is_c_interop = 0;
9772           sym->ts.is_c_interop = 0;
9773         }
9774       else
9775         {
9776           /* So far, no errors have been found.  */
9777           sym->attr.is_c_interop = 1;
9778           sym->ts.is_c_interop = 1;
9779         }
9780       
9781       curr_arg = sym->formal;
9782       while (curr_arg != NULL)
9783         {
9784           /* Skip implicitly typed dummy args here.  */
9785           if (curr_arg->sym->attr.implicit_type == 0)
9786             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9787               /* If something is found to fail, record the fact so we
9788                  can mark the symbol for the procedure as not being
9789                  BIND(C) to try and prevent multiple errors being
9790                  reported.  */
9791               has_non_interop_arg = 1;
9792           
9793           curr_arg = curr_arg->next;
9794         }
9795
9796       /* See if any of the arguments were not interoperable and if so, clear
9797          the procedure symbol to prevent duplicate error messages.  */
9798       if (has_non_interop_arg != 0)
9799         {
9800           sym->attr.is_c_interop = 0;
9801           sym->ts.is_c_interop = 0;
9802           sym->attr.is_bind_c = 0;
9803         }
9804     }
9805   
9806   if (!sym->attr.proc_pointer)
9807     {
9808       if (sym->attr.save == SAVE_EXPLICIT)
9809         {
9810           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9811                      "in '%s' at %L", sym->name, &sym->declared_at);
9812           return FAILURE;
9813         }
9814       if (sym->attr.intent)
9815         {
9816           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9817                      "in '%s' at %L", sym->name, &sym->declared_at);
9818           return FAILURE;
9819         }
9820       if (sym->attr.subroutine && sym->attr.result)
9821         {
9822           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9823                      "in '%s' at %L", sym->name, &sym->declared_at);
9824           return FAILURE;
9825         }
9826       if (sym->attr.external && sym->attr.function
9827           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9828               || sym->attr.contained))
9829         {
9830           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9831                      "in '%s' at %L", sym->name, &sym->declared_at);
9832           return FAILURE;
9833         }
9834       if (strcmp ("ppr@", sym->name) == 0)
9835         {
9836           gfc_error ("Procedure pointer result '%s' at %L "
9837                      "is missing the pointer attribute",
9838                      sym->ns->proc_name->name, &sym->declared_at);
9839           return FAILURE;
9840         }
9841     }
9842
9843   return SUCCESS;
9844 }
9845
9846
9847 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9848    been defined and we now know their defined arguments, check that they fulfill
9849    the requirements of the standard for procedures used as finalizers.  */
9850
9851 static gfc_try
9852 gfc_resolve_finalizers (gfc_symbol* derived)
9853 {
9854   gfc_finalizer* list;
9855   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9856   gfc_try result = SUCCESS;
9857   bool seen_scalar = false;
9858
9859   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9860     return SUCCESS;
9861
9862   /* Walk over the list of finalizer-procedures, check them, and if any one
9863      does not fit in with the standard's definition, print an error and remove
9864      it from the list.  */
9865   prev_link = &derived->f2k_derived->finalizers;
9866   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9867     {
9868       gfc_symbol* arg;
9869       gfc_finalizer* i;
9870       int my_rank;
9871
9872       /* Skip this finalizer if we already resolved it.  */
9873       if (list->proc_tree)
9874         {
9875           prev_link = &(list->next);
9876           continue;
9877         }
9878
9879       /* Check this exists and is a SUBROUTINE.  */
9880       if (!list->proc_sym->attr.subroutine)
9881         {
9882           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9883                      list->proc_sym->name, &list->where);
9884           goto error;
9885         }
9886
9887       /* We should have exactly one argument.  */
9888       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9889         {
9890           gfc_error ("FINAL procedure at %L must have exactly one argument",
9891                      &list->where);
9892           goto error;
9893         }
9894       arg = list->proc_sym->formal->sym;
9895
9896       /* This argument must be of our type.  */
9897       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9898         {
9899           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9900                      &arg->declared_at, derived->name);
9901           goto error;
9902         }
9903
9904       /* It must neither be a pointer nor allocatable nor optional.  */
9905       if (arg->attr.pointer)
9906         {
9907           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9908                      &arg->declared_at);
9909           goto error;
9910         }
9911       if (arg->attr.allocatable)
9912         {
9913           gfc_error ("Argument of FINAL procedure at %L must not be"
9914                      " ALLOCATABLE", &arg->declared_at);
9915           goto error;
9916         }
9917       if (arg->attr.optional)
9918         {
9919           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9920                      &arg->declared_at);
9921           goto error;
9922         }
9923
9924       /* It must not be INTENT(OUT).  */
9925       if (arg->attr.intent == INTENT_OUT)
9926         {
9927           gfc_error ("Argument of FINAL procedure at %L must not be"
9928                      " INTENT(OUT)", &arg->declared_at);
9929           goto error;
9930         }
9931
9932       /* Warn if the procedure is non-scalar and not assumed shape.  */
9933       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9934           && arg->as->type != AS_ASSUMED_SHAPE)
9935         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9936                      " shape argument", &arg->declared_at);
9937
9938       /* Check that it does not match in kind and rank with a FINAL procedure
9939          defined earlier.  To really loop over the *earlier* declarations,
9940          we need to walk the tail of the list as new ones were pushed at the
9941          front.  */
9942       /* TODO: Handle kind parameters once they are implemented.  */
9943       my_rank = (arg->as ? arg->as->rank : 0);
9944       for (i = list->next; i; i = i->next)
9945         {
9946           /* Argument list might be empty; that is an error signalled earlier,
9947              but we nevertheless continued resolving.  */
9948           if (i->proc_sym->formal)
9949             {
9950               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9951               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9952               if (i_rank == my_rank)
9953                 {
9954                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9955                              " rank (%d) as '%s'",
9956                              list->proc_sym->name, &list->where, my_rank, 
9957                              i->proc_sym->name);
9958                   goto error;
9959                 }
9960             }
9961         }
9962
9963         /* Is this the/a scalar finalizer procedure?  */
9964         if (!arg->as || arg->as->rank == 0)
9965           seen_scalar = true;
9966
9967         /* Find the symtree for this procedure.  */
9968         gcc_assert (!list->proc_tree);
9969         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9970
9971         prev_link = &list->next;
9972         continue;
9973
9974         /* Remove wrong nodes immediately from the list so we don't risk any
9975            troubles in the future when they might fail later expectations.  */
9976 error:
9977         result = FAILURE;
9978         i = list;
9979         *prev_link = list->next;
9980         gfc_free_finalizer (i);
9981     }
9982
9983   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9984      were nodes in the list, must have been for arrays.  It is surely a good
9985      idea to have a scalar version there if there's something to finalize.  */
9986   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9987     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9988                  " defined at %L, suggest also scalar one",
9989                  derived->name, &derived->declared_at);
9990
9991   /* TODO:  Remove this error when finalization is finished.  */
9992   gfc_error ("Finalization at %L is not yet implemented",
9993              &derived->declared_at);
9994
9995   return result;
9996 }
9997
9998
9999 /* Check that it is ok for the typebound procedure proc to override the
10000    procedure old.  */
10001
10002 static gfc_try
10003 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10004 {
10005   locus where;
10006   const gfc_symbol* proc_target;
10007   const gfc_symbol* old_target;
10008   unsigned proc_pass_arg, old_pass_arg, argpos;
10009   gfc_formal_arglist* proc_formal;
10010   gfc_formal_arglist* old_formal;
10011
10012   /* This procedure should only be called for non-GENERIC proc.  */
10013   gcc_assert (!proc->n.tb->is_generic);
10014
10015   /* If the overwritten procedure is GENERIC, this is an error.  */
10016   if (old->n.tb->is_generic)
10017     {
10018       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10019                  old->name, &proc->n.tb->where);
10020       return FAILURE;
10021     }
10022
10023   where = proc->n.tb->where;
10024   proc_target = proc->n.tb->u.specific->n.sym;
10025   old_target = old->n.tb->u.specific->n.sym;
10026
10027   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10028   if (old->n.tb->non_overridable)
10029     {
10030       gfc_error ("'%s' at %L overrides a procedure binding declared"
10031                  " NON_OVERRIDABLE", proc->name, &where);
10032       return FAILURE;
10033     }
10034
10035   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10036   if (!old->n.tb->deferred && proc->n.tb->deferred)
10037     {
10038       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10039                  " non-DEFERRED binding", proc->name, &where);
10040       return FAILURE;
10041     }
10042
10043   /* If the overridden binding is PURE, the overriding must be, too.  */
10044   if (old_target->attr.pure && !proc_target->attr.pure)
10045     {
10046       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10047                  proc->name, &where);
10048       return FAILURE;
10049     }
10050
10051   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10052      is not, the overriding must not be either.  */
10053   if (old_target->attr.elemental && !proc_target->attr.elemental)
10054     {
10055       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10056                  " ELEMENTAL", proc->name, &where);
10057       return FAILURE;
10058     }
10059   if (!old_target->attr.elemental && proc_target->attr.elemental)
10060     {
10061       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10062                  " be ELEMENTAL, either", proc->name, &where);
10063       return FAILURE;
10064     }
10065
10066   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10067      SUBROUTINE.  */
10068   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10069     {
10070       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10071                  " SUBROUTINE", proc->name, &where);
10072       return FAILURE;
10073     }
10074
10075   /* If the overridden binding is a FUNCTION, the overriding must also be a
10076      FUNCTION and have the same characteristics.  */
10077   if (old_target->attr.function)
10078     {
10079       if (!proc_target->attr.function)
10080         {
10081           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10082                      " FUNCTION", proc->name, &where);
10083           return FAILURE;
10084         }
10085
10086       /* FIXME:  Do more comprehensive checking (including, for instance, the
10087          rank and array-shape).  */
10088       gcc_assert (proc_target->result && old_target->result);
10089       if (!gfc_compare_types (&proc_target->result->ts,
10090                               &old_target->result->ts))
10091         {
10092           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10093                      " matching result types", proc->name, &where);
10094           return FAILURE;
10095         }
10096     }
10097
10098   /* If the overridden binding is PUBLIC, the overriding one must not be
10099      PRIVATE.  */
10100   if (old->n.tb->access == ACCESS_PUBLIC
10101       && proc->n.tb->access == ACCESS_PRIVATE)
10102     {
10103       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10104                  " PRIVATE", proc->name, &where);
10105       return FAILURE;
10106     }
10107
10108   /* Compare the formal argument lists of both procedures.  This is also abused
10109      to find the position of the passed-object dummy arguments of both
10110      bindings as at least the overridden one might not yet be resolved and we
10111      need those positions in the check below.  */
10112   proc_pass_arg = old_pass_arg = 0;
10113   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10114     proc_pass_arg = 1;
10115   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10116     old_pass_arg = 1;
10117   argpos = 1;
10118   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10119        proc_formal && old_formal;
10120        proc_formal = proc_formal->next, old_formal = old_formal->next)
10121     {
10122       if (proc->n.tb->pass_arg
10123           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10124         proc_pass_arg = argpos;
10125       if (old->n.tb->pass_arg
10126           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10127         old_pass_arg = argpos;
10128
10129       /* Check that the names correspond.  */
10130       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10131         {
10132           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10133                      " to match the corresponding argument of the overridden"
10134                      " procedure", proc_formal->sym->name, proc->name, &where,
10135                      old_formal->sym->name);
10136           return FAILURE;
10137         }
10138
10139       /* Check that the types correspond if neither is the passed-object
10140          argument.  */
10141       /* FIXME:  Do more comprehensive testing here.  */
10142       if (proc_pass_arg != argpos && old_pass_arg != argpos
10143           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10144         {
10145           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10146                      "in respect to the overridden procedure",
10147                      proc_formal->sym->name, proc->name, &where);
10148           return FAILURE;
10149         }
10150
10151       ++argpos;
10152     }
10153   if (proc_formal || old_formal)
10154     {
10155       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10156                  " the overridden procedure", proc->name, &where);
10157       return FAILURE;
10158     }
10159
10160   /* If the overridden binding is NOPASS, the overriding one must also be
10161      NOPASS.  */
10162   if (old->n.tb->nopass && !proc->n.tb->nopass)
10163     {
10164       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10165                  " NOPASS", proc->name, &where);
10166       return FAILURE;
10167     }
10168
10169   /* If the overridden binding is PASS(x), the overriding one must also be
10170      PASS and the passed-object dummy arguments must correspond.  */
10171   if (!old->n.tb->nopass)
10172     {
10173       if (proc->n.tb->nopass)
10174         {
10175           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10176                      " PASS", proc->name, &where);
10177           return FAILURE;
10178         }
10179
10180       if (proc_pass_arg != old_pass_arg)
10181         {
10182           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10183                      " the same position as the passed-object dummy argument of"
10184                      " the overridden procedure", proc->name, &where);
10185           return FAILURE;
10186         }
10187     }
10188
10189   return SUCCESS;
10190 }
10191
10192
10193 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10194
10195 static gfc_try
10196 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10197                              const char* generic_name, locus where)
10198 {
10199   gfc_symbol* sym1;
10200   gfc_symbol* sym2;
10201
10202   gcc_assert (t1->specific && t2->specific);
10203   gcc_assert (!t1->specific->is_generic);
10204   gcc_assert (!t2->specific->is_generic);
10205
10206   sym1 = t1->specific->u.specific->n.sym;
10207   sym2 = t2->specific->u.specific->n.sym;
10208
10209   if (sym1 == sym2)
10210     return SUCCESS;
10211
10212   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10213   if (sym1->attr.subroutine != sym2->attr.subroutine
10214       || sym1->attr.function != sym2->attr.function)
10215     {
10216       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10217                  " GENERIC '%s' at %L",
10218                  sym1->name, sym2->name, generic_name, &where);
10219       return FAILURE;
10220     }
10221
10222   /* Compare the interfaces.  */
10223   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10224     {
10225       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10226                  sym1->name, sym2->name, generic_name, &where);
10227       return FAILURE;
10228     }
10229
10230   return SUCCESS;
10231 }
10232
10233
10234 /* Worker function for resolving a generic procedure binding; this is used to
10235    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10236
10237    The difference between those cases is finding possible inherited bindings
10238    that are overridden, as one has to look for them in tb_sym_root,
10239    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10240    the super-type and set p->overridden correctly.  */
10241
10242 static gfc_try
10243 resolve_tb_generic_targets (gfc_symbol* super_type,
10244                             gfc_typebound_proc* p, const char* name)
10245 {
10246   gfc_tbp_generic* target;
10247   gfc_symtree* first_target;
10248   gfc_symtree* inherited;
10249
10250   gcc_assert (p && p->is_generic);
10251
10252   /* Try to find the specific bindings for the symtrees in our target-list.  */
10253   gcc_assert (p->u.generic);
10254   for (target = p->u.generic; target; target = target->next)
10255     if (!target->specific)
10256       {
10257         gfc_typebound_proc* overridden_tbp;
10258         gfc_tbp_generic* g;
10259         const char* target_name;
10260
10261         target_name = target->specific_st->name;
10262
10263         /* Defined for this type directly.  */
10264         if (target->specific_st->n.tb)
10265           {
10266             target->specific = target->specific_st->n.tb;
10267             goto specific_found;
10268           }
10269
10270         /* Look for an inherited specific binding.  */
10271         if (super_type)
10272           {
10273             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10274                                                  true, NULL);
10275
10276             if (inherited)
10277               {
10278                 gcc_assert (inherited->n.tb);
10279                 target->specific = inherited->n.tb;
10280                 goto specific_found;
10281               }
10282           }
10283
10284         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10285                    " at %L", target_name, name, &p->where);
10286         return FAILURE;
10287
10288         /* Once we've found the specific binding, check it is not ambiguous with
10289            other specifics already found or inherited for the same GENERIC.  */
10290 specific_found:
10291         gcc_assert (target->specific);
10292
10293         /* This must really be a specific binding!  */
10294         if (target->specific->is_generic)
10295           {
10296             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10297                        " '%s' is GENERIC, too", name, &p->where, target_name);
10298             return FAILURE;
10299           }
10300
10301         /* Check those already resolved on this type directly.  */
10302         for (g = p->u.generic; g; g = g->next)
10303           if (g != target && g->specific
10304               && check_generic_tbp_ambiguity (target, g, name, p->where)
10305                   == FAILURE)
10306             return FAILURE;
10307
10308         /* Check for ambiguity with inherited specific targets.  */
10309         for (overridden_tbp = p->overridden; overridden_tbp;
10310              overridden_tbp = overridden_tbp->overridden)
10311           if (overridden_tbp->is_generic)
10312             {
10313               for (g = overridden_tbp->u.generic; g; g = g->next)
10314                 {
10315                   gcc_assert (g->specific);
10316                   if (check_generic_tbp_ambiguity (target, g,
10317                                                    name, p->where) == FAILURE)
10318                     return FAILURE;
10319                 }
10320             }
10321       }
10322
10323   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10324   if (p->overridden && !p->overridden->is_generic)
10325     {
10326       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10327                  " the same name", name, &p->where);
10328       return FAILURE;
10329     }
10330
10331   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10332      all must have the same attributes here.  */
10333   first_target = p->u.generic->specific->u.specific;
10334   gcc_assert (first_target);
10335   p->subroutine = first_target->n.sym->attr.subroutine;
10336   p->function = first_target->n.sym->attr.function;
10337
10338   return SUCCESS;
10339 }
10340
10341
10342 /* Resolve a GENERIC procedure binding for a derived type.  */
10343
10344 static gfc_try
10345 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10346 {
10347   gfc_symbol* super_type;
10348
10349   /* Find the overridden binding if any.  */
10350   st->n.tb->overridden = NULL;
10351   super_type = gfc_get_derived_super_type (derived);
10352   if (super_type)
10353     {
10354       gfc_symtree* overridden;
10355       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10356                                             true, NULL);
10357
10358       if (overridden && overridden->n.tb)
10359         st->n.tb->overridden = overridden->n.tb;
10360     }
10361
10362   /* Resolve using worker function.  */
10363   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10364 }
10365
10366
10367 /* Retrieve the target-procedure of an operator binding and do some checks in
10368    common for intrinsic and user-defined type-bound operators.  */
10369
10370 static gfc_symbol*
10371 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10372 {
10373   gfc_symbol* target_proc;
10374
10375   gcc_assert (target->specific && !target->specific->is_generic);
10376   target_proc = target->specific->u.specific->n.sym;
10377   gcc_assert (target_proc);
10378
10379   /* All operator bindings must have a passed-object dummy argument.  */
10380   if (target->specific->nopass)
10381     {
10382       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10383       return NULL;
10384     }
10385
10386   return target_proc;
10387 }
10388
10389
10390 /* Resolve a type-bound intrinsic operator.  */
10391
10392 static gfc_try
10393 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10394                                 gfc_typebound_proc* p)
10395 {
10396   gfc_symbol* super_type;
10397   gfc_tbp_generic* target;
10398   
10399   /* If there's already an error here, do nothing (but don't fail again).  */
10400   if (p->error)
10401     return SUCCESS;
10402
10403   /* Operators should always be GENERIC bindings.  */
10404   gcc_assert (p->is_generic);
10405
10406   /* Look for an overridden binding.  */
10407   super_type = gfc_get_derived_super_type (derived);
10408   if (super_type && super_type->f2k_derived)
10409     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10410                                                      op, true, NULL);
10411   else
10412     p->overridden = NULL;
10413
10414   /* Resolve general GENERIC properties using worker function.  */
10415   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10416     goto error;
10417
10418   /* Check the targets to be procedures of correct interface.  */
10419   for (target = p->u.generic; target; target = target->next)
10420     {
10421       gfc_symbol* target_proc;
10422
10423       target_proc = get_checked_tb_operator_target (target, p->where);
10424       if (!target_proc)
10425         goto error;
10426
10427       if (!gfc_check_operator_interface (target_proc, op, p->where))
10428         goto error;
10429     }
10430
10431   return SUCCESS;
10432
10433 error:
10434   p->error = 1;
10435   return FAILURE;
10436 }
10437
10438
10439 /* Resolve a type-bound user operator (tree-walker callback).  */
10440
10441 static gfc_symbol* resolve_bindings_derived;
10442 static gfc_try resolve_bindings_result;
10443
10444 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10445
10446 static void
10447 resolve_typebound_user_op (gfc_symtree* stree)
10448 {
10449   gfc_symbol* super_type;
10450   gfc_tbp_generic* target;
10451
10452   gcc_assert (stree && stree->n.tb);
10453
10454   if (stree->n.tb->error)
10455     return;
10456
10457   /* Operators should always be GENERIC bindings.  */
10458   gcc_assert (stree->n.tb->is_generic);
10459
10460   /* Find overridden procedure, if any.  */
10461   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10462   if (super_type && super_type->f2k_derived)
10463     {
10464       gfc_symtree* overridden;
10465       overridden = gfc_find_typebound_user_op (super_type, NULL,
10466                                                stree->name, true, NULL);
10467
10468       if (overridden && overridden->n.tb)
10469         stree->n.tb->overridden = overridden->n.tb;
10470     }
10471   else
10472     stree->n.tb->overridden = NULL;
10473
10474   /* Resolve basically using worker function.  */
10475   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10476         == FAILURE)
10477     goto error;
10478
10479   /* Check the targets to be functions of correct interface.  */
10480   for (target = stree->n.tb->u.generic; target; target = target->next)
10481     {
10482       gfc_symbol* target_proc;
10483
10484       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10485       if (!target_proc)
10486         goto error;
10487
10488       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10489         goto error;
10490     }
10491
10492   return;
10493
10494 error:
10495   resolve_bindings_result = FAILURE;
10496   stree->n.tb->error = 1;
10497 }
10498
10499
10500 /* Resolve the type-bound procedures for a derived type.  */
10501
10502 static void
10503 resolve_typebound_procedure (gfc_symtree* stree)
10504 {
10505   gfc_symbol* proc;
10506   locus where;
10507   gfc_symbol* me_arg;
10508   gfc_symbol* super_type;
10509   gfc_component* comp;
10510
10511   gcc_assert (stree);
10512
10513   /* Undefined specific symbol from GENERIC target definition.  */
10514   if (!stree->n.tb)
10515     return;
10516
10517   if (stree->n.tb->error)
10518     return;
10519
10520   /* If this is a GENERIC binding, use that routine.  */
10521   if (stree->n.tb->is_generic)
10522     {
10523       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10524             == FAILURE)
10525         goto error;
10526       return;
10527     }
10528
10529   /* Get the target-procedure to check it.  */
10530   gcc_assert (!stree->n.tb->is_generic);
10531   gcc_assert (stree->n.tb->u.specific);
10532   proc = stree->n.tb->u.specific->n.sym;
10533   where = stree->n.tb->where;
10534
10535   /* Default access should already be resolved from the parser.  */
10536   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10537
10538   /* It should be a module procedure or an external procedure with explicit
10539      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10540   if ((!proc->attr.subroutine && !proc->attr.function)
10541       || (proc->attr.proc != PROC_MODULE
10542           && proc->attr.if_source != IFSRC_IFBODY)
10543       || (proc->attr.abstract && !stree->n.tb->deferred))
10544     {
10545       gfc_error ("'%s' must be a module procedure or an external procedure with"
10546                  " an explicit interface at %L", proc->name, &where);
10547       goto error;
10548     }
10549   stree->n.tb->subroutine = proc->attr.subroutine;
10550   stree->n.tb->function = proc->attr.function;
10551
10552   /* Find the super-type of the current derived type.  We could do this once and
10553      store in a global if speed is needed, but as long as not I believe this is
10554      more readable and clearer.  */
10555   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10556
10557   /* If PASS, resolve and check arguments if not already resolved / loaded
10558      from a .mod file.  */
10559   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10560     {
10561       if (stree->n.tb->pass_arg)
10562         {
10563           gfc_formal_arglist* i;
10564
10565           /* If an explicit passing argument name is given, walk the arg-list
10566              and look for it.  */
10567
10568           me_arg = NULL;
10569           stree->n.tb->pass_arg_num = 1;
10570           for (i = proc->formal; i; i = i->next)
10571             {
10572               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10573                 {
10574                   me_arg = i->sym;
10575                   break;
10576                 }
10577               ++stree->n.tb->pass_arg_num;
10578             }
10579
10580           if (!me_arg)
10581             {
10582               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10583                          " argument '%s'",
10584                          proc->name, stree->n.tb->pass_arg, &where,
10585                          stree->n.tb->pass_arg);
10586               goto error;
10587             }
10588         }
10589       else
10590         {
10591           /* Otherwise, take the first one; there should in fact be at least
10592              one.  */
10593           stree->n.tb->pass_arg_num = 1;
10594           if (!proc->formal)
10595             {
10596               gfc_error ("Procedure '%s' with PASS at %L must have at"
10597                          " least one argument", proc->name, &where);
10598               goto error;
10599             }
10600           me_arg = proc->formal->sym;
10601         }
10602
10603       /* Now check that the argument-type matches and the passed-object
10604          dummy argument is generally fine.  */
10605
10606       gcc_assert (me_arg);
10607
10608       if (me_arg->ts.type != BT_CLASS)
10609         {
10610           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10611                      " at %L", proc->name, &where);
10612           goto error;
10613         }
10614
10615       if (CLASS_DATA (me_arg)->ts.u.derived
10616           != resolve_bindings_derived)
10617         {
10618           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10619                      " the derived-type '%s'", me_arg->name, proc->name,
10620                      me_arg->name, &where, resolve_bindings_derived->name);
10621           goto error;
10622         }
10623   
10624       gcc_assert (me_arg->ts.type == BT_CLASS);
10625       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
10626         {
10627           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10628                      " scalar", proc->name, &where);
10629           goto error;
10630         }
10631       if (CLASS_DATA (me_arg)->attr.allocatable)
10632         {
10633           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10634                      " be ALLOCATABLE", proc->name, &where);
10635           goto error;
10636         }
10637       if (CLASS_DATA (me_arg)->attr.class_pointer)
10638         {
10639           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10640                      " be POINTER", proc->name, &where);
10641           goto error;
10642         }
10643     }
10644
10645   /* If we are extending some type, check that we don't override a procedure
10646      flagged NON_OVERRIDABLE.  */
10647   stree->n.tb->overridden = NULL;
10648   if (super_type)
10649     {
10650       gfc_symtree* overridden;
10651       overridden = gfc_find_typebound_proc (super_type, NULL,
10652                                             stree->name, true, NULL);
10653
10654       if (overridden && overridden->n.tb)
10655         stree->n.tb->overridden = overridden->n.tb;
10656
10657       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10658         goto error;
10659     }
10660
10661   /* See if there's a name collision with a component directly in this type.  */
10662   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10663     if (!strcmp (comp->name, stree->name))
10664       {
10665         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10666                    " '%s'",
10667                    stree->name, &where, resolve_bindings_derived->name);
10668         goto error;
10669       }
10670
10671   /* Try to find a name collision with an inherited component.  */
10672   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10673     {
10674       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10675                  " component of '%s'",
10676                  stree->name, &where, resolve_bindings_derived->name);
10677       goto error;
10678     }
10679
10680   stree->n.tb->error = 0;
10681   return;
10682
10683 error:
10684   resolve_bindings_result = FAILURE;
10685   stree->n.tb->error = 1;
10686 }
10687
10688 static gfc_try
10689 resolve_typebound_procedures (gfc_symbol* derived)
10690 {
10691   int op;
10692
10693   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10694     return SUCCESS;
10695
10696   resolve_bindings_derived = derived;
10697   resolve_bindings_result = SUCCESS;
10698
10699   if (derived->f2k_derived->tb_sym_root)
10700     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10701                           &resolve_typebound_procedure);
10702
10703   if (derived->f2k_derived->tb_uop_root)
10704     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10705                           &resolve_typebound_user_op);
10706
10707   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10708     {
10709       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10710       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10711                                                p) == FAILURE)
10712         resolve_bindings_result = FAILURE;
10713     }
10714
10715   return resolve_bindings_result;
10716 }
10717
10718
10719 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10720    to give all identical derived types the same backend_decl.  */
10721 static void
10722 add_dt_to_dt_list (gfc_symbol *derived)
10723 {
10724   gfc_dt_list *dt_list;
10725
10726   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10727     if (derived == dt_list->derived)
10728       break;
10729
10730   if (dt_list == NULL)
10731     {
10732       dt_list = gfc_get_dt_list ();
10733       dt_list->next = gfc_derived_types;
10734       dt_list->derived = derived;
10735       gfc_derived_types = dt_list;
10736     }
10737 }
10738
10739
10740 /* Ensure that a derived-type is really not abstract, meaning that every
10741    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10742
10743 static gfc_try
10744 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10745 {
10746   if (!st)
10747     return SUCCESS;
10748
10749   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10750     return FAILURE;
10751   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10752     return FAILURE;
10753
10754   if (st->n.tb && st->n.tb->deferred)
10755     {
10756       gfc_symtree* overriding;
10757       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10758       if (!overriding)
10759         return FAILURE;
10760       gcc_assert (overriding->n.tb);
10761       if (overriding->n.tb->deferred)
10762         {
10763           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10764                      " '%s' is DEFERRED and not overridden",
10765                      sub->name, &sub->declared_at, st->name);
10766           return FAILURE;
10767         }
10768     }
10769
10770   return SUCCESS;
10771 }
10772
10773 static gfc_try
10774 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10775 {
10776   /* The algorithm used here is to recursively travel up the ancestry of sub
10777      and for each ancestor-type, check all bindings.  If any of them is
10778      DEFERRED, look it up starting from sub and see if the found (overriding)
10779      binding is not DEFERRED.
10780      This is not the most efficient way to do this, but it should be ok and is
10781      clearer than something sophisticated.  */
10782
10783   gcc_assert (ancestor && !sub->attr.abstract);
10784   
10785   if (!ancestor->attr.abstract)
10786     return SUCCESS;
10787
10788   /* Walk bindings of this ancestor.  */
10789   if (ancestor->f2k_derived)
10790     {
10791       gfc_try t;
10792       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10793       if (t == FAILURE)
10794         return FAILURE;
10795     }
10796
10797   /* Find next ancestor type and recurse on it.  */
10798   ancestor = gfc_get_derived_super_type (ancestor);
10799   if (ancestor)
10800     return ensure_not_abstract (sub, ancestor);
10801
10802   return SUCCESS;
10803 }
10804
10805
10806 static void resolve_symbol (gfc_symbol *sym);
10807
10808
10809 /* Resolve the components of a derived type.  */
10810
10811 static gfc_try
10812 resolve_fl_derived (gfc_symbol *sym)
10813 {
10814   gfc_symbol* super_type;
10815   gfc_component *c;
10816
10817   super_type = gfc_get_derived_super_type (sym);
10818   
10819   if (sym->attr.is_class && sym->ts.u.derived == NULL)
10820     {
10821       /* Fix up incomplete CLASS symbols.  */
10822       gfc_component *data = gfc_find_component (sym, "$data", true, true);
10823       gfc_component *vptr = gfc_find_component (sym, "$vptr", true, true);
10824       if (vptr->ts.u.derived == NULL)
10825         {
10826           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
10827           gcc_assert (vtab);
10828           vptr->ts.u.derived = vtab->ts.u.derived;
10829         }
10830     }
10831
10832   /* F2008, C432. */
10833   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
10834     {
10835       gfc_error ("As extending type '%s' at %L has a coarray component, "
10836                  "parent type '%s' shall also have one", sym->name,
10837                  &sym->declared_at, super_type->name);
10838       return FAILURE;
10839     }
10840
10841   /* Ensure the extended type gets resolved before we do.  */
10842   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10843     return FAILURE;
10844
10845   /* An ABSTRACT type must be extensible.  */
10846   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10847     {
10848       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10849                  sym->name, &sym->declared_at);
10850       return FAILURE;
10851     }
10852
10853   for (c = sym->components; c != NULL; c = c->next)
10854     {
10855       /* F2008, C442.  */
10856       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
10857           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
10858         {
10859           gfc_error ("Coarray component '%s' at %L must be allocatable with "
10860                      "deferred shape", c->name, &c->loc);
10861           return FAILURE;
10862         }
10863
10864       /* F2008, C443.  */
10865       if (c->attr.codimension && c->ts.type == BT_DERIVED
10866           && c->ts.u.derived->ts.is_iso_c)
10867         {
10868           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
10869                      "shall not be a coarray", c->name, &c->loc);
10870           return FAILURE;
10871         }
10872
10873       /* F2008, C444.  */
10874       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
10875           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
10876               || c->attr.allocatable))
10877         {
10878           gfc_error ("Component '%s' at %L with coarray component "
10879                      "shall be a nonpointer, nonallocatable scalar",
10880                      c->name, &c->loc);
10881           return FAILURE;
10882         }
10883
10884       /* F2008, C448.  */
10885       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
10886         {
10887           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
10888                      "is not an array pointer", c->name, &c->loc);
10889           return FAILURE;
10890         }
10891
10892       if (c->attr.proc_pointer && c->ts.interface)
10893         {
10894           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
10895             gfc_error ("Interface '%s', used by procedure pointer component "
10896                        "'%s' at %L, is declared in a later PROCEDURE statement",
10897                        c->ts.interface->name, c->name, &c->loc);
10898
10899           /* Get the attributes from the interface (now resolved).  */
10900           if (c->ts.interface->attr.if_source
10901               || c->ts.interface->attr.intrinsic)
10902             {
10903               gfc_symbol *ifc = c->ts.interface;
10904
10905               if (ifc->formal && !ifc->formal_ns)
10906                 resolve_symbol (ifc);
10907
10908               if (ifc->attr.intrinsic)
10909                 resolve_intrinsic (ifc, &ifc->declared_at);
10910
10911               if (ifc->result)
10912                 {
10913                   c->ts = ifc->result->ts;
10914                   c->attr.allocatable = ifc->result->attr.allocatable;
10915                   c->attr.pointer = ifc->result->attr.pointer;
10916                   c->attr.dimension = ifc->result->attr.dimension;
10917                   c->as = gfc_copy_array_spec (ifc->result->as);
10918                 }
10919               else
10920                 {   
10921                   c->ts = ifc->ts;
10922                   c->attr.allocatable = ifc->attr.allocatable;
10923                   c->attr.pointer = ifc->attr.pointer;
10924                   c->attr.dimension = ifc->attr.dimension;
10925                   c->as = gfc_copy_array_spec (ifc->as);
10926                 }
10927               c->ts.interface = ifc;
10928               c->attr.function = ifc->attr.function;
10929               c->attr.subroutine = ifc->attr.subroutine;
10930               gfc_copy_formal_args_ppc (c, ifc);
10931
10932               c->attr.pure = ifc->attr.pure;
10933               c->attr.elemental = ifc->attr.elemental;
10934               c->attr.recursive = ifc->attr.recursive;
10935               c->attr.always_explicit = ifc->attr.always_explicit;
10936               c->attr.ext_attr |= ifc->attr.ext_attr;
10937               /* Replace symbols in array spec.  */
10938               if (c->as)
10939                 {
10940                   int i;
10941                   for (i = 0; i < c->as->rank; i++)
10942                     {
10943                       gfc_expr_replace_comp (c->as->lower[i], c);
10944                       gfc_expr_replace_comp (c->as->upper[i], c);
10945                     }
10946                 }
10947               /* Copy char length.  */
10948               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10949                 {
10950                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10951                   gfc_expr_replace_comp (cl->length, c);
10952                   if (cl->length && !cl->resolved
10953                         && gfc_resolve_expr (cl->length) == FAILURE)
10954                     return FAILURE;
10955                   c->ts.u.cl = cl;
10956                 }
10957             }
10958           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
10959             {
10960               gfc_error ("Interface '%s' of procedure pointer component "
10961                          "'%s' at %L must be explicit", c->ts.interface->name,
10962                          c->name, &c->loc);
10963               return FAILURE;
10964             }
10965         }
10966       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10967         {
10968           /* Since PPCs are not implicitly typed, a PPC without an explicit
10969              interface must be a subroutine.  */
10970           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10971         }
10972
10973       /* Procedure pointer components: Check PASS arg.  */
10974       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
10975           && !sym->attr.vtype)
10976         {
10977           gfc_symbol* me_arg;
10978
10979           if (c->tb->pass_arg)
10980             {
10981               gfc_formal_arglist* i;
10982
10983               /* If an explicit passing argument name is given, walk the arg-list
10984                 and look for it.  */
10985
10986               me_arg = NULL;
10987               c->tb->pass_arg_num = 1;
10988               for (i = c->formal; i; i = i->next)
10989                 {
10990                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10991                     {
10992                       me_arg = i->sym;
10993                       break;
10994                     }
10995                   c->tb->pass_arg_num++;
10996                 }
10997
10998               if (!me_arg)
10999                 {
11000                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11001                              "at %L has no argument '%s'", c->name,
11002                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11003                   c->tb->error = 1;
11004                   return FAILURE;
11005                 }
11006             }
11007           else
11008             {
11009               /* Otherwise, take the first one; there should in fact be at least
11010                 one.  */
11011               c->tb->pass_arg_num = 1;
11012               if (!c->formal)
11013                 {
11014                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11015                              "must have at least one argument",
11016                              c->name, &c->loc);
11017                   c->tb->error = 1;
11018                   return FAILURE;
11019                 }
11020               me_arg = c->formal->sym;
11021             }
11022
11023           /* Now check that the argument-type matches.  */
11024           gcc_assert (me_arg);
11025           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11026               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11027               || (me_arg->ts.type == BT_CLASS
11028                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11029             {
11030               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11031                          " the derived type '%s'", me_arg->name, c->name,
11032                          me_arg->name, &c->loc, sym->name);
11033               c->tb->error = 1;
11034               return FAILURE;
11035             }
11036
11037           /* Check for C453.  */
11038           if (me_arg->attr.dimension)
11039             {
11040               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11041                          "must be scalar", me_arg->name, c->name, me_arg->name,
11042                          &c->loc);
11043               c->tb->error = 1;
11044               return FAILURE;
11045             }
11046
11047           if (me_arg->attr.pointer)
11048             {
11049               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11050                          "may not have the POINTER attribute", me_arg->name,
11051                          c->name, me_arg->name, &c->loc);
11052               c->tb->error = 1;
11053               return FAILURE;
11054             }
11055
11056           if (me_arg->attr.allocatable)
11057             {
11058               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11059                          "may not be ALLOCATABLE", me_arg->name, c->name,
11060                          me_arg->name, &c->loc);
11061               c->tb->error = 1;
11062               return FAILURE;
11063             }
11064
11065           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11066             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11067                        " at %L", c->name, &c->loc);
11068
11069         }
11070
11071       /* Check type-spec if this is not the parent-type component.  */
11072       if ((!sym->attr.extension || c != sym->components)
11073           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11074         return FAILURE;
11075
11076       /* If this type is an extension, set the accessibility of the parent
11077          component.  */
11078       if (super_type && c == sym->components
11079           && strcmp (super_type->name, c->name) == 0)
11080         c->attr.access = super_type->attr.access;
11081       
11082       /* If this type is an extension, see if this component has the same name
11083          as an inherited type-bound procedure.  */
11084       if (super_type && !sym->attr.is_class
11085           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11086         {
11087           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11088                      " inherited type-bound procedure",
11089                      c->name, sym->name, &c->loc);
11090           return FAILURE;
11091         }
11092
11093       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
11094         {
11095          if (c->ts.u.cl->length == NULL
11096              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11097              || !gfc_is_constant_expr (c->ts.u.cl->length))
11098            {
11099              gfc_error ("Character length of component '%s' needs to "
11100                         "be a constant specification expression at %L",
11101                         c->name,
11102                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11103              return FAILURE;
11104            }
11105         }
11106
11107       if (c->ts.type == BT_DERIVED
11108           && sym->component_access != ACCESS_PRIVATE
11109           && gfc_check_access (sym->attr.access, sym->ns->default_access)
11110           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11111           && !c->ts.u.derived->attr.use_assoc
11112           && !gfc_check_access (c->ts.u.derived->attr.access,
11113                                 c->ts.u.derived->ns->default_access)
11114           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11115                              "is a PRIVATE type and cannot be a component of "
11116                              "'%s', which is PUBLIC at %L", c->name,
11117                              sym->name, &sym->declared_at) == FAILURE)
11118         return FAILURE;
11119
11120       if (sym->attr.sequence)
11121         {
11122           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11123             {
11124               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11125                          "not have the SEQUENCE attribute",
11126                          c->ts.u.derived->name, &sym->declared_at);
11127               return FAILURE;
11128             }
11129         }
11130
11131       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && c->attr.pointer
11132           && c->ts.u.derived->components == NULL
11133           && !c->ts.u.derived->attr.zero_comp)
11134         {
11135           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11136                      "that has not been declared", c->name, sym->name,
11137                      &c->loc);
11138           return FAILURE;
11139         }
11140
11141       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.class_pointer
11142           && CLASS_DATA (c)->ts.u.derived->components == NULL
11143           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11144         {
11145           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11146                      "that has not been declared", c->name, sym->name,
11147                      &c->loc);
11148           return FAILURE;
11149         }
11150
11151       /* C437.  */
11152       if (c->ts.type == BT_CLASS
11153           && !(CLASS_DATA (c)->attr.class_pointer
11154                || CLASS_DATA (c)->attr.allocatable))
11155         {
11156           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11157                      "or pointer", c->name, &c->loc);
11158           return FAILURE;
11159         }
11160
11161       /* Ensure that all the derived type components are put on the
11162          derived type list; even in formal namespaces, where derived type
11163          pointer components might not have been declared.  */
11164       if (c->ts.type == BT_DERIVED
11165             && c->ts.u.derived
11166             && c->ts.u.derived->components
11167             && c->attr.pointer
11168             && sym != c->ts.u.derived)
11169         add_dt_to_dt_list (c->ts.u.derived);
11170
11171       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11172                                            || c->attr.proc_pointer
11173                                            || c->attr.allocatable)) == FAILURE)
11174         return FAILURE;
11175     }
11176
11177   /* Resolve the type-bound procedures.  */
11178   if (resolve_typebound_procedures (sym) == FAILURE)
11179     return FAILURE;
11180
11181   /* Resolve the finalizer procedures.  */
11182   if (gfc_resolve_finalizers (sym) == FAILURE)
11183     return FAILURE;
11184
11185   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11186      all DEFERRED bindings are overridden.  */
11187   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11188       && !sym->attr.is_class
11189       && ensure_not_abstract (sym, super_type) == FAILURE)
11190     return FAILURE;
11191
11192   /* Add derived type to the derived type list.  */
11193   add_dt_to_dt_list (sym);
11194
11195   return SUCCESS;
11196 }
11197
11198
11199 static gfc_try
11200 resolve_fl_namelist (gfc_symbol *sym)
11201 {
11202   gfc_namelist *nl;
11203   gfc_symbol *nlsym;
11204
11205   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11206   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11207     {
11208       for (nl = sym->namelist; nl; nl = nl->next)
11209         {
11210           if (!nl->sym->attr.use_assoc
11211               && !is_sym_host_assoc (nl->sym, sym->ns)
11212               && !gfc_check_access(nl->sym->attr.access,
11213                                 nl->sym->ns->default_access))
11214             {
11215               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11216                          "cannot be member of PUBLIC namelist '%s' at %L",
11217                          nl->sym->name, sym->name, &sym->declared_at);
11218               return FAILURE;
11219             }
11220
11221           /* Types with private components that came here by USE-association.  */
11222           if (nl->sym->ts.type == BT_DERIVED
11223               && derived_inaccessible (nl->sym->ts.u.derived))
11224             {
11225               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11226                          "components and cannot be member of namelist '%s' at %L",
11227                          nl->sym->name, sym->name, &sym->declared_at);
11228               return FAILURE;
11229             }
11230
11231           /* Types with private components that are defined in the same module.  */
11232           if (nl->sym->ts.type == BT_DERIVED
11233               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11234               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11235                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11236                                         nl->sym->ns->default_access))
11237             {
11238               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11239                          "cannot be a member of PUBLIC namelist '%s' at %L",
11240                          nl->sym->name, sym->name, &sym->declared_at);
11241               return FAILURE;
11242             }
11243         }
11244     }
11245
11246   for (nl = sym->namelist; nl; nl = nl->next)
11247     {
11248       /* Reject namelist arrays of assumed shape.  */
11249       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11250           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11251                              "must not have assumed shape in namelist "
11252                              "'%s' at %L", nl->sym->name, sym->name,
11253                              &sym->declared_at) == FAILURE)
11254             return FAILURE;
11255
11256       /* Reject namelist arrays that are not constant shape.  */
11257       if (is_non_constant_shape_array (nl->sym))
11258         {
11259           gfc_error ("NAMELIST array object '%s' must have constant "
11260                      "shape in namelist '%s' at %L", nl->sym->name,
11261                      sym->name, &sym->declared_at);
11262           return FAILURE;
11263         }
11264
11265       /* Namelist objects cannot have allocatable or pointer components.  */
11266       if (nl->sym->ts.type != BT_DERIVED)
11267         continue;
11268
11269       if (nl->sym->ts.u.derived->attr.alloc_comp)
11270         {
11271           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11272                      "have ALLOCATABLE components",
11273                      nl->sym->name, sym->name, &sym->declared_at);
11274           return FAILURE;
11275         }
11276
11277       if (nl->sym->ts.u.derived->attr.pointer_comp)
11278         {
11279           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11280                      "have POINTER components", 
11281                      nl->sym->name, sym->name, &sym->declared_at);
11282           return FAILURE;
11283         }
11284     }
11285
11286
11287   /* 14.1.2 A module or internal procedure represent local entities
11288      of the same type as a namelist member and so are not allowed.  */
11289   for (nl = sym->namelist; nl; nl = nl->next)
11290     {
11291       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11292         continue;
11293
11294       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11295         if ((nl->sym == sym->ns->proc_name)
11296                ||
11297             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11298           continue;
11299
11300       nlsym = NULL;
11301       if (nl->sym && nl->sym->name)
11302         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11303       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11304         {
11305           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11306                      "attribute in '%s' at %L", nlsym->name,
11307                      &sym->declared_at);
11308           return FAILURE;
11309         }
11310     }
11311
11312   return SUCCESS;
11313 }
11314
11315
11316 static gfc_try
11317 resolve_fl_parameter (gfc_symbol *sym)
11318 {
11319   /* A parameter array's shape needs to be constant.  */
11320   if (sym->as != NULL 
11321       && (sym->as->type == AS_DEFERRED
11322           || is_non_constant_shape_array (sym)))
11323     {
11324       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11325                  "or of deferred shape", sym->name, &sym->declared_at);
11326       return FAILURE;
11327     }
11328
11329   /* Make sure a parameter that has been implicitly typed still
11330      matches the implicit type, since PARAMETER statements can precede
11331      IMPLICIT statements.  */
11332   if (sym->attr.implicit_type
11333       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11334                                                              sym->ns)))
11335     {
11336       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11337                  "later IMPLICIT type", sym->name, &sym->declared_at);
11338       return FAILURE;
11339     }
11340
11341   /* Make sure the types of derived parameters are consistent.  This
11342      type checking is deferred until resolution because the type may
11343      refer to a derived type from the host.  */
11344   if (sym->ts.type == BT_DERIVED
11345       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11346     {
11347       gfc_error ("Incompatible derived type in PARAMETER at %L",
11348                  &sym->value->where);
11349       return FAILURE;
11350     }
11351   return SUCCESS;
11352 }
11353
11354
11355 /* Do anything necessary to resolve a symbol.  Right now, we just
11356    assume that an otherwise unknown symbol is a variable.  This sort
11357    of thing commonly happens for symbols in module.  */
11358
11359 static void
11360 resolve_symbol (gfc_symbol *sym)
11361 {
11362   int check_constant, mp_flag;
11363   gfc_symtree *symtree;
11364   gfc_symtree *this_symtree;
11365   gfc_namespace *ns;
11366   gfc_component *c;
11367
11368   /* Avoid double resolution of function result symbols.  */
11369   if ((sym->result || sym->attr.result) && (sym->ns != gfc_current_ns))
11370     return;
11371   
11372   if (sym->attr.flavor == FL_UNKNOWN)
11373     {
11374
11375     /* If we find that a flavorless symbol is an interface in one of the
11376        parent namespaces, find its symtree in this namespace, free the
11377        symbol and set the symtree to point to the interface symbol.  */
11378       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11379         {
11380           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11381           if (symtree && symtree->n.sym->generic)
11382             {
11383               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11384                                                sym->name);
11385               gfc_release_symbol (sym);
11386               symtree->n.sym->refs++;
11387               this_symtree->n.sym = symtree->n.sym;
11388               return;
11389             }
11390         }
11391
11392       /* Otherwise give it a flavor according to such attributes as
11393          it has.  */
11394       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11395         sym->attr.flavor = FL_VARIABLE;
11396       else
11397         {
11398           sym->attr.flavor = FL_PROCEDURE;
11399           if (sym->attr.dimension)
11400             sym->attr.function = 1;
11401         }
11402     }
11403
11404   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11405     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11406
11407   if (sym->attr.procedure && sym->ts.interface
11408       && sym->attr.if_source != IFSRC_DECL)
11409     {
11410       if (sym->ts.interface == sym)
11411         {
11412           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
11413                      "interface", sym->name, &sym->declared_at);
11414           return;
11415         }
11416       if (sym->ts.interface->attr.procedure)
11417         {
11418           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
11419                      " in a later PROCEDURE statement", sym->ts.interface->name,
11420                      sym->name,&sym->declared_at);
11421           return;
11422         }
11423
11424       /* Get the attributes from the interface (now resolved).  */
11425       if (sym->ts.interface->attr.if_source
11426           || sym->ts.interface->attr.intrinsic)
11427         {
11428           gfc_symbol *ifc = sym->ts.interface;
11429           resolve_symbol (ifc);
11430
11431           if (ifc->attr.intrinsic)
11432             resolve_intrinsic (ifc, &ifc->declared_at);
11433
11434           if (ifc->result)
11435             sym->ts = ifc->result->ts;
11436           else   
11437             sym->ts = ifc->ts;
11438           sym->ts.interface = ifc;
11439           sym->attr.function = ifc->attr.function;
11440           sym->attr.subroutine = ifc->attr.subroutine;
11441           gfc_copy_formal_args (sym, ifc);
11442
11443           sym->attr.allocatable = ifc->attr.allocatable;
11444           sym->attr.pointer = ifc->attr.pointer;
11445           sym->attr.pure = ifc->attr.pure;
11446           sym->attr.elemental = ifc->attr.elemental;
11447           sym->attr.dimension = ifc->attr.dimension;
11448           sym->attr.contiguous = ifc->attr.contiguous;
11449           sym->attr.recursive = ifc->attr.recursive;
11450           sym->attr.always_explicit = ifc->attr.always_explicit;
11451           sym->attr.ext_attr |= ifc->attr.ext_attr;
11452           /* Copy array spec.  */
11453           sym->as = gfc_copy_array_spec (ifc->as);
11454           if (sym->as)
11455             {
11456               int i;
11457               for (i = 0; i < sym->as->rank; i++)
11458                 {
11459                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
11460                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
11461                 }
11462             }
11463           /* Copy char length.  */
11464           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11465             {
11466               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11467               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
11468               if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
11469                     && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
11470                 return;
11471             }
11472         }
11473       else if (sym->ts.interface->name[0] != '\0')
11474         {
11475           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
11476                     sym->ts.interface->name, sym->name, &sym->declared_at);
11477           return;
11478         }
11479     }
11480
11481   if (sym->attr.is_protected && !sym->attr.proc_pointer
11482       && (sym->attr.procedure || sym->attr.external))
11483     {
11484       if (sym->attr.external)
11485         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11486                    "at %L", &sym->declared_at);
11487       else
11488         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11489                    "at %L", &sym->declared_at);
11490
11491       return;
11492     }
11493
11494
11495   /* F2008, C530. */
11496   if (sym->attr.contiguous
11497       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
11498                                    && !sym->attr.pointer)))
11499     {
11500       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
11501                   "array pointer or an assumed-shape array", sym->name,
11502                   &sym->declared_at);
11503       return;
11504     }
11505
11506   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11507     return;
11508
11509   /* Symbols that are module procedures with results (functions) have
11510      the types and array specification copied for type checking in
11511      procedures that call them, as well as for saving to a module
11512      file.  These symbols can't stand the scrutiny that their results
11513      can.  */
11514   mp_flag = (sym->result != NULL && sym->result != sym);
11515
11516   /* Make sure that the intrinsic is consistent with its internal 
11517      representation. This needs to be done before assigning a default 
11518      type to avoid spurious warnings.  */
11519   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11520       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11521     return;
11522
11523   /* For associate names, resolve corresponding expression and make sure
11524      they get their type-spec set this way.  */
11525   if (sym->assoc)
11526     {
11527       gcc_assert (sym->attr.flavor == FL_VARIABLE);
11528       if (gfc_resolve_expr (sym->assoc->target) != SUCCESS)
11529         return;
11530
11531       sym->ts = sym->assoc->target->ts;
11532       gcc_assert (sym->ts.type != BT_UNKNOWN);
11533     }
11534
11535   /* Assign default type to symbols that need one and don't have one.  */
11536   if (sym->ts.type == BT_UNKNOWN)
11537     {
11538       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11539         gfc_set_default_type (sym, 1, NULL);
11540
11541       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11542           && !sym->attr.function && !sym->attr.subroutine
11543           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11544         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11545
11546       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11547         {
11548           /* The specific case of an external procedure should emit an error
11549              in the case that there is no implicit type.  */
11550           if (!mp_flag)
11551             gfc_set_default_type (sym, sym->attr.external, NULL);
11552           else
11553             {
11554               /* Result may be in another namespace.  */
11555               resolve_symbol (sym->result);
11556
11557               if (!sym->result->attr.proc_pointer)
11558                 {
11559                   sym->ts = sym->result->ts;
11560                   sym->as = gfc_copy_array_spec (sym->result->as);
11561                   sym->attr.dimension = sym->result->attr.dimension;
11562                   sym->attr.pointer = sym->result->attr.pointer;
11563                   sym->attr.allocatable = sym->result->attr.allocatable;
11564                   sym->attr.contiguous = sym->result->attr.contiguous;
11565                 }
11566             }
11567         }
11568     }
11569
11570   /* Assumed size arrays and assumed shape arrays must be dummy
11571      arguments.  */
11572
11573   if (sym->as != NULL
11574       && ((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11575           || sym->as->type == AS_ASSUMED_SHAPE)
11576       && sym->attr.dummy == 0)
11577     {
11578       if (sym->as->type == AS_ASSUMED_SIZE)
11579         gfc_error ("Assumed size array at %L must be a dummy argument",
11580                    &sym->declared_at);
11581       else
11582         gfc_error ("Assumed shape array at %L must be a dummy argument",
11583                    &sym->declared_at);
11584       return;
11585     }
11586
11587   /* Make sure symbols with known intent or optional are really dummy
11588      variable.  Because of ENTRY statement, this has to be deferred
11589      until resolution time.  */
11590
11591   if (!sym->attr.dummy
11592       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11593     {
11594       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11595       return;
11596     }
11597
11598   if (sym->attr.value && !sym->attr.dummy)
11599     {
11600       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11601                  "it is not a dummy argument", sym->name, &sym->declared_at);
11602       return;
11603     }
11604
11605   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11606     {
11607       gfc_charlen *cl = sym->ts.u.cl;
11608       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11609         {
11610           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11611                      "attribute must have constant length",
11612                      sym->name, &sym->declared_at);
11613           return;
11614         }
11615
11616       if (sym->ts.is_c_interop
11617           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11618         {
11619           gfc_error ("C interoperable character dummy variable '%s' at %L "
11620                      "with VALUE attribute must have length one",
11621                      sym->name, &sym->declared_at);
11622           return;
11623         }
11624     }
11625
11626   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11627      do this for something that was implicitly typed because that is handled
11628      in gfc_set_default_type.  Handle dummy arguments and procedure
11629      definitions separately.  Also, anything that is use associated is not
11630      handled here but instead is handled in the module it is declared in.
11631      Finally, derived type definitions are allowed to be BIND(C) since that
11632      only implies that they're interoperable, and they are checked fully for
11633      interoperability when a variable is declared of that type.  */
11634   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11635       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11636       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11637     {
11638       gfc_try t = SUCCESS;
11639       
11640       /* First, make sure the variable is declared at the
11641          module-level scope (J3/04-007, Section 15.3).  */
11642       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11643           sym->attr.in_common == 0)
11644         {
11645           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11646                      "is neither a COMMON block nor declared at the "
11647                      "module level scope", sym->name, &(sym->declared_at));
11648           t = FAILURE;
11649         }
11650       else if (sym->common_head != NULL)
11651         {
11652           t = verify_com_block_vars_c_interop (sym->common_head);
11653         }
11654       else
11655         {
11656           /* If type() declaration, we need to verify that the components
11657              of the given type are all C interoperable, etc.  */
11658           if (sym->ts.type == BT_DERIVED &&
11659               sym->ts.u.derived->attr.is_c_interop != 1)
11660             {
11661               /* Make sure the user marked the derived type as BIND(C).  If
11662                  not, call the verify routine.  This could print an error
11663                  for the derived type more than once if multiple variables
11664                  of that type are declared.  */
11665               if (sym->ts.u.derived->attr.is_bind_c != 1)
11666                 verify_bind_c_derived_type (sym->ts.u.derived);
11667               t = FAILURE;
11668             }
11669           
11670           /* Verify the variable itself as C interoperable if it
11671              is BIND(C).  It is not possible for this to succeed if
11672              the verify_bind_c_derived_type failed, so don't have to handle
11673              any error returned by verify_bind_c_derived_type.  */
11674           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11675                                  sym->common_block);
11676         }
11677
11678       if (t == FAILURE)
11679         {
11680           /* clear the is_bind_c flag to prevent reporting errors more than
11681              once if something failed.  */
11682           sym->attr.is_bind_c = 0;
11683           return;
11684         }
11685     }
11686
11687   /* If a derived type symbol has reached this point, without its
11688      type being declared, we have an error.  Notice that most
11689      conditions that produce undefined derived types have already
11690      been dealt with.  However, the likes of:
11691      implicit type(t) (t) ..... call foo (t) will get us here if
11692      the type is not declared in the scope of the implicit
11693      statement. Change the type to BT_UNKNOWN, both because it is so
11694      and to prevent an ICE.  */
11695   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11696       && !sym->ts.u.derived->attr.zero_comp)
11697     {
11698       gfc_error ("The derived type '%s' at %L is of type '%s', "
11699                  "which has not been defined", sym->name,
11700                   &sym->declared_at, sym->ts.u.derived->name);
11701       sym->ts.type = BT_UNKNOWN;
11702       return;
11703     }
11704
11705   /* Make sure that the derived type has been resolved and that the
11706      derived type is visible in the symbol's namespace, if it is a
11707      module function and is not PRIVATE.  */
11708   if (sym->ts.type == BT_DERIVED
11709         && sym->ts.u.derived->attr.use_assoc
11710         && sym->ns->proc_name
11711         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11712     {
11713       gfc_symbol *ds;
11714
11715       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11716         return;
11717
11718       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11719       if (!ds && sym->attr.function
11720             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11721         {
11722           symtree = gfc_new_symtree (&sym->ns->sym_root,
11723                                      sym->ts.u.derived->name);
11724           symtree->n.sym = sym->ts.u.derived;
11725           sym->ts.u.derived->refs++;
11726         }
11727     }
11728
11729   /* Unless the derived-type declaration is use associated, Fortran 95
11730      does not allow public entries of private derived types.
11731      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11732      161 in 95-006r3.  */
11733   if (sym->ts.type == BT_DERIVED
11734       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11735       && !sym->ts.u.derived->attr.use_assoc
11736       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11737       && !gfc_check_access (sym->ts.u.derived->attr.access,
11738                             sym->ts.u.derived->ns->default_access)
11739       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11740                          "of PRIVATE derived type '%s'",
11741                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11742                          : "variable", sym->name, &sym->declared_at,
11743                          sym->ts.u.derived->name) == FAILURE)
11744     return;
11745
11746   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11747      default initialization is defined (5.1.2.4.4).  */
11748   if (sym->ts.type == BT_DERIVED
11749       && sym->attr.dummy
11750       && sym->attr.intent == INTENT_OUT
11751       && sym->as
11752       && sym->as->type == AS_ASSUMED_SIZE)
11753     {
11754       for (c = sym->ts.u.derived->components; c; c = c->next)
11755         {
11756           if (c->initializer)
11757             {
11758               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11759                          "ASSUMED SIZE and so cannot have a default initializer",
11760                          sym->name, &sym->declared_at);
11761               return;
11762             }
11763         }
11764     }
11765
11766   /* F2008, C526.  */
11767   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11768        || sym->attr.codimension)
11769       && sym->attr.result)
11770     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
11771                "a coarray component", sym->name, &sym->declared_at);
11772
11773   /* F2008, C524.  */
11774   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
11775       && sym->ts.u.derived->ts.is_iso_c)
11776     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11777                "shall not be a coarray", sym->name, &sym->declared_at);
11778
11779   /* F2008, C525.  */
11780   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
11781       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
11782           || sym->attr.allocatable))
11783     gfc_error ("Variable '%s' at %L with coarray component "
11784                "shall be a nonpointer, nonallocatable scalar",
11785                sym->name, &sym->declared_at);
11786
11787   /* F2008, C526.  The function-result case was handled above.  */
11788   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11789        || sym->attr.codimension)
11790       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
11791            || sym->ns->proc_name->attr.flavor == FL_MODULE
11792            || sym->ns->proc_name->attr.is_main_program
11793            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
11794     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
11795                "component and is not ALLOCATABLE, SAVE nor a "
11796                "dummy argument", sym->name, &sym->declared_at);
11797   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
11798   else if (sym->attr.codimension && !sym->attr.allocatable
11799       && sym->as && sym->as->cotype == AS_DEFERRED)
11800     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
11801                 "deferred shape", sym->name, &sym->declared_at);
11802   else if (sym->attr.codimension && sym->attr.allocatable
11803       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
11804     gfc_error ("Allocatable coarray variable '%s' at %L must have "
11805                "deferred shape", sym->name, &sym->declared_at);
11806
11807
11808   /* F2008, C541.  */
11809   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11810        || (sym->attr.codimension && sym->attr.allocatable))
11811       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
11812     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
11813                "allocatable coarray or have coarray components",
11814                sym->name, &sym->declared_at);
11815
11816   if (sym->attr.codimension && sym->attr.dummy
11817       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
11818     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
11819                "procedure '%s'", sym->name, &sym->declared_at,
11820                sym->ns->proc_name->name);
11821
11822   switch (sym->attr.flavor)
11823     {
11824     case FL_VARIABLE:
11825       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11826         return;
11827       break;
11828
11829     case FL_PROCEDURE:
11830       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11831         return;
11832       break;
11833
11834     case FL_NAMELIST:
11835       if (resolve_fl_namelist (sym) == FAILURE)
11836         return;
11837       break;
11838
11839     case FL_PARAMETER:
11840       if (resolve_fl_parameter (sym) == FAILURE)
11841         return;
11842       break;
11843
11844     default:
11845       break;
11846     }
11847
11848   /* Resolve array specifier. Check as well some constraints
11849      on COMMON blocks.  */
11850
11851   check_constant = sym->attr.in_common && !sym->attr.pointer;
11852
11853   /* Set the formal_arg_flag so that check_conflict will not throw
11854      an error for host associated variables in the specification
11855      expression for an array_valued function.  */
11856   if (sym->attr.function && sym->as)
11857     formal_arg_flag = 1;
11858
11859   gfc_resolve_array_spec (sym->as, check_constant);
11860
11861   formal_arg_flag = 0;
11862
11863   /* Resolve formal namespaces.  */
11864   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11865       && !sym->attr.contained && !sym->attr.intrinsic)
11866     gfc_resolve (sym->formal_ns);
11867
11868   /* Make sure the formal namespace is present.  */
11869   if (sym->formal && !sym->formal_ns)
11870     {
11871       gfc_formal_arglist *formal = sym->formal;
11872       while (formal && !formal->sym)
11873         formal = formal->next;
11874
11875       if (formal)
11876         {
11877           sym->formal_ns = formal->sym->ns;
11878           sym->formal_ns->refs++;
11879         }
11880     }
11881
11882   /* Check threadprivate restrictions.  */
11883   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11884       && (!sym->attr.in_common
11885           && sym->module == NULL
11886           && (sym->ns->proc_name == NULL
11887               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11888     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11889
11890   /* If we have come this far we can apply default-initializers, as
11891      described in 14.7.5, to those variables that have not already
11892      been assigned one.  */
11893   if (sym->ts.type == BT_DERIVED
11894       && sym->attr.referenced
11895       && sym->ns == gfc_current_ns
11896       && !sym->value
11897       && !sym->attr.allocatable
11898       && !sym->attr.alloc_comp)
11899     {
11900       symbol_attribute *a = &sym->attr;
11901
11902       if ((!a->save && !a->dummy && !a->pointer
11903            && !a->in_common && !a->use_assoc
11904            && !(a->function && sym != sym->result))
11905           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11906         apply_default_init (sym);
11907     }
11908
11909   /* If this symbol has a type-spec, check it.  */
11910   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11911       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11912     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11913           == FAILURE)
11914       return;
11915 }
11916
11917
11918 /************* Resolve DATA statements *************/
11919
11920 static struct
11921 {
11922   gfc_data_value *vnode;
11923   mpz_t left;
11924 }
11925 values;
11926
11927
11928 /* Advance the values structure to point to the next value in the data list.  */
11929
11930 static gfc_try
11931 next_data_value (void)
11932 {
11933   while (mpz_cmp_ui (values.left, 0) == 0)
11934     {
11935
11936       if (values.vnode->next == NULL)
11937         return FAILURE;
11938
11939       values.vnode = values.vnode->next;
11940       mpz_set (values.left, values.vnode->repeat);
11941     }
11942
11943   return SUCCESS;
11944 }
11945
11946
11947 static gfc_try
11948 check_data_variable (gfc_data_variable *var, locus *where)
11949 {
11950   gfc_expr *e;
11951   mpz_t size;
11952   mpz_t offset;
11953   gfc_try t;
11954   ar_type mark = AR_UNKNOWN;
11955   int i;
11956   mpz_t section_index[GFC_MAX_DIMENSIONS];
11957   gfc_ref *ref;
11958   gfc_array_ref *ar;
11959   gfc_symbol *sym;
11960   int has_pointer;
11961
11962   if (gfc_resolve_expr (var->expr) == FAILURE)
11963     return FAILURE;
11964
11965   ar = NULL;
11966   mpz_init_set_si (offset, 0);
11967   e = var->expr;
11968
11969   if (e->expr_type != EXPR_VARIABLE)
11970     gfc_internal_error ("check_data_variable(): Bad expression");
11971
11972   sym = e->symtree->n.sym;
11973
11974   if (sym->ns->is_block_data && !sym->attr.in_common)
11975     {
11976       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11977                  sym->name, &sym->declared_at);
11978     }
11979
11980   if (e->ref == NULL && sym->as)
11981     {
11982       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11983                  " declaration", sym->name, where);
11984       return FAILURE;
11985     }
11986
11987   has_pointer = sym->attr.pointer;
11988
11989   for (ref = e->ref; ref; ref = ref->next)
11990     {
11991       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11992         has_pointer = 1;
11993
11994       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
11995         {
11996           gfc_error ("DATA element '%s' at %L cannot have a coindex",
11997                      sym->name, where);
11998           return FAILURE;
11999         }
12000
12001       if (has_pointer
12002             && ref->type == REF_ARRAY
12003             && ref->u.ar.type != AR_FULL)
12004           {
12005             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12006                         "be a full array", sym->name, where);
12007             return FAILURE;
12008           }
12009     }
12010
12011   if (e->rank == 0 || has_pointer)
12012     {
12013       mpz_init_set_ui (size, 1);
12014       ref = NULL;
12015     }
12016   else
12017     {
12018       ref = e->ref;
12019
12020       /* Find the array section reference.  */
12021       for (ref = e->ref; ref; ref = ref->next)
12022         {
12023           if (ref->type != REF_ARRAY)
12024             continue;
12025           if (ref->u.ar.type == AR_ELEMENT)
12026             continue;
12027           break;
12028         }
12029       gcc_assert (ref);
12030
12031       /* Set marks according to the reference pattern.  */
12032       switch (ref->u.ar.type)
12033         {
12034         case AR_FULL:
12035           mark = AR_FULL;
12036           break;
12037
12038         case AR_SECTION:
12039           ar = &ref->u.ar;
12040           /* Get the start position of array section.  */
12041           gfc_get_section_index (ar, section_index, &offset);
12042           mark = AR_SECTION;
12043           break;
12044
12045         default:
12046           gcc_unreachable ();
12047         }
12048
12049       if (gfc_array_size (e, &size) == FAILURE)
12050         {
12051           gfc_error ("Nonconstant array section at %L in DATA statement",
12052                      &e->where);
12053           mpz_clear (offset);
12054           return FAILURE;
12055         }
12056     }
12057
12058   t = SUCCESS;
12059
12060   while (mpz_cmp_ui (size, 0) > 0)
12061     {
12062       if (next_data_value () == FAILURE)
12063         {
12064           gfc_error ("DATA statement at %L has more variables than values",
12065                      where);
12066           t = FAILURE;
12067           break;
12068         }
12069
12070       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12071       if (t == FAILURE)
12072         break;
12073
12074       /* If we have more than one element left in the repeat count,
12075          and we have more than one element left in the target variable,
12076          then create a range assignment.  */
12077       /* FIXME: Only done for full arrays for now, since array sections
12078          seem tricky.  */
12079       if (mark == AR_FULL && ref && ref->next == NULL
12080           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12081         {
12082           mpz_t range;
12083
12084           if (mpz_cmp (size, values.left) >= 0)
12085             {
12086               mpz_init_set (range, values.left);
12087               mpz_sub (size, size, values.left);
12088               mpz_set_ui (values.left, 0);
12089             }
12090           else
12091             {
12092               mpz_init_set (range, size);
12093               mpz_sub (values.left, values.left, size);
12094               mpz_set_ui (size, 0);
12095             }
12096
12097           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12098                                            offset, range);
12099
12100           mpz_add (offset, offset, range);
12101           mpz_clear (range);
12102
12103           if (t == FAILURE)
12104             break;
12105         }
12106
12107       /* Assign initial value to symbol.  */
12108       else
12109         {
12110           mpz_sub_ui (values.left, values.left, 1);
12111           mpz_sub_ui (size, size, 1);
12112
12113           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12114           if (t == FAILURE)
12115             break;
12116
12117           if (mark == AR_FULL)
12118             mpz_add_ui (offset, offset, 1);
12119
12120           /* Modify the array section indexes and recalculate the offset
12121              for next element.  */
12122           else if (mark == AR_SECTION)
12123             gfc_advance_section (section_index, ar, &offset);
12124         }
12125     }
12126
12127   if (mark == AR_SECTION)
12128     {
12129       for (i = 0; i < ar->dimen; i++)
12130         mpz_clear (section_index[i]);
12131     }
12132
12133   mpz_clear (size);
12134   mpz_clear (offset);
12135
12136   return t;
12137 }
12138
12139
12140 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12141
12142 /* Iterate over a list of elements in a DATA statement.  */
12143
12144 static gfc_try
12145 traverse_data_list (gfc_data_variable *var, locus *where)
12146 {
12147   mpz_t trip;
12148   iterator_stack frame;
12149   gfc_expr *e, *start, *end, *step;
12150   gfc_try retval = SUCCESS;
12151
12152   mpz_init (frame.value);
12153   mpz_init (trip);
12154
12155   start = gfc_copy_expr (var->iter.start);
12156   end = gfc_copy_expr (var->iter.end);
12157   step = gfc_copy_expr (var->iter.step);
12158
12159   if (gfc_simplify_expr (start, 1) == FAILURE
12160       || start->expr_type != EXPR_CONSTANT)
12161     {
12162       gfc_error ("start of implied-do loop at %L could not be "
12163                  "simplified to a constant value", &start->where);
12164       retval = FAILURE;
12165       goto cleanup;
12166     }
12167   if (gfc_simplify_expr (end, 1) == FAILURE
12168       || end->expr_type != EXPR_CONSTANT)
12169     {
12170       gfc_error ("end of implied-do loop at %L could not be "
12171                  "simplified to a constant value", &start->where);
12172       retval = FAILURE;
12173       goto cleanup;
12174     }
12175   if (gfc_simplify_expr (step, 1) == FAILURE
12176       || step->expr_type != EXPR_CONSTANT)
12177     {
12178       gfc_error ("step of implied-do loop at %L could not be "
12179                  "simplified to a constant value", &start->where);
12180       retval = FAILURE;
12181       goto cleanup;
12182     }
12183
12184   mpz_set (trip, end->value.integer);
12185   mpz_sub (trip, trip, start->value.integer);
12186   mpz_add (trip, trip, step->value.integer);
12187
12188   mpz_div (trip, trip, step->value.integer);
12189
12190   mpz_set (frame.value, start->value.integer);
12191
12192   frame.prev = iter_stack;
12193   frame.variable = var->iter.var->symtree;
12194   iter_stack = &frame;
12195
12196   while (mpz_cmp_ui (trip, 0) > 0)
12197     {
12198       if (traverse_data_var (var->list, where) == FAILURE)
12199         {
12200           retval = FAILURE;
12201           goto cleanup;
12202         }
12203
12204       e = gfc_copy_expr (var->expr);
12205       if (gfc_simplify_expr (e, 1) == FAILURE)
12206         {
12207           gfc_free_expr (e);
12208           retval = FAILURE;
12209           goto cleanup;
12210         }
12211
12212       mpz_add (frame.value, frame.value, step->value.integer);
12213
12214       mpz_sub_ui (trip, trip, 1);
12215     }
12216
12217 cleanup:
12218   mpz_clear (frame.value);
12219   mpz_clear (trip);
12220
12221   gfc_free_expr (start);
12222   gfc_free_expr (end);
12223   gfc_free_expr (step);
12224
12225   iter_stack = frame.prev;
12226   return retval;
12227 }
12228
12229
12230 /* Type resolve variables in the variable list of a DATA statement.  */
12231
12232 static gfc_try
12233 traverse_data_var (gfc_data_variable *var, locus *where)
12234 {
12235   gfc_try t;
12236
12237   for (; var; var = var->next)
12238     {
12239       if (var->expr == NULL)
12240         t = traverse_data_list (var, where);
12241       else
12242         t = check_data_variable (var, where);
12243
12244       if (t == FAILURE)
12245         return FAILURE;
12246     }
12247
12248   return SUCCESS;
12249 }
12250
12251
12252 /* Resolve the expressions and iterators associated with a data statement.
12253    This is separate from the assignment checking because data lists should
12254    only be resolved once.  */
12255
12256 static gfc_try
12257 resolve_data_variables (gfc_data_variable *d)
12258 {
12259   for (; d; d = d->next)
12260     {
12261       if (d->list == NULL)
12262         {
12263           if (gfc_resolve_expr (d->expr) == FAILURE)
12264             return FAILURE;
12265         }
12266       else
12267         {
12268           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12269             return FAILURE;
12270
12271           if (resolve_data_variables (d->list) == FAILURE)
12272             return FAILURE;
12273         }
12274     }
12275
12276   return SUCCESS;
12277 }
12278
12279
12280 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12281    the value list into static variables, and then recursively traversing the
12282    variables list, expanding iterators and such.  */
12283
12284 static void
12285 resolve_data (gfc_data *d)
12286 {
12287
12288   if (resolve_data_variables (d->var) == FAILURE)
12289     return;
12290
12291   values.vnode = d->value;
12292   if (d->value == NULL)
12293     mpz_set_ui (values.left, 0);
12294   else
12295     mpz_set (values.left, d->value->repeat);
12296
12297   if (traverse_data_var (d->var, &d->where) == FAILURE)
12298     return;
12299
12300   /* At this point, we better not have any values left.  */
12301
12302   if (next_data_value () == SUCCESS)
12303     gfc_error ("DATA statement at %L has more values than variables",
12304                &d->where);
12305 }
12306
12307
12308 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12309    accessed by host or use association, is a dummy argument to a pure function,
12310    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12311    is storage associated with any such variable, shall not be used in the
12312    following contexts: (clients of this function).  */
12313
12314 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12315    procedure.  Returns zero if assignment is OK, nonzero if there is a
12316    problem.  */
12317 int
12318 gfc_impure_variable (gfc_symbol *sym)
12319 {
12320   gfc_symbol *proc;
12321   gfc_namespace *ns;
12322
12323   if (sym->attr.use_assoc || sym->attr.in_common)
12324     return 1;
12325
12326   /* Check if the symbol's ns is inside the pure procedure.  */
12327   for (ns = gfc_current_ns; ns; ns = ns->parent)
12328     {
12329       if (ns == sym->ns)
12330         break;
12331       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12332         return 1;
12333     }
12334
12335   proc = sym->ns->proc_name;
12336   if (sym->attr.dummy && gfc_pure (proc)
12337         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12338                 ||
12339              proc->attr.function))
12340     return 1;
12341
12342   /* TODO: Sort out what can be storage associated, if anything, and include
12343      it here.  In principle equivalences should be scanned but it does not
12344      seem to be possible to storage associate an impure variable this way.  */
12345   return 0;
12346 }
12347
12348
12349 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12350    current namespace is inside a pure procedure.  */
12351
12352 int
12353 gfc_pure (gfc_symbol *sym)
12354 {
12355   symbol_attribute attr;
12356   gfc_namespace *ns;
12357
12358   if (sym == NULL)
12359     {
12360       /* Check if the current namespace or one of its parents
12361         belongs to a pure procedure.  */
12362       for (ns = gfc_current_ns; ns; ns = ns->parent)
12363         {
12364           sym = ns->proc_name;
12365           if (sym == NULL)
12366             return 0;
12367           attr = sym->attr;
12368           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
12369             return 1;
12370         }
12371       return 0;
12372     }
12373
12374   attr = sym->attr;
12375
12376   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
12377 }
12378
12379
12380 /* Test whether the current procedure is elemental or not.  */
12381
12382 int
12383 gfc_elemental (gfc_symbol *sym)
12384 {
12385   symbol_attribute attr;
12386
12387   if (sym == NULL)
12388     sym = gfc_current_ns->proc_name;
12389   if (sym == NULL)
12390     return 0;
12391   attr = sym->attr;
12392
12393   return attr.flavor == FL_PROCEDURE && attr.elemental;
12394 }
12395
12396
12397 /* Warn about unused labels.  */
12398
12399 static void
12400 warn_unused_fortran_label (gfc_st_label *label)
12401 {
12402   if (label == NULL)
12403     return;
12404
12405   warn_unused_fortran_label (label->left);
12406
12407   if (label->defined == ST_LABEL_UNKNOWN)
12408     return;
12409
12410   switch (label->referenced)
12411     {
12412     case ST_LABEL_UNKNOWN:
12413       gfc_warning ("Label %d at %L defined but not used", label->value,
12414                    &label->where);
12415       break;
12416
12417     case ST_LABEL_BAD_TARGET:
12418       gfc_warning ("Label %d at %L defined but cannot be used",
12419                    label->value, &label->where);
12420       break;
12421
12422     default:
12423       break;
12424     }
12425
12426   warn_unused_fortran_label (label->right);
12427 }
12428
12429
12430 /* Returns the sequence type of a symbol or sequence.  */
12431
12432 static seq_type
12433 sequence_type (gfc_typespec ts)
12434 {
12435   seq_type result;
12436   gfc_component *c;
12437
12438   switch (ts.type)
12439   {
12440     case BT_DERIVED:
12441
12442       if (ts.u.derived->components == NULL)
12443         return SEQ_NONDEFAULT;
12444
12445       result = sequence_type (ts.u.derived->components->ts);
12446       for (c = ts.u.derived->components->next; c; c = c->next)
12447         if (sequence_type (c->ts) != result)
12448           return SEQ_MIXED;
12449
12450       return result;
12451
12452     case BT_CHARACTER:
12453       if (ts.kind != gfc_default_character_kind)
12454           return SEQ_NONDEFAULT;
12455
12456       return SEQ_CHARACTER;
12457
12458     case BT_INTEGER:
12459       if (ts.kind != gfc_default_integer_kind)
12460           return SEQ_NONDEFAULT;
12461
12462       return SEQ_NUMERIC;
12463
12464     case BT_REAL:
12465       if (!(ts.kind == gfc_default_real_kind
12466             || ts.kind == gfc_default_double_kind))
12467           return SEQ_NONDEFAULT;
12468
12469       return SEQ_NUMERIC;
12470
12471     case BT_COMPLEX:
12472       if (ts.kind != gfc_default_complex_kind)
12473           return SEQ_NONDEFAULT;
12474
12475       return SEQ_NUMERIC;
12476
12477     case BT_LOGICAL:
12478       if (ts.kind != gfc_default_logical_kind)
12479           return SEQ_NONDEFAULT;
12480
12481       return SEQ_NUMERIC;
12482
12483     default:
12484       return SEQ_NONDEFAULT;
12485   }
12486 }
12487
12488
12489 /* Resolve derived type EQUIVALENCE object.  */
12490
12491 static gfc_try
12492 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12493 {
12494   gfc_component *c = derived->components;
12495
12496   if (!derived)
12497     return SUCCESS;
12498
12499   /* Shall not be an object of nonsequence derived type.  */
12500   if (!derived->attr.sequence)
12501     {
12502       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12503                  "attribute to be an EQUIVALENCE object", sym->name,
12504                  &e->where);
12505       return FAILURE;
12506     }
12507
12508   /* Shall not have allocatable components.  */
12509   if (derived->attr.alloc_comp)
12510     {
12511       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12512                  "components to be an EQUIVALENCE object",sym->name,
12513                  &e->where);
12514       return FAILURE;
12515     }
12516
12517   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
12518     {
12519       gfc_error ("Derived type variable '%s' at %L with default "
12520                  "initialization cannot be in EQUIVALENCE with a variable "
12521                  "in COMMON", sym->name, &e->where);
12522       return FAILURE;
12523     }
12524
12525   for (; c ; c = c->next)
12526     {
12527       if (c->ts.type == BT_DERIVED
12528           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12529         return FAILURE;
12530
12531       /* Shall not be an object of sequence derived type containing a pointer
12532          in the structure.  */
12533       if (c->attr.pointer)
12534         {
12535           gfc_error ("Derived type variable '%s' at %L with pointer "
12536                      "component(s) cannot be an EQUIVALENCE object",
12537                      sym->name, &e->where);
12538           return FAILURE;
12539         }
12540     }
12541   return SUCCESS;
12542 }
12543
12544
12545 /* Resolve equivalence object. 
12546    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12547    an allocatable array, an object of nonsequence derived type, an object of
12548    sequence derived type containing a pointer at any level of component
12549    selection, an automatic object, a function name, an entry name, a result
12550    name, a named constant, a structure component, or a subobject of any of
12551    the preceding objects.  A substring shall not have length zero.  A
12552    derived type shall not have components with default initialization nor
12553    shall two objects of an equivalence group be initialized.
12554    Either all or none of the objects shall have an protected attribute.
12555    The simple constraints are done in symbol.c(check_conflict) and the rest
12556    are implemented here.  */
12557
12558 static void
12559 resolve_equivalence (gfc_equiv *eq)
12560 {
12561   gfc_symbol *sym;
12562   gfc_symbol *first_sym;
12563   gfc_expr *e;
12564   gfc_ref *r;
12565   locus *last_where = NULL;
12566   seq_type eq_type, last_eq_type;
12567   gfc_typespec *last_ts;
12568   int object, cnt_protected;
12569   const char *msg;
12570
12571   last_ts = &eq->expr->symtree->n.sym->ts;
12572
12573   first_sym = eq->expr->symtree->n.sym;
12574
12575   cnt_protected = 0;
12576
12577   for (object = 1; eq; eq = eq->eq, object++)
12578     {
12579       e = eq->expr;
12580
12581       e->ts = e->symtree->n.sym->ts;
12582       /* match_varspec might not know yet if it is seeing
12583          array reference or substring reference, as it doesn't
12584          know the types.  */
12585       if (e->ref && e->ref->type == REF_ARRAY)
12586         {
12587           gfc_ref *ref = e->ref;
12588           sym = e->symtree->n.sym;
12589
12590           if (sym->attr.dimension)
12591             {
12592               ref->u.ar.as = sym->as;
12593               ref = ref->next;
12594             }
12595
12596           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12597           if (e->ts.type == BT_CHARACTER
12598               && ref
12599               && ref->type == REF_ARRAY
12600               && ref->u.ar.dimen == 1
12601               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12602               && ref->u.ar.stride[0] == NULL)
12603             {
12604               gfc_expr *start = ref->u.ar.start[0];
12605               gfc_expr *end = ref->u.ar.end[0];
12606               void *mem = NULL;
12607
12608               /* Optimize away the (:) reference.  */
12609               if (start == NULL && end == NULL)
12610                 {
12611                   if (e->ref == ref)
12612                     e->ref = ref->next;
12613                   else
12614                     e->ref->next = ref->next;
12615                   mem = ref;
12616                 }
12617               else
12618                 {
12619                   ref->type = REF_SUBSTRING;
12620                   if (start == NULL)
12621                     start = gfc_get_int_expr (gfc_default_integer_kind,
12622                                               NULL, 1);
12623                   ref->u.ss.start = start;
12624                   if (end == NULL && e->ts.u.cl)
12625                     end = gfc_copy_expr (e->ts.u.cl->length);
12626                   ref->u.ss.end = end;
12627                   ref->u.ss.length = e->ts.u.cl;
12628                   e->ts.u.cl = NULL;
12629                 }
12630               ref = ref->next;
12631               gfc_free (mem);
12632             }
12633
12634           /* Any further ref is an error.  */
12635           if (ref)
12636             {
12637               gcc_assert (ref->type == REF_ARRAY);
12638               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12639                          &ref->u.ar.where);
12640               continue;
12641             }
12642         }
12643
12644       if (gfc_resolve_expr (e) == FAILURE)
12645         continue;
12646
12647       sym = e->symtree->n.sym;
12648
12649       if (sym->attr.is_protected)
12650         cnt_protected++;
12651       if (cnt_protected > 0 && cnt_protected != object)
12652         {
12653               gfc_error ("Either all or none of the objects in the "
12654                          "EQUIVALENCE set at %L shall have the "
12655                          "PROTECTED attribute",
12656                          &e->where);
12657               break;
12658         }
12659
12660       /* Shall not equivalence common block variables in a PURE procedure.  */
12661       if (sym->ns->proc_name
12662           && sym->ns->proc_name->attr.pure
12663           && sym->attr.in_common)
12664         {
12665           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12666                      "object in the pure procedure '%s'",
12667                      sym->name, &e->where, sym->ns->proc_name->name);
12668           break;
12669         }
12670
12671       /* Shall not be a named constant.  */
12672       if (e->expr_type == EXPR_CONSTANT)
12673         {
12674           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12675                      "object", sym->name, &e->where);
12676           continue;
12677         }
12678
12679       if (e->ts.type == BT_DERIVED
12680           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12681         continue;
12682
12683       /* Check that the types correspond correctly:
12684          Note 5.28:
12685          A numeric sequence structure may be equivalenced to another sequence
12686          structure, an object of default integer type, default real type, double
12687          precision real type, default logical type such that components of the
12688          structure ultimately only become associated to objects of the same
12689          kind. A character sequence structure may be equivalenced to an object
12690          of default character kind or another character sequence structure.
12691          Other objects may be equivalenced only to objects of the same type and
12692          kind parameters.  */
12693
12694       /* Identical types are unconditionally OK.  */
12695       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12696         goto identical_types;
12697
12698       last_eq_type = sequence_type (*last_ts);
12699       eq_type = sequence_type (sym->ts);
12700
12701       /* Since the pair of objects is not of the same type, mixed or
12702          non-default sequences can be rejected.  */
12703
12704       msg = "Sequence %s with mixed components in EQUIVALENCE "
12705             "statement at %L with different type objects";
12706       if ((object ==2
12707            && last_eq_type == SEQ_MIXED
12708            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12709               == FAILURE)
12710           || (eq_type == SEQ_MIXED
12711               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12712                                  &e->where) == FAILURE))
12713         continue;
12714
12715       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12716             "statement at %L with objects of different type";
12717       if ((object ==2
12718            && last_eq_type == SEQ_NONDEFAULT
12719            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12720                               last_where) == FAILURE)
12721           || (eq_type == SEQ_NONDEFAULT
12722               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12723                                  &e->where) == FAILURE))
12724         continue;
12725
12726       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12727            "EQUIVALENCE statement at %L";
12728       if (last_eq_type == SEQ_CHARACTER
12729           && eq_type != SEQ_CHARACTER
12730           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12731                              &e->where) == FAILURE)
12732                 continue;
12733
12734       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12735            "EQUIVALENCE statement at %L";
12736       if (last_eq_type == SEQ_NUMERIC
12737           && eq_type != SEQ_NUMERIC
12738           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12739                              &e->where) == FAILURE)
12740                 continue;
12741
12742   identical_types:
12743       last_ts =&sym->ts;
12744       last_where = &e->where;
12745
12746       if (!e->ref)
12747         continue;
12748
12749       /* Shall not be an automatic array.  */
12750       if (e->ref->type == REF_ARRAY
12751           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12752         {
12753           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12754                      "an EQUIVALENCE object", sym->name, &e->where);
12755           continue;
12756         }
12757
12758       r = e->ref;
12759       while (r)
12760         {
12761           /* Shall not be a structure component.  */
12762           if (r->type == REF_COMPONENT)
12763             {
12764               gfc_error ("Structure component '%s' at %L cannot be an "
12765                          "EQUIVALENCE object",
12766                          r->u.c.component->name, &e->where);
12767               break;
12768             }
12769
12770           /* A substring shall not have length zero.  */
12771           if (r->type == REF_SUBSTRING)
12772             {
12773               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12774                 {
12775                   gfc_error ("Substring at %L has length zero",
12776                              &r->u.ss.start->where);
12777                   break;
12778                 }
12779             }
12780           r = r->next;
12781         }
12782     }
12783 }
12784
12785
12786 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12787
12788 static void
12789 resolve_fntype (gfc_namespace *ns)
12790 {
12791   gfc_entry_list *el;
12792   gfc_symbol *sym;
12793
12794   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12795     return;
12796
12797   /* If there are any entries, ns->proc_name is the entry master
12798      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12799   if (ns->entries)
12800     sym = ns->entries->sym;
12801   else
12802     sym = ns->proc_name;
12803   if (sym->result == sym
12804       && sym->ts.type == BT_UNKNOWN
12805       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12806       && !sym->attr.untyped)
12807     {
12808       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12809                  sym->name, &sym->declared_at);
12810       sym->attr.untyped = 1;
12811     }
12812
12813   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12814       && !sym->attr.contained
12815       && !gfc_check_access (sym->ts.u.derived->attr.access,
12816                             sym->ts.u.derived->ns->default_access)
12817       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12818     {
12819       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12820                       "%L of PRIVATE type '%s'", sym->name,
12821                       &sym->declared_at, sym->ts.u.derived->name);
12822     }
12823
12824     if (ns->entries)
12825     for (el = ns->entries->next; el; el = el->next)
12826       {
12827         if (el->sym->result == el->sym
12828             && el->sym->ts.type == BT_UNKNOWN
12829             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12830             && !el->sym->attr.untyped)
12831           {
12832             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12833                        el->sym->name, &el->sym->declared_at);
12834             el->sym->attr.untyped = 1;
12835           }
12836       }
12837 }
12838
12839
12840 /* 12.3.2.1.1 Defined operators.  */
12841
12842 static gfc_try
12843 check_uop_procedure (gfc_symbol *sym, locus where)
12844 {
12845   gfc_formal_arglist *formal;
12846
12847   if (!sym->attr.function)
12848     {
12849       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12850                  sym->name, &where);
12851       return FAILURE;
12852     }
12853
12854   if (sym->ts.type == BT_CHARACTER
12855       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12856       && !(sym->result && sym->result->ts.u.cl
12857            && sym->result->ts.u.cl->length))
12858     {
12859       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12860                  "character length", sym->name, &where);
12861       return FAILURE;
12862     }
12863
12864   formal = sym->formal;
12865   if (!formal || !formal->sym)
12866     {
12867       gfc_error ("User operator procedure '%s' at %L must have at least "
12868                  "one argument", sym->name, &where);
12869       return FAILURE;
12870     }
12871
12872   if (formal->sym->attr.intent != INTENT_IN)
12873     {
12874       gfc_error ("First argument of operator interface at %L must be "
12875                  "INTENT(IN)", &where);
12876       return FAILURE;
12877     }
12878
12879   if (formal->sym->attr.optional)
12880     {
12881       gfc_error ("First argument of operator interface at %L cannot be "
12882                  "optional", &where);
12883       return FAILURE;
12884     }
12885
12886   formal = formal->next;
12887   if (!formal || !formal->sym)
12888     return SUCCESS;
12889
12890   if (formal->sym->attr.intent != INTENT_IN)
12891     {
12892       gfc_error ("Second argument of operator interface at %L must be "
12893                  "INTENT(IN)", &where);
12894       return FAILURE;
12895     }
12896
12897   if (formal->sym->attr.optional)
12898     {
12899       gfc_error ("Second argument of operator interface at %L cannot be "
12900                  "optional", &where);
12901       return FAILURE;
12902     }
12903
12904   if (formal->next)
12905     {
12906       gfc_error ("Operator interface at %L must have, at most, two "
12907                  "arguments", &where);
12908       return FAILURE;
12909     }
12910
12911   return SUCCESS;
12912 }
12913
12914 static void
12915 gfc_resolve_uops (gfc_symtree *symtree)
12916 {
12917   gfc_interface *itr;
12918
12919   if (symtree == NULL)
12920     return;
12921
12922   gfc_resolve_uops (symtree->left);
12923   gfc_resolve_uops (symtree->right);
12924
12925   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12926     check_uop_procedure (itr->sym, itr->sym->declared_at);
12927 }
12928
12929
12930 /* Examine all of the expressions associated with a program unit,
12931    assign types to all intermediate expressions, make sure that all
12932    assignments are to compatible types and figure out which names
12933    refer to which functions or subroutines.  It doesn't check code
12934    block, which is handled by resolve_code.  */
12935
12936 static void
12937 resolve_types (gfc_namespace *ns)
12938 {
12939   gfc_namespace *n;
12940   gfc_charlen *cl;
12941   gfc_data *d;
12942   gfc_equiv *eq;
12943   gfc_namespace* old_ns = gfc_current_ns;
12944
12945   /* Check that all IMPLICIT types are ok.  */
12946   if (!ns->seen_implicit_none)
12947     {
12948       unsigned letter;
12949       for (letter = 0; letter != GFC_LETTERS; ++letter)
12950         if (ns->set_flag[letter]
12951             && resolve_typespec_used (&ns->default_type[letter],
12952                                       &ns->implicit_loc[letter],
12953                                       NULL) == FAILURE)
12954           return;
12955     }
12956
12957   gfc_current_ns = ns;
12958
12959   resolve_entries (ns);
12960
12961   resolve_common_vars (ns->blank_common.head, false);
12962   resolve_common_blocks (ns->common_root);
12963
12964   resolve_contained_functions (ns);
12965
12966   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12967
12968   for (cl = ns->cl_list; cl; cl = cl->next)
12969     resolve_charlen (cl);
12970
12971   gfc_traverse_ns (ns, resolve_symbol);
12972
12973   resolve_fntype (ns);
12974
12975   for (n = ns->contained; n; n = n->sibling)
12976     {
12977       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12978         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12979                    "also be PURE", n->proc_name->name,
12980                    &n->proc_name->declared_at);
12981
12982       resolve_types (n);
12983     }
12984
12985   forall_flag = 0;
12986   gfc_check_interfaces (ns);
12987
12988   gfc_traverse_ns (ns, resolve_values);
12989
12990   if (ns->save_all)
12991     gfc_save_all (ns);
12992
12993   iter_stack = NULL;
12994   for (d = ns->data; d; d = d->next)
12995     resolve_data (d);
12996
12997   iter_stack = NULL;
12998   gfc_traverse_ns (ns, gfc_formalize_init_value);
12999
13000   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13001
13002   if (ns->common_root != NULL)
13003     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13004
13005   for (eq = ns->equiv; eq; eq = eq->next)
13006     resolve_equivalence (eq);
13007
13008   /* Warn about unused labels.  */
13009   if (warn_unused_label)
13010     warn_unused_fortran_label (ns->st_labels);
13011
13012   gfc_resolve_uops (ns->uop_root);
13013
13014   gfc_current_ns = old_ns;
13015 }
13016
13017
13018 /* Call resolve_code recursively.  */
13019
13020 static void
13021 resolve_codes (gfc_namespace *ns)
13022 {
13023   gfc_namespace *n;
13024   bitmap_obstack old_obstack;
13025
13026   for (n = ns->contained; n; n = n->sibling)
13027     resolve_codes (n);
13028
13029   gfc_current_ns = ns;
13030
13031   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13032   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13033     cs_base = NULL;
13034
13035   /* Set to an out of range value.  */
13036   current_entry_id = -1;
13037
13038   old_obstack = labels_obstack;
13039   bitmap_obstack_initialize (&labels_obstack);
13040
13041   resolve_code (ns->code, ns);
13042
13043   bitmap_obstack_release (&labels_obstack);
13044   labels_obstack = old_obstack;
13045 }
13046
13047
13048 /* This function is called after a complete program unit has been compiled.
13049    Its purpose is to examine all of the expressions associated with a program
13050    unit, assign types to all intermediate expressions, make sure that all
13051    assignments are to compatible types and figure out which names refer to
13052    which functions or subroutines.  */
13053
13054 void
13055 gfc_resolve (gfc_namespace *ns)
13056 {
13057   gfc_namespace *old_ns;
13058   code_stack *old_cs_base;
13059
13060   if (ns->resolved)
13061     return;
13062
13063   ns->resolved = -1;
13064   old_ns = gfc_current_ns;
13065   old_cs_base = cs_base;
13066
13067   resolve_types (ns);
13068   resolve_codes (ns);
13069
13070   gfc_current_ns = old_ns;
13071   cs_base = old_cs_base;
13072   ns->resolved = 1;
13073
13074   gfc_run_passes (ns);
13075 }