OSDN Git Service

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