OSDN Git Service

* config/i386/i386.md (maxmin_int): Rename code attribute from
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32 #include "constructor.h"
33
34 /* Types used in equivalence statements.  */
35
36 typedef enum seq_type
37 {
38   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
39 }
40 seq_type;
41
42 /* Stack to keep track of the nesting of blocks as we move through the
43    code.  See resolve_branch() and resolve_code().  */
44
45 typedef struct code_stack
46 {
47   struct gfc_code *head, *current;
48   struct code_stack *prev;
49
50   /* This bitmap keeps track of the targets valid for a branch from
51      inside this block except for END {IF|SELECT}s of enclosing
52      blocks.  */
53   bitmap reachable_labels;
54 }
55 code_stack;
56
57 static code_stack *cs_base = NULL;
58
59
60 /* Nonzero if we're inside a FORALL block.  */
61
62 static int forall_flag;
63
64 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
65
66 static int omp_workshare_flag;
67
68 /* Nonzero if we are processing a formal arglist. The corresponding function
69    resets the flag each time that it is read.  */
70 static int formal_arg_flag = 0;
71
72 /* True if we are resolving a specification expression.  */
73 static int specification_expr = 0;
74
75 /* The id of the last entry seen.  */
76 static int current_entry_id;
77
78 /* We use bitmaps to determine if a branch target is valid.  */
79 static bitmap_obstack labels_obstack;
80
81 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
82 static bool inquiry_argument = false;
83
84 int
85 gfc_is_formal_arg (void)
86 {
87   return formal_arg_flag;
88 }
89
90 /* Is the symbol host associated?  */
91 static bool
92 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
93 {
94   for (ns = ns->parent; ns; ns = ns->parent)
95     {      
96       if (sym->ns == ns)
97         return true;
98     }
99
100   return false;
101 }
102
103 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
104    an ABSTRACT derived-type.  If where is not NULL, an error message with that
105    locus is printed, optionally using name.  */
106
107 static gfc_try
108 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
109 {
110   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
111     {
112       if (where)
113         {
114           if (name)
115             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
116                        name, where, ts->u.derived->name);
117           else
118             gfc_error ("ABSTRACT type '%s' used at %L",
119                        ts->u.derived->name, where);
120         }
121
122       return FAILURE;
123     }
124
125   return SUCCESS;
126 }
127
128
129 /* Resolve types of formal argument lists.  These have to be done early so that
130    the formal argument lists of module procedures can be copied to the
131    containing module before the individual procedures are resolved
132    individually.  We also resolve argument lists of procedures in interface
133    blocks because they are self-contained scoping units.
134
135    Since a dummy argument cannot be a non-dummy procedure, the only
136    resort left for untyped names are the IMPLICIT types.  */
137
138 static void
139 resolve_formal_arglist (gfc_symbol *proc)
140 {
141   gfc_formal_arglist *f;
142   gfc_symbol *sym;
143   int i;
144
145   if (proc->result != NULL)
146     sym = proc->result;
147   else
148     sym = proc;
149
150   if (gfc_elemental (proc)
151       || sym->attr.pointer || sym->attr.allocatable
152       || (sym->as && sym->as->rank > 0))
153     {
154       proc->attr.always_explicit = 1;
155       sym->attr.always_explicit = 1;
156     }
157
158   formal_arg_flag = 1;
159
160   for (f = proc->formal; f; f = f->next)
161     {
162       sym = f->sym;
163
164       if (sym == NULL)
165         {
166           /* Alternate return placeholder.  */
167           if (gfc_elemental (proc))
168             gfc_error ("Alternate return specifier in elemental subroutine "
169                        "'%s' at %L is not allowed", proc->name,
170                        &proc->declared_at);
171           if (proc->attr.function)
172             gfc_error ("Alternate return specifier in function "
173                        "'%s' at %L is not allowed", proc->name,
174                        &proc->declared_at);
175           continue;
176         }
177
178       if (sym->attr.if_source != IFSRC_UNKNOWN)
179         resolve_formal_arglist (sym);
180
181       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
182         {
183           if (gfc_pure (proc) && !gfc_pure (sym))
184             {
185               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
186                          "also be PURE", sym->name, &sym->declared_at);
187               continue;
188             }
189
190           if (gfc_elemental (proc))
191             {
192               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
193                          "procedure", &sym->declared_at);
194               continue;
195             }
196
197           if (sym->attr.function
198                 && sym->ts.type == BT_UNKNOWN
199                 && sym->attr.intrinsic)
200             {
201               gfc_intrinsic_sym *isym;
202               isym = gfc_find_function (sym->name);
203               if (isym == NULL || !isym->specific)
204                 {
205                   gfc_error ("Unable to find a specific INTRINSIC procedure "
206                              "for the reference '%s' at %L", sym->name,
207                              &sym->declared_at);
208                 }
209               sym->ts = isym->ts;
210             }
211
212           continue;
213         }
214
215       if (sym->ts.type == BT_UNKNOWN)
216         {
217           if (!sym->attr.function || sym->result == sym)
218             gfc_set_default_type (sym, 1, sym->ns);
219         }
220
221       gfc_resolve_array_spec (sym->as, 0);
222
223       /* We can't tell if an array with dimension (:) is assumed or deferred
224          shape until we know if it has the pointer or allocatable attributes.
225       */
226       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
227           && !(sym->attr.pointer || sym->attr.allocatable))
228         {
229           sym->as->type = AS_ASSUMED_SHAPE;
230           for (i = 0; i < sym->as->rank; i++)
231             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
232                                                   NULL, 1);
233         }
234
235       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
236           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
237           || sym->attr.optional)
238         {
239           proc->attr.always_explicit = 1;
240           if (proc->result)
241             proc->result->attr.always_explicit = 1;
242         }
243
244       /* If the flavor is unknown at this point, it has to be a variable.
245          A procedure specification would have already set the type.  */
246
247       if (sym->attr.flavor == FL_UNKNOWN)
248         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
249
250       if (gfc_pure (proc) && !sym->attr.pointer
251           && sym->attr.flavor != FL_PROCEDURE)
252         {
253           if (proc->attr.function && sym->attr.intent != INTENT_IN)
254             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
255                        "INTENT(IN)", sym->name, proc->name,
256                        &sym->declared_at);
257
258           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
259             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
260                        "have its INTENT specified", sym->name, proc->name,
261                        &sym->declared_at);
262         }
263
264       if (gfc_elemental (proc))
265         {
266           /* F2008, C1289.  */
267           if (sym->attr.codimension)
268             {
269               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
270                          "procedure", sym->name, &sym->declared_at);
271               continue;
272             }
273
274           if (sym->as != NULL)
275             {
276               gfc_error ("Argument '%s' of elemental procedure at %L must "
277                          "be scalar", sym->name, &sym->declared_at);
278               continue;
279             }
280
281           if (sym->attr.pointer)
282             {
283               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
284                          "have the POINTER attribute", sym->name,
285                          &sym->declared_at);
286               continue;
287             }
288
289           if (sym->attr.flavor == FL_PROCEDURE)
290             {
291               gfc_error ("Dummy procedure '%s' not allowed in elemental "
292                          "procedure '%s' at %L", sym->name, proc->name,
293                          &sym->declared_at);
294               continue;
295             }
296         }
297
298       /* Each dummy shall be specified to be scalar.  */
299       if (proc->attr.proc == PROC_ST_FUNCTION)
300         {
301           if (sym->as != NULL)
302             {
303               gfc_error ("Argument '%s' of statement function at %L must "
304                          "be scalar", sym->name, &sym->declared_at);
305               continue;
306             }
307
308           if (sym->ts.type == BT_CHARACTER)
309             {
310               gfc_charlen *cl = sym->ts.u.cl;
311               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
312                 {
313                   gfc_error ("Character-valued argument '%s' of statement "
314                              "function at %L must have constant length",
315                              sym->name, &sym->declared_at);
316                   continue;
317                 }
318             }
319         }
320     }
321   formal_arg_flag = 0;
322 }
323
324
325 /* Work function called when searching for symbols that have argument lists
326    associated with them.  */
327
328 static void
329 find_arglists (gfc_symbol *sym)
330 {
331   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
332     return;
333
334   resolve_formal_arglist (sym);
335 }
336
337
338 /* Given a namespace, resolve all formal argument lists within the namespace.
339  */
340
341 static void
342 resolve_formal_arglists (gfc_namespace *ns)
343 {
344   if (ns == NULL)
345     return;
346
347   gfc_traverse_ns (ns, find_arglists);
348 }
349
350
351 static void
352 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
353 {
354   gfc_try t;
355
356   /* If this namespace is not a function or an entry master function,
357      ignore it.  */
358   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
359       || sym->attr.entry_master)
360     return;
361
362   /* Try to find out of what the return type is.  */
363   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
364     {
365       t = gfc_set_default_type (sym->result, 0, ns);
366
367       if (t == FAILURE && !sym->result->attr.untyped)
368         {
369           if (sym->result == sym)
370             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
371                        sym->name, &sym->declared_at);
372           else if (!sym->result->attr.proc_pointer)
373             gfc_error ("Result '%s' of contained function '%s' at %L has "
374                        "no IMPLICIT type", sym->result->name, sym->name,
375                        &sym->result->declared_at);
376           sym->result->attr.untyped = 1;
377         }
378     }
379
380   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
381      type, lists the only ways a character length value of * can be used:
382      dummy arguments of procedures, named constants, and function results
383      in external functions.  Internal function results and results of module
384      procedures are not on this list, ergo, not permitted.  */
385
386   if (sym->result->ts.type == BT_CHARACTER)
387     {
388       gfc_charlen *cl = sym->result->ts.u.cl;
389       if (!cl || !cl->length)
390         {
391           /* See if this is a module-procedure and adapt error message
392              accordingly.  */
393           bool module_proc;
394           gcc_assert (ns->parent && ns->parent->proc_name);
395           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
396
397           gfc_error ("Character-valued %s '%s' at %L must not be"
398                      " assumed length",
399                      module_proc ? _("module procedure")
400                                  : _("internal function"),
401                      sym->name, &sym->declared_at);
402         }
403     }
404 }
405
406
407 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
408    introduce duplicates.  */
409
410 static void
411 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
412 {
413   gfc_formal_arglist *f, *new_arglist;
414   gfc_symbol *new_sym;
415
416   for (; new_args != NULL; new_args = new_args->next)
417     {
418       new_sym = new_args->sym;
419       /* See if this arg is already in the formal argument list.  */
420       for (f = proc->formal; f; f = f->next)
421         {
422           if (new_sym == f->sym)
423             break;
424         }
425
426       if (f)
427         continue;
428
429       /* Add a new argument.  Argument order is not important.  */
430       new_arglist = gfc_get_formal_arglist ();
431       new_arglist->sym = new_sym;
432       new_arglist->next = proc->formal;
433       proc->formal  = new_arglist;
434     }
435 }
436
437
438 /* Flag the arguments that are not present in all entries.  */
439
440 static void
441 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
442 {
443   gfc_formal_arglist *f, *head;
444   head = new_args;
445
446   for (f = proc->formal; f; f = f->next)
447     {
448       if (f->sym == NULL)
449         continue;
450
451       for (new_args = head; new_args; new_args = new_args->next)
452         {
453           if (new_args->sym == f->sym)
454             break;
455         }
456
457       if (new_args)
458         continue;
459
460       f->sym->attr.not_always_present = 1;
461     }
462 }
463
464
465 /* Resolve alternate entry points.  If a symbol has multiple entry points we
466    create a new master symbol for the main routine, and turn the existing
467    symbol into an entry point.  */
468
469 static void
470 resolve_entries (gfc_namespace *ns)
471 {
472   gfc_namespace *old_ns;
473   gfc_code *c;
474   gfc_symbol *proc;
475   gfc_entry_list *el;
476   char name[GFC_MAX_SYMBOL_LEN + 1];
477   static int master_count = 0;
478
479   if (ns->proc_name == NULL)
480     return;
481
482   /* No need to do anything if this procedure doesn't have alternate entry
483      points.  */
484   if (!ns->entries)
485     return;
486
487   /* We may already have resolved alternate entry points.  */
488   if (ns->proc_name->attr.entry_master)
489     return;
490
491   /* If this isn't a procedure something has gone horribly wrong.  */
492   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
493
494   /* Remember the current namespace.  */
495   old_ns = gfc_current_ns;
496
497   gfc_current_ns = ns;
498
499   /* Add the main entry point to the list of entry points.  */
500   el = gfc_get_entry_list ();
501   el->sym = ns->proc_name;
502   el->id = 0;
503   el->next = ns->entries;
504   ns->entries = el;
505   ns->proc_name->attr.entry = 1;
506
507   /* If it is a module function, it needs to be in the right namespace
508      so that gfc_get_fake_result_decl can gather up the results. The
509      need for this arose in get_proc_name, where these beasts were
510      left in their own namespace, to keep prior references linked to
511      the entry declaration.*/
512   if (ns->proc_name->attr.function
513       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
514     el->sym->ns = ns;
515
516   /* Do the same for entries where the master is not a module
517      procedure.  These are retained in the module namespace because
518      of the module procedure declaration.  */
519   for (el = el->next; el; el = el->next)
520     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
521           && el->sym->attr.mod_proc)
522       el->sym->ns = ns;
523   el = ns->entries;
524
525   /* Add an entry statement for it.  */
526   c = gfc_get_code ();
527   c->op = EXEC_ENTRY;
528   c->ext.entry = el;
529   c->next = ns->code;
530   ns->code = c;
531
532   /* Create a new symbol for the master function.  */
533   /* Give the internal function a unique name (within this file).
534      Also include the function name so the user has some hope of figuring
535      out what is going on.  */
536   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
537             master_count++, ns->proc_name->name);
538   gfc_get_ha_symbol (name, &proc);
539   gcc_assert (proc != NULL);
540
541   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
542   if (ns->proc_name->attr.subroutine)
543     gfc_add_subroutine (&proc->attr, proc->name, NULL);
544   else
545     {
546       gfc_symbol *sym;
547       gfc_typespec *ts, *fts;
548       gfc_array_spec *as, *fas;
549       gfc_add_function (&proc->attr, proc->name, NULL);
550       proc->result = proc;
551       fas = ns->entries->sym->as;
552       fas = fas ? fas : ns->entries->sym->result->as;
553       fts = &ns->entries->sym->result->ts;
554       if (fts->type == BT_UNKNOWN)
555         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
556       for (el = ns->entries->next; el; el = el->next)
557         {
558           ts = &el->sym->result->ts;
559           as = el->sym->as;
560           as = as ? as : el->sym->result->as;
561           if (ts->type == BT_UNKNOWN)
562             ts = gfc_get_default_type (el->sym->result->name, NULL);
563
564           if (! gfc_compare_types (ts, fts)
565               || (el->sym->result->attr.dimension
566                   != ns->entries->sym->result->attr.dimension)
567               || (el->sym->result->attr.pointer
568                   != ns->entries->sym->result->attr.pointer))
569             break;
570           else if (as && fas && ns->entries->sym->result != el->sym->result
571                       && gfc_compare_array_spec (as, fas) == 0)
572             gfc_error ("Function %s at %L has entries with mismatched "
573                        "array specifications", ns->entries->sym->name,
574                        &ns->entries->sym->declared_at);
575           /* The characteristics need to match and thus both need to have
576              the same string length, i.e. both len=*, or both len=4.
577              Having both len=<variable> is also possible, but difficult to
578              check at compile time.  */
579           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
580                    && (((ts->u.cl->length && !fts->u.cl->length)
581                         ||(!ts->u.cl->length && fts->u.cl->length))
582                        || (ts->u.cl->length
583                            && ts->u.cl->length->expr_type
584                               != fts->u.cl->length->expr_type)
585                        || (ts->u.cl->length
586                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
587                            && mpz_cmp (ts->u.cl->length->value.integer,
588                                        fts->u.cl->length->value.integer) != 0)))
589             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
590                             "entries returning variables of different "
591                             "string lengths", ns->entries->sym->name,
592                             &ns->entries->sym->declared_at);
593         }
594
595       if (el == NULL)
596         {
597           sym = ns->entries->sym->result;
598           /* All result types the same.  */
599           proc->ts = *fts;
600           if (sym->attr.dimension)
601             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
602           if (sym->attr.pointer)
603             gfc_add_pointer (&proc->attr, NULL);
604         }
605       else
606         {
607           /* Otherwise the result will be passed through a union by
608              reference.  */
609           proc->attr.mixed_entry_master = 1;
610           for (el = ns->entries; el; el = el->next)
611             {
612               sym = el->sym->result;
613               if (sym->attr.dimension)
614                 {
615                   if (el == ns->entries)
616                     gfc_error ("FUNCTION result %s can't be an array in "
617                                "FUNCTION %s at %L", sym->name,
618                                ns->entries->sym->name, &sym->declared_at);
619                   else
620                     gfc_error ("ENTRY result %s can't be an array in "
621                                "FUNCTION %s at %L", sym->name,
622                                ns->entries->sym->name, &sym->declared_at);
623                 }
624               else if (sym->attr.pointer)
625                 {
626                   if (el == ns->entries)
627                     gfc_error ("FUNCTION result %s can't be a POINTER in "
628                                "FUNCTION %s at %L", sym->name,
629                                ns->entries->sym->name, &sym->declared_at);
630                   else
631                     gfc_error ("ENTRY result %s can't be a POINTER in "
632                                "FUNCTION %s at %L", sym->name,
633                                ns->entries->sym->name, &sym->declared_at);
634                 }
635               else
636                 {
637                   ts = &sym->ts;
638                   if (ts->type == BT_UNKNOWN)
639                     ts = gfc_get_default_type (sym->name, NULL);
640                   switch (ts->type)
641                     {
642                     case BT_INTEGER:
643                       if (ts->kind == gfc_default_integer_kind)
644                         sym = NULL;
645                       break;
646                     case BT_REAL:
647                       if (ts->kind == gfc_default_real_kind
648                           || ts->kind == gfc_default_double_kind)
649                         sym = NULL;
650                       break;
651                     case BT_COMPLEX:
652                       if (ts->kind == gfc_default_complex_kind)
653                         sym = NULL;
654                       break;
655                     case BT_LOGICAL:
656                       if (ts->kind == gfc_default_logical_kind)
657                         sym = NULL;
658                       break;
659                     case BT_UNKNOWN:
660                       /* We will issue error elsewhere.  */
661                       sym = NULL;
662                       break;
663                     default:
664                       break;
665                     }
666                   if (sym)
667                     {
668                       if (el == ns->entries)
669                         gfc_error ("FUNCTION result %s can't be of type %s "
670                                    "in FUNCTION %s at %L", sym->name,
671                                    gfc_typename (ts), ns->entries->sym->name,
672                                    &sym->declared_at);
673                       else
674                         gfc_error ("ENTRY result %s can't be of type %s "
675                                    "in FUNCTION %s at %L", sym->name,
676                                    gfc_typename (ts), ns->entries->sym->name,
677                                    &sym->declared_at);
678                     }
679                 }
680             }
681         }
682     }
683   proc->attr.access = ACCESS_PRIVATE;
684   proc->attr.entry_master = 1;
685
686   /* Merge all the entry point arguments.  */
687   for (el = ns->entries; el; el = el->next)
688     merge_argument_lists (proc, el->sym->formal);
689
690   /* Check the master formal arguments for any that are not
691      present in all entry points.  */
692   for (el = ns->entries; el; el = el->next)
693     check_argument_lists (proc, el->sym->formal);
694
695   /* Use the master function for the function body.  */
696   ns->proc_name = proc;
697
698   /* Finalize the new symbols.  */
699   gfc_commit_symbols ();
700
701   /* Restore the original namespace.  */
702   gfc_current_ns = old_ns;
703 }
704
705
706 static bool
707 has_default_initializer (gfc_symbol *der)
708 {
709   gfc_component *c;
710
711   gcc_assert (der->attr.flavor == FL_DERIVED);
712   for (c = der->components; c; c = c->next)
713     if ((c->ts.type != BT_DERIVED && c->initializer)
714         || (c->ts.type == BT_DERIVED
715             && (!c->attr.pointer && has_default_initializer (c->ts.u.derived))))
716       break;
717
718   return c != NULL;
719 }
720
721 /* Resolve common variables.  */
722 static void
723 resolve_common_vars (gfc_symbol *sym, bool named_common)
724 {
725   gfc_symbol *csym = sym;
726
727   for (; csym; csym = csym->common_next)
728     {
729       if (csym->value || csym->attr.data)
730         {
731           if (!csym->ns->is_block_data)
732             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
733                             "but only in BLOCK DATA initialization is "
734                             "allowed", csym->name, &csym->declared_at);
735           else if (!named_common)
736             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
737                             "in a blank COMMON but initialization is only "
738                             "allowed in named common blocks", csym->name,
739                             &csym->declared_at);
740         }
741
742       if (csym->ts.type != BT_DERIVED)
743         continue;
744
745       if (!(csym->ts.u.derived->attr.sequence
746             || csym->ts.u.derived->attr.is_bind_c))
747         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
748                        "has neither the SEQUENCE nor the BIND(C) "
749                        "attribute", csym->name, &csym->declared_at);
750       if (csym->ts.u.derived->attr.alloc_comp)
751         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
752                        "has an ultimate component that is "
753                        "allocatable", csym->name, &csym->declared_at);
754       if (has_default_initializer (csym->ts.u.derived))
755         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
756                        "may not have default initializer", csym->name,
757                        &csym->declared_at);
758
759       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
760         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
761     }
762 }
763
764 /* Resolve common blocks.  */
765 static void
766 resolve_common_blocks (gfc_symtree *common_root)
767 {
768   gfc_symbol *sym;
769
770   if (common_root == NULL)
771     return;
772
773   if (common_root->left)
774     resolve_common_blocks (common_root->left);
775   if (common_root->right)
776     resolve_common_blocks (common_root->right);
777
778   resolve_common_vars (common_root->n.common->head, true);
779
780   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
781   if (sym == NULL)
782     return;
783
784   if (sym->attr.flavor == FL_PARAMETER)
785     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
786                sym->name, &common_root->n.common->where, &sym->declared_at);
787
788   if (sym->attr.intrinsic)
789     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
790                sym->name, &common_root->n.common->where);
791   else if (sym->attr.result
792            || gfc_is_function_return_value (sym, gfc_current_ns))
793     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
794                     "that is also a function result", sym->name,
795                     &common_root->n.common->where);
796   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
797            && sym->attr.proc != PROC_ST_FUNCTION)
798     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
799                     "that is also a global procedure", sym->name,
800                     &common_root->n.common->where);
801 }
802
803
804 /* Resolve contained function types.  Because contained functions can call one
805    another, they have to be worked out before any of the contained procedures
806    can be resolved.
807
808    The good news is that if a function doesn't already have a type, the only
809    way it can get one is through an IMPLICIT type or a RESULT variable, because
810    by definition contained functions are contained namespace they're contained
811    in, not in a sibling or parent namespace.  */
812
813 static void
814 resolve_contained_functions (gfc_namespace *ns)
815 {
816   gfc_namespace *child;
817   gfc_entry_list *el;
818
819   resolve_formal_arglists (ns);
820
821   for (child = ns->contained; child; child = child->sibling)
822     {
823       /* Resolve alternate entry points first.  */
824       resolve_entries (child);
825
826       /* Then check function return types.  */
827       resolve_contained_fntype (child->proc_name, child);
828       for (el = child->entries; el; el = el->next)
829         resolve_contained_fntype (el->sym, child);
830     }
831 }
832
833
834 /* Resolve all of the elements of a structure constructor and make sure that
835    the types are correct.  */
836
837 static gfc_try
838 resolve_structure_cons (gfc_expr *expr)
839 {
840   gfc_constructor *cons;
841   gfc_component *comp;
842   gfc_try t;
843   symbol_attribute a;
844
845   t = SUCCESS;
846   cons = gfc_constructor_first (expr->value.constructor);
847   /* A constructor may have references if it is the result of substituting a
848      parameter variable.  In this case we just pull out the component we
849      want.  */
850   if (expr->ref)
851     comp = expr->ref->u.c.sym->components;
852   else
853     comp = expr->ts.u.derived->components;
854
855   /* See if the user is trying to invoke a structure constructor for one of
856      the iso_c_binding derived types.  */
857   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
858       && expr->ts.u.derived->ts.is_iso_c && cons
859       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
860     {
861       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
862                  expr->ts.u.derived->name, &(expr->where));
863       return FAILURE;
864     }
865
866   /* Return if structure constructor is c_null_(fun)prt.  */
867   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
868       && expr->ts.u.derived->ts.is_iso_c && cons
869       && cons->expr && cons->expr->expr_type == EXPR_NULL)
870     return SUCCESS;
871
872   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
873     {
874       int rank;
875
876       if (!cons->expr)
877         continue;
878
879       if (gfc_resolve_expr (cons->expr) == FAILURE)
880         {
881           t = FAILURE;
882           continue;
883         }
884
885       rank = comp->as ? comp->as->rank : 0;
886       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
887           && (comp->attr.allocatable || cons->expr->rank))
888         {
889           gfc_error ("The rank of the element in the derived type "
890                      "constructor at %L does not match that of the "
891                      "component (%d/%d)", &cons->expr->where,
892                      cons->expr->rank, rank);
893           t = FAILURE;
894         }
895
896       /* If we don't have the right type, try to convert it.  */
897
898       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
899         {
900           t = FAILURE;
901           if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
902             gfc_error ("The element in the derived type constructor at %L, "
903                        "for pointer component '%s', is %s but should be %s",
904                        &cons->expr->where, comp->name,
905                        gfc_basic_typename (cons->expr->ts.type),
906                        gfc_basic_typename (comp->ts.type));
907           else
908             t = gfc_convert_type (cons->expr, &comp->ts, 1);
909         }
910
911       if (cons->expr->expr_type == EXPR_NULL
912           && !(comp->attr.pointer || comp->attr.allocatable
913                || comp->attr.proc_pointer
914                || (comp->ts.type == BT_CLASS
915                    && (comp->ts.u.derived->components->attr.pointer
916                        || comp->ts.u.derived->components->attr.allocatable))))
917         {
918           t = FAILURE;
919           gfc_error ("The NULL in the derived type constructor at %L is "
920                      "being applied to component '%s', which is neither "
921                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
922                      comp->name);
923         }
924
925       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
926         continue;
927
928       a = gfc_expr_attr (cons->expr);
929
930       if (!a.pointer && !a.target)
931         {
932           t = FAILURE;
933           gfc_error ("The element in the derived type constructor at %L, "
934                      "for pointer component '%s' should be a POINTER or "
935                      "a TARGET", &cons->expr->where, comp->name);
936         }
937
938       /* F2003, C1272 (3).  */
939       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
940           && (gfc_impure_variable (cons->expr->symtree->n.sym)
941               || gfc_is_coindexed (cons->expr)))
942         {
943           t = FAILURE;
944           gfc_error ("Invalid expression in the derived type constructor for "
945                      "pointer component '%s' at %L in PURE procedure",
946                      comp->name, &cons->expr->where);
947         }
948     }
949
950   return t;
951 }
952
953
954 /****************** Expression name resolution ******************/
955
956 /* Returns 0 if a symbol was not declared with a type or
957    attribute declaration statement, nonzero otherwise.  */
958
959 static int
960 was_declared (gfc_symbol *sym)
961 {
962   symbol_attribute a;
963
964   a = sym->attr;
965
966   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
967     return 1;
968
969   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
970       || a.optional || a.pointer || a.save || a.target || a.volatile_
971       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
972       || a.asynchronous || a.codimension)
973     return 1;
974
975   return 0;
976 }
977
978
979 /* Determine if a symbol is generic or not.  */
980
981 static int
982 generic_sym (gfc_symbol *sym)
983 {
984   gfc_symbol *s;
985
986   if (sym->attr.generic ||
987       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
988     return 1;
989
990   if (was_declared (sym) || sym->ns->parent == NULL)
991     return 0;
992
993   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
994   
995   if (s != NULL)
996     {
997       if (s == sym)
998         return 0;
999       else
1000         return generic_sym (s);
1001     }
1002
1003   return 0;
1004 }
1005
1006
1007 /* Determine if a symbol is specific or not.  */
1008
1009 static int
1010 specific_sym (gfc_symbol *sym)
1011 {
1012   gfc_symbol *s;
1013
1014   if (sym->attr.if_source == IFSRC_IFBODY
1015       || sym->attr.proc == PROC_MODULE
1016       || sym->attr.proc == PROC_INTERNAL
1017       || sym->attr.proc == PROC_ST_FUNCTION
1018       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1019       || sym->attr.external)
1020     return 1;
1021
1022   if (was_declared (sym) || sym->ns->parent == NULL)
1023     return 0;
1024
1025   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1026
1027   return (s == NULL) ? 0 : specific_sym (s);
1028 }
1029
1030
1031 /* Figure out if the procedure is specific, generic or unknown.  */
1032
1033 typedef enum
1034 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1035 proc_type;
1036
1037 static proc_type
1038 procedure_kind (gfc_symbol *sym)
1039 {
1040   if (generic_sym (sym))
1041     return PTYPE_GENERIC;
1042
1043   if (specific_sym (sym))
1044     return PTYPE_SPECIFIC;
1045
1046   return PTYPE_UNKNOWN;
1047 }
1048
1049 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1050    is nonzero when matching actual arguments.  */
1051
1052 static int need_full_assumed_size = 0;
1053
1054 static bool
1055 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1056 {
1057   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1058       return false;
1059
1060   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1061      What should it be?  */
1062   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1063           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1064                && (e->ref->u.ar.type == AR_FULL))
1065     {
1066       gfc_error ("The upper bound in the last dimension must "
1067                  "appear in the reference to the assumed size "
1068                  "array '%s' at %L", sym->name, &e->where);
1069       return true;
1070     }
1071   return false;
1072 }
1073
1074
1075 /* Look for bad assumed size array references in argument expressions
1076   of elemental and array valued intrinsic procedures.  Since this is
1077   called from procedure resolution functions, it only recurses at
1078   operators.  */
1079
1080 static bool
1081 resolve_assumed_size_actual (gfc_expr *e)
1082 {
1083   if (e == NULL)
1084    return false;
1085
1086   switch (e->expr_type)
1087     {
1088     case EXPR_VARIABLE:
1089       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1090         return true;
1091       break;
1092
1093     case EXPR_OP:
1094       if (resolve_assumed_size_actual (e->value.op.op1)
1095           || resolve_assumed_size_actual (e->value.op.op2))
1096         return true;
1097       break;
1098
1099     default:
1100       break;
1101     }
1102   return false;
1103 }
1104
1105
1106 /* Check a generic procedure, passed as an actual argument, to see if
1107    there is a matching specific name.  If none, it is an error, and if
1108    more than one, the reference is ambiguous.  */
1109 static int
1110 count_specific_procs (gfc_expr *e)
1111 {
1112   int n;
1113   gfc_interface *p;
1114   gfc_symbol *sym;
1115         
1116   n = 0;
1117   sym = e->symtree->n.sym;
1118
1119   for (p = sym->generic; p; p = p->next)
1120     if (strcmp (sym->name, p->sym->name) == 0)
1121       {
1122         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1123                                        sym->name);
1124         n++;
1125       }
1126
1127   if (n > 1)
1128     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1129                &e->where);
1130
1131   if (n == 0)
1132     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1133                "argument at %L", sym->name, &e->where);
1134
1135   return n;
1136 }
1137
1138
1139 /* See if a call to sym could possibly be a not allowed RECURSION because of
1140    a missing RECURIVE declaration.  This means that either sym is the current
1141    context itself, or sym is the parent of a contained procedure calling its
1142    non-RECURSIVE containing procedure.
1143    This also works if sym is an ENTRY.  */
1144
1145 static bool
1146 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1147 {
1148   gfc_symbol* proc_sym;
1149   gfc_symbol* context_proc;
1150   gfc_namespace* real_context;
1151
1152   if (sym->attr.flavor == FL_PROGRAM)
1153     return false;
1154
1155   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1156
1157   /* If we've got an ENTRY, find real procedure.  */
1158   if (sym->attr.entry && sym->ns->entries)
1159     proc_sym = sym->ns->entries->sym;
1160   else
1161     proc_sym = sym;
1162
1163   /* If sym is RECURSIVE, all is well of course.  */
1164   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1165     return false;
1166
1167   /* Find the context procedure's "real" symbol if it has entries.
1168      We look for a procedure symbol, so recurse on the parents if we don't
1169      find one (like in case of a BLOCK construct).  */
1170   for (real_context = context; ; real_context = real_context->parent)
1171     {
1172       /* We should find something, eventually!  */
1173       gcc_assert (real_context);
1174
1175       context_proc = (real_context->entries ? real_context->entries->sym
1176                                             : real_context->proc_name);
1177
1178       /* In some special cases, there may not be a proc_name, like for this
1179          invalid code:
1180          real(bad_kind()) function foo () ...
1181          when checking the call to bad_kind ().
1182          In these cases, we simply return here and assume that the
1183          call is ok.  */
1184       if (!context_proc)
1185         return false;
1186
1187       if (context_proc->attr.flavor != FL_LABEL)
1188         break;
1189     }
1190
1191   /* A call from sym's body to itself is recursion, of course.  */
1192   if (context_proc == proc_sym)
1193     return true;
1194
1195   /* The same is true if context is a contained procedure and sym the
1196      containing one.  */
1197   if (context_proc->attr.contained)
1198     {
1199       gfc_symbol* parent_proc;
1200
1201       gcc_assert (context->parent);
1202       parent_proc = (context->parent->entries ? context->parent->entries->sym
1203                                               : context->parent->proc_name);
1204
1205       if (parent_proc == proc_sym)
1206         return true;
1207     }
1208
1209   return false;
1210 }
1211
1212
1213 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1214    its typespec and formal argument list.  */
1215
1216 static gfc_try
1217 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1218 {
1219   gfc_intrinsic_sym* isym;
1220   const char* symstd;
1221
1222   if (sym->formal)
1223     return SUCCESS;
1224
1225   /* We already know this one is an intrinsic, so we don't call
1226      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1227      gfc_find_subroutine directly to check whether it is a function or
1228      subroutine.  */
1229
1230   if ((isym = gfc_find_function (sym->name)))
1231     {
1232       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1233           && !sym->attr.implicit_type)
1234         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1235                       " ignored", sym->name, &sym->declared_at);
1236
1237       if (!sym->attr.function &&
1238           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1239         return FAILURE;
1240
1241       sym->ts = isym->ts;
1242     }
1243   else if ((isym = gfc_find_subroutine (sym->name)))
1244     {
1245       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1246         {
1247           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1248                       " specifier", sym->name, &sym->declared_at);
1249           return FAILURE;
1250         }
1251
1252       if (!sym->attr.subroutine &&
1253           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1254         return FAILURE;
1255     }
1256   else
1257     {
1258       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1259                  &sym->declared_at);
1260       return FAILURE;
1261     }
1262
1263   gfc_copy_formal_args_intr (sym, isym);
1264
1265   /* Check it is actually available in the standard settings.  */
1266   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1267       == FAILURE)
1268     {
1269       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1270                  " available in the current standard settings but %s.  Use"
1271                  " an appropriate -std=* option or enable -fall-intrinsics"
1272                  " in order to use it.",
1273                  sym->name, &sym->declared_at, symstd);
1274       return FAILURE;
1275     }
1276
1277   return SUCCESS;
1278 }
1279
1280
1281 /* Resolve a procedure expression, like passing it to a called procedure or as
1282    RHS for a procedure pointer assignment.  */
1283
1284 static gfc_try
1285 resolve_procedure_expression (gfc_expr* expr)
1286 {
1287   gfc_symbol* sym;
1288
1289   if (expr->expr_type != EXPR_VARIABLE)
1290     return SUCCESS;
1291   gcc_assert (expr->symtree);
1292
1293   sym = expr->symtree->n.sym;
1294
1295   if (sym->attr.intrinsic)
1296     resolve_intrinsic (sym, &expr->where);
1297
1298   if (sym->attr.flavor != FL_PROCEDURE
1299       || (sym->attr.function && sym->result == sym))
1300     return SUCCESS;
1301
1302   /* A non-RECURSIVE procedure that is used as procedure expression within its
1303      own body is in danger of being called recursively.  */
1304   if (is_illegal_recursion (sym, gfc_current_ns))
1305     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1306                  " itself recursively.  Declare it RECURSIVE or use"
1307                  " -frecursive", sym->name, &expr->where);
1308   
1309   return SUCCESS;
1310 }
1311
1312
1313 /* Resolve an actual argument list.  Most of the time, this is just
1314    resolving the expressions in the list.
1315    The exception is that we sometimes have to decide whether arguments
1316    that look like procedure arguments are really simple variable
1317    references.  */
1318
1319 static gfc_try
1320 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1321                         bool no_formal_args)
1322 {
1323   gfc_symbol *sym;
1324   gfc_symtree *parent_st;
1325   gfc_expr *e;
1326   int save_need_full_assumed_size;
1327   gfc_component *comp;
1328
1329   for (; arg; arg = arg->next)
1330     {
1331       e = arg->expr;
1332       if (e == NULL)
1333         {
1334           /* Check the label is a valid branching target.  */
1335           if (arg->label)
1336             {
1337               if (arg->label->defined == ST_LABEL_UNKNOWN)
1338                 {
1339                   gfc_error ("Label %d referenced at %L is never defined",
1340                              arg->label->value, &arg->label->where);
1341                   return FAILURE;
1342                 }
1343             }
1344           continue;
1345         }
1346
1347       if (gfc_is_proc_ptr_comp (e, &comp))
1348         {
1349           e->ts = comp->ts;
1350           if (e->expr_type == EXPR_PPC)
1351             {
1352               if (comp->as != NULL)
1353                 e->rank = comp->as->rank;
1354               e->expr_type = EXPR_FUNCTION;
1355             }
1356           if (gfc_resolve_expr (e) == FAILURE)                          
1357             return FAILURE; 
1358           goto argument_list;
1359         }
1360
1361       if (e->expr_type == EXPR_VARIABLE
1362             && e->symtree->n.sym->attr.generic
1363             && no_formal_args
1364             && count_specific_procs (e) != 1)
1365         return FAILURE;
1366
1367       if (e->ts.type != BT_PROCEDURE)
1368         {
1369           save_need_full_assumed_size = need_full_assumed_size;
1370           if (e->expr_type != EXPR_VARIABLE)
1371             need_full_assumed_size = 0;
1372           if (gfc_resolve_expr (e) != SUCCESS)
1373             return FAILURE;
1374           need_full_assumed_size = save_need_full_assumed_size;
1375           goto argument_list;
1376         }
1377
1378       /* See if the expression node should really be a variable reference.  */
1379
1380       sym = e->symtree->n.sym;
1381
1382       if (sym->attr.flavor == FL_PROCEDURE
1383           || sym->attr.intrinsic
1384           || sym->attr.external)
1385         {
1386           int actual_ok;
1387
1388           /* If a procedure is not already determined to be something else
1389              check if it is intrinsic.  */
1390           if (!sym->attr.intrinsic
1391               && !(sym->attr.external || sym->attr.use_assoc
1392                    || sym->attr.if_source == IFSRC_IFBODY)
1393               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1394             sym->attr.intrinsic = 1;
1395
1396           if (sym->attr.proc == PROC_ST_FUNCTION)
1397             {
1398               gfc_error ("Statement function '%s' at %L is not allowed as an "
1399                          "actual argument", sym->name, &e->where);
1400             }
1401
1402           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1403                                                sym->attr.subroutine);
1404           if (sym->attr.intrinsic && actual_ok == 0)
1405             {
1406               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1407                          "actual argument", sym->name, &e->where);
1408             }
1409
1410           if (sym->attr.contained && !sym->attr.use_assoc
1411               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1412             {
1413               gfc_error ("Internal procedure '%s' is not allowed as an "
1414                          "actual argument at %L", sym->name, &e->where);
1415             }
1416
1417           if (sym->attr.elemental && !sym->attr.intrinsic)
1418             {
1419               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1420                          "allowed as an actual argument at %L", sym->name,
1421                          &e->where);
1422             }
1423
1424           /* Check if a generic interface has a specific procedure
1425             with the same name before emitting an error.  */
1426           if (sym->attr.generic && count_specific_procs (e) != 1)
1427             return FAILURE;
1428           
1429           /* Just in case a specific was found for the expression.  */
1430           sym = e->symtree->n.sym;
1431
1432           /* If the symbol is the function that names the current (or
1433              parent) scope, then we really have a variable reference.  */
1434
1435           if (gfc_is_function_return_value (sym, sym->ns))
1436             goto got_variable;
1437
1438           /* If all else fails, see if we have a specific intrinsic.  */
1439           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1440             {
1441               gfc_intrinsic_sym *isym;
1442
1443               isym = gfc_find_function (sym->name);
1444               if (isym == NULL || !isym->specific)
1445                 {
1446                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1447                              "for the reference '%s' at %L", sym->name,
1448                              &e->where);
1449                   return FAILURE;
1450                 }
1451               sym->ts = isym->ts;
1452               sym->attr.intrinsic = 1;
1453               sym->attr.function = 1;
1454             }
1455
1456           if (gfc_resolve_expr (e) == FAILURE)
1457             return FAILURE;
1458           goto argument_list;
1459         }
1460
1461       /* See if the name is a module procedure in a parent unit.  */
1462
1463       if (was_declared (sym) || sym->ns->parent == NULL)
1464         goto got_variable;
1465
1466       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1467         {
1468           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1469           return FAILURE;
1470         }
1471
1472       if (parent_st == NULL)
1473         goto got_variable;
1474
1475       sym = parent_st->n.sym;
1476       e->symtree = parent_st;           /* Point to the right thing.  */
1477
1478       if (sym->attr.flavor == FL_PROCEDURE
1479           || sym->attr.intrinsic
1480           || sym->attr.external)
1481         {
1482           if (gfc_resolve_expr (e) == FAILURE)
1483             return FAILURE;
1484           goto argument_list;
1485         }
1486
1487     got_variable:
1488       e->expr_type = EXPR_VARIABLE;
1489       e->ts = sym->ts;
1490       if (sym->as != NULL)
1491         {
1492           e->rank = sym->as->rank;
1493           e->ref = gfc_get_ref ();
1494           e->ref->type = REF_ARRAY;
1495           e->ref->u.ar.type = AR_FULL;
1496           e->ref->u.ar.as = sym->as;
1497         }
1498
1499       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1500          primary.c (match_actual_arg). If above code determines that it
1501          is a  variable instead, it needs to be resolved as it was not
1502          done at the beginning of this function.  */
1503       save_need_full_assumed_size = need_full_assumed_size;
1504       if (e->expr_type != EXPR_VARIABLE)
1505         need_full_assumed_size = 0;
1506       if (gfc_resolve_expr (e) != SUCCESS)
1507         return FAILURE;
1508       need_full_assumed_size = save_need_full_assumed_size;
1509
1510     argument_list:
1511       /* Check argument list functions %VAL, %LOC and %REF.  There is
1512          nothing to do for %REF.  */
1513       if (arg->name && arg->name[0] == '%')
1514         {
1515           if (strncmp ("%VAL", arg->name, 4) == 0)
1516             {
1517               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1518                 {
1519                   gfc_error ("By-value argument at %L is not of numeric "
1520                              "type", &e->where);
1521                   return FAILURE;
1522                 }
1523
1524               if (e->rank)
1525                 {
1526                   gfc_error ("By-value argument at %L cannot be an array or "
1527                              "an array section", &e->where);
1528                 return FAILURE;
1529                 }
1530
1531               /* Intrinsics are still PROC_UNKNOWN here.  However,
1532                  since same file external procedures are not resolvable
1533                  in gfortran, it is a good deal easier to leave them to
1534                  intrinsic.c.  */
1535               if (ptype != PROC_UNKNOWN
1536                   && ptype != PROC_DUMMY
1537                   && ptype != PROC_EXTERNAL
1538                   && ptype != PROC_MODULE)
1539                 {
1540                   gfc_error ("By-value argument at %L is not allowed "
1541                              "in this context", &e->where);
1542                   return FAILURE;
1543                 }
1544             }
1545
1546           /* Statement functions have already been excluded above.  */
1547           else if (strncmp ("%LOC", arg->name, 4) == 0
1548                    && e->ts.type == BT_PROCEDURE)
1549             {
1550               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1551                 {
1552                   gfc_error ("Passing internal procedure at %L by location "
1553                              "not allowed", &e->where);
1554                   return FAILURE;
1555                 }
1556             }
1557         }
1558
1559       /* Fortran 2008, C1237.  */
1560       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1561           && gfc_has_ultimate_pointer (e))
1562         {
1563           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1564                      "component", &e->where);
1565           return FAILURE;
1566         }
1567     }
1568
1569   return SUCCESS;
1570 }
1571
1572
1573 /* Do the checks of the actual argument list that are specific to elemental
1574    procedures.  If called with c == NULL, we have a function, otherwise if
1575    expr == NULL, we have a subroutine.  */
1576
1577 static gfc_try
1578 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1579 {
1580   gfc_actual_arglist *arg0;
1581   gfc_actual_arglist *arg;
1582   gfc_symbol *esym = NULL;
1583   gfc_intrinsic_sym *isym = NULL;
1584   gfc_expr *e = NULL;
1585   gfc_intrinsic_arg *iformal = NULL;
1586   gfc_formal_arglist *eformal = NULL;
1587   bool formal_optional = false;
1588   bool set_by_optional = false;
1589   int i;
1590   int rank = 0;
1591
1592   /* Is this an elemental procedure?  */
1593   if (expr && expr->value.function.actual != NULL)
1594     {
1595       if (expr->value.function.esym != NULL
1596           && expr->value.function.esym->attr.elemental)
1597         {
1598           arg0 = expr->value.function.actual;
1599           esym = expr->value.function.esym;
1600         }
1601       else if (expr->value.function.isym != NULL
1602                && expr->value.function.isym->elemental)
1603         {
1604           arg0 = expr->value.function.actual;
1605           isym = expr->value.function.isym;
1606         }
1607       else
1608         return SUCCESS;
1609     }
1610   else if (c && c->ext.actual != NULL)
1611     {
1612       arg0 = c->ext.actual;
1613       
1614       if (c->resolved_sym)
1615         esym = c->resolved_sym;
1616       else
1617         esym = c->symtree->n.sym;
1618       gcc_assert (esym);
1619
1620       if (!esym->attr.elemental)
1621         return SUCCESS;
1622     }
1623   else
1624     return SUCCESS;
1625
1626   /* The rank of an elemental is the rank of its array argument(s).  */
1627   for (arg = arg0; arg; arg = arg->next)
1628     {
1629       if (arg->expr != NULL && arg->expr->rank > 0)
1630         {
1631           rank = arg->expr->rank;
1632           if (arg->expr->expr_type == EXPR_VARIABLE
1633               && arg->expr->symtree->n.sym->attr.optional)
1634             set_by_optional = true;
1635
1636           /* Function specific; set the result rank and shape.  */
1637           if (expr)
1638             {
1639               expr->rank = rank;
1640               if (!expr->shape && arg->expr->shape)
1641                 {
1642                   expr->shape = gfc_get_shape (rank);
1643                   for (i = 0; i < rank; i++)
1644                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1645                 }
1646             }
1647           break;
1648         }
1649     }
1650
1651   /* If it is an array, it shall not be supplied as an actual argument
1652      to an elemental procedure unless an array of the same rank is supplied
1653      as an actual argument corresponding to a nonoptional dummy argument of
1654      that elemental procedure(12.4.1.5).  */
1655   formal_optional = false;
1656   if (isym)
1657     iformal = isym->formal;
1658   else
1659     eformal = esym->formal;
1660
1661   for (arg = arg0; arg; arg = arg->next)
1662     {
1663       if (eformal)
1664         {
1665           if (eformal->sym && eformal->sym->attr.optional)
1666             formal_optional = true;
1667           eformal = eformal->next;
1668         }
1669       else if (isym && iformal)
1670         {
1671           if (iformal->optional)
1672             formal_optional = true;
1673           iformal = iformal->next;
1674         }
1675       else if (isym)
1676         formal_optional = true;
1677
1678       if (pedantic && arg->expr != NULL
1679           && arg->expr->expr_type == EXPR_VARIABLE
1680           && arg->expr->symtree->n.sym->attr.optional
1681           && formal_optional
1682           && arg->expr->rank
1683           && (set_by_optional || arg->expr->rank != rank)
1684           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1685         {
1686           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1687                        "MISSING, it cannot be the actual argument of an "
1688                        "ELEMENTAL procedure unless there is a non-optional "
1689                        "argument with the same rank (12.4.1.5)",
1690                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1691           return FAILURE;
1692         }
1693     }
1694
1695   for (arg = arg0; arg; arg = arg->next)
1696     {
1697       if (arg->expr == NULL || arg->expr->rank == 0)
1698         continue;
1699
1700       /* Being elemental, the last upper bound of an assumed size array
1701          argument must be present.  */
1702       if (resolve_assumed_size_actual (arg->expr))
1703         return FAILURE;
1704
1705       /* Elemental procedure's array actual arguments must conform.  */
1706       if (e != NULL)
1707         {
1708           if (gfc_check_conformance (arg->expr, e,
1709                                      "elemental procedure") == FAILURE)
1710             return FAILURE;
1711         }
1712       else
1713         e = arg->expr;
1714     }
1715
1716   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1717      is an array, the intent inout/out variable needs to be also an array.  */
1718   if (rank > 0 && esym && expr == NULL)
1719     for (eformal = esym->formal, arg = arg0; arg && eformal;
1720          arg = arg->next, eformal = eformal->next)
1721       if ((eformal->sym->attr.intent == INTENT_OUT
1722            || eformal->sym->attr.intent == INTENT_INOUT)
1723           && arg->expr && arg->expr->rank == 0)
1724         {
1725           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1726                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1727                      "actual argument is an array", &arg->expr->where,
1728                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1729                      : "INOUT", eformal->sym->name, esym->name);
1730           return FAILURE;
1731         }
1732   return SUCCESS;
1733 }
1734
1735
1736 /* Go through each actual argument in ACTUAL and see if it can be
1737    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1738    function being called, or NULL if not known.  */
1739
1740 static void
1741 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1742 {
1743   gfc_actual_arglist *ap;
1744   gfc_expr *expr;
1745
1746   for (ap = actual; ap; ap = ap->next)
1747     if (ap->expr
1748         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1749         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1750                                          NOT_ELEMENTAL))
1751       ap->expr->inline_noncopying_intrinsic = 1;
1752 }
1753
1754
1755 /* This function does the checking of references to global procedures
1756    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1757    77 and 95 standards.  It checks for a gsymbol for the name, making
1758    one if it does not already exist.  If it already exists, then the
1759    reference being resolved must correspond to the type of gsymbol.
1760    Otherwise, the new symbol is equipped with the attributes of the
1761    reference.  The corresponding code that is called in creating
1762    global entities is parse.c.
1763
1764    In addition, for all but -std=legacy, the gsymbols are used to
1765    check the interfaces of external procedures from the same file.
1766    The namespace of the gsymbol is resolved and then, once this is
1767    done the interface is checked.  */
1768
1769
1770 static bool
1771 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1772 {
1773   if (!gsym_ns->proc_name->attr.recursive)
1774     return true;
1775
1776   if (sym->ns == gsym_ns)
1777     return false;
1778
1779   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1780     return false;
1781
1782   return true;
1783 }
1784
1785 static bool
1786 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1787 {
1788   if (gsym_ns->entries)
1789     {
1790       gfc_entry_list *entry = gsym_ns->entries;
1791
1792       for (; entry; entry = entry->next)
1793         {
1794           if (strcmp (sym->name, entry->sym->name) == 0)
1795             {
1796               if (strcmp (gsym_ns->proc_name->name,
1797                           sym->ns->proc_name->name) == 0)
1798                 return false;
1799
1800               if (sym->ns->parent
1801                   && strcmp (gsym_ns->proc_name->name,
1802                              sym->ns->parent->proc_name->name) == 0)
1803                 return false;
1804             }
1805         }
1806     }
1807   return true;
1808 }
1809
1810 static void
1811 resolve_global_procedure (gfc_symbol *sym, locus *where,
1812                           gfc_actual_arglist **actual, int sub)
1813 {
1814   gfc_gsymbol * gsym;
1815   gfc_namespace *ns;
1816   enum gfc_symbol_type type;
1817
1818   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1819
1820   gsym = gfc_get_gsymbol (sym->name);
1821
1822   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1823     gfc_global_used (gsym, where);
1824
1825   if (gfc_option.flag_whole_file
1826         && sym->attr.if_source == IFSRC_UNKNOWN
1827         && gsym->type != GSYM_UNKNOWN
1828         && gsym->ns
1829         && gsym->ns->resolved != -1
1830         && gsym->ns->proc_name
1831         && not_in_recursive (sym, gsym->ns)
1832         && not_entry_self_reference (sym, gsym->ns))
1833     {
1834       /* Make sure that translation for the gsymbol occurs before
1835          the procedure currently being resolved.  */
1836       ns = gsym->ns->resolved ? NULL : gfc_global_ns_list;
1837       for (; ns && ns != gsym->ns; ns = ns->sibling)
1838         {
1839           if (ns->sibling == gsym->ns)
1840             {
1841               ns->sibling = gsym->ns->sibling;
1842               gsym->ns->sibling = gfc_global_ns_list;
1843               gfc_global_ns_list = gsym->ns;
1844               break;
1845             }
1846         }
1847
1848       if (!gsym->ns->resolved)
1849         {
1850           gfc_dt_list *old_dt_list;
1851
1852           /* Stash away derived types so that the backend_decls do not
1853              get mixed up.  */
1854           old_dt_list = gfc_derived_types;
1855           gfc_derived_types = NULL;
1856
1857           gfc_resolve (gsym->ns);
1858
1859           /* Store the new derived types with the global namespace.  */
1860           if (gfc_derived_types)
1861             gsym->ns->derived_types = gfc_derived_types;
1862
1863           /* Restore the derived types of this namespace.  */
1864           gfc_derived_types = old_dt_list;
1865         }
1866
1867       if (gsym->ns->proc_name->attr.function
1868             && gsym->ns->proc_name->as
1869             && gsym->ns->proc_name->as->rank
1870             && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1871         gfc_error ("The reference to function '%s' at %L either needs an "
1872                    "explicit INTERFACE or the rank is incorrect", sym->name,
1873                    where);
1874      
1875       /* Non-assumed length character functions.  */
1876       if (sym->attr.function && sym->ts.type == BT_CHARACTER
1877             && gsym->ns->proc_name->ts.u.cl != NULL
1878             && gsym->ns->proc_name->ts.u.cl->length != NULL)
1879         {
1880           gfc_charlen *cl = sym->ts.u.cl;
1881
1882           if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1883                 && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1884             {
1885               gfc_error ("Nonconstant character-length function '%s' at %L "
1886                          "must have an explicit interface", sym->name,
1887                          &sym->declared_at);
1888             }
1889         }
1890
1891       if (gfc_option.flag_whole_file == 1
1892             || ((gfc_option.warn_std & GFC_STD_LEGACY)
1893                   &&
1894                !(gfc_option.warn_std & GFC_STD_GNU)))
1895         gfc_errors_to_warnings (1);
1896
1897       gfc_procedure_use (gsym->ns->proc_name, actual, where);
1898
1899       gfc_errors_to_warnings (0);
1900     }
1901
1902   if (gsym->type == GSYM_UNKNOWN)
1903     {
1904       gsym->type = type;
1905       gsym->where = *where;
1906     }
1907
1908   gsym->used = 1;
1909 }
1910
1911
1912 /************* Function resolution *************/
1913
1914 /* Resolve a function call known to be generic.
1915    Section 14.1.2.4.1.  */
1916
1917 static match
1918 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1919 {
1920   gfc_symbol *s;
1921
1922   if (sym->attr.generic)
1923     {
1924       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1925       if (s != NULL)
1926         {
1927           expr->value.function.name = s->name;
1928           expr->value.function.esym = s;
1929
1930           if (s->ts.type != BT_UNKNOWN)
1931             expr->ts = s->ts;
1932           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1933             expr->ts = s->result->ts;
1934
1935           if (s->as != NULL)
1936             expr->rank = s->as->rank;
1937           else if (s->result != NULL && s->result->as != NULL)
1938             expr->rank = s->result->as->rank;
1939
1940           gfc_set_sym_referenced (expr->value.function.esym);
1941
1942           return MATCH_YES;
1943         }
1944
1945       /* TODO: Need to search for elemental references in generic
1946          interface.  */
1947     }
1948
1949   if (sym->attr.intrinsic)
1950     return gfc_intrinsic_func_interface (expr, 0);
1951
1952   return MATCH_NO;
1953 }
1954
1955
1956 static gfc_try
1957 resolve_generic_f (gfc_expr *expr)
1958 {
1959   gfc_symbol *sym;
1960   match m;
1961
1962   sym = expr->symtree->n.sym;
1963
1964   for (;;)
1965     {
1966       m = resolve_generic_f0 (expr, sym);
1967       if (m == MATCH_YES)
1968         return SUCCESS;
1969       else if (m == MATCH_ERROR)
1970         return FAILURE;
1971
1972 generic:
1973       if (sym->ns->parent == NULL)
1974         break;
1975       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1976
1977       if (sym == NULL)
1978         break;
1979       if (!generic_sym (sym))
1980         goto generic;
1981     }
1982
1983   /* Last ditch attempt.  See if the reference is to an intrinsic
1984      that possesses a matching interface.  14.1.2.4  */
1985   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
1986     {
1987       gfc_error ("There is no specific function for the generic '%s' at %L",
1988                  expr->symtree->n.sym->name, &expr->where);
1989       return FAILURE;
1990     }
1991
1992   m = gfc_intrinsic_func_interface (expr, 0);
1993   if (m == MATCH_YES)
1994     return SUCCESS;
1995   if (m == MATCH_NO)
1996     gfc_error ("Generic function '%s' at %L is not consistent with a "
1997                "specific intrinsic interface", expr->symtree->n.sym->name,
1998                &expr->where);
1999
2000   return FAILURE;
2001 }
2002
2003
2004 /* Resolve a function call known to be specific.  */
2005
2006 static match
2007 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2008 {
2009   match m;
2010
2011   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2012     {
2013       if (sym->attr.dummy)
2014         {
2015           sym->attr.proc = PROC_DUMMY;
2016           goto found;
2017         }
2018
2019       sym->attr.proc = PROC_EXTERNAL;
2020       goto found;
2021     }
2022
2023   if (sym->attr.proc == PROC_MODULE
2024       || sym->attr.proc == PROC_ST_FUNCTION
2025       || sym->attr.proc == PROC_INTERNAL)
2026     goto found;
2027
2028   if (sym->attr.intrinsic)
2029     {
2030       m = gfc_intrinsic_func_interface (expr, 1);
2031       if (m == MATCH_YES)
2032         return MATCH_YES;
2033       if (m == MATCH_NO)
2034         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2035                    "with an intrinsic", sym->name, &expr->where);
2036
2037       return MATCH_ERROR;
2038     }
2039
2040   return MATCH_NO;
2041
2042 found:
2043   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2044
2045   if (sym->result)
2046     expr->ts = sym->result->ts;
2047   else
2048     expr->ts = sym->ts;
2049   expr->value.function.name = sym->name;
2050   expr->value.function.esym = sym;
2051   if (sym->as != NULL)
2052     expr->rank = sym->as->rank;
2053
2054   return MATCH_YES;
2055 }
2056
2057
2058 static gfc_try
2059 resolve_specific_f (gfc_expr *expr)
2060 {
2061   gfc_symbol *sym;
2062   match m;
2063
2064   sym = expr->symtree->n.sym;
2065
2066   for (;;)
2067     {
2068       m = resolve_specific_f0 (sym, expr);
2069       if (m == MATCH_YES)
2070         return SUCCESS;
2071       if (m == MATCH_ERROR)
2072         return FAILURE;
2073
2074       if (sym->ns->parent == NULL)
2075         break;
2076
2077       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2078
2079       if (sym == NULL)
2080         break;
2081     }
2082
2083   gfc_error ("Unable to resolve the specific function '%s' at %L",
2084              expr->symtree->n.sym->name, &expr->where);
2085
2086   return SUCCESS;
2087 }
2088
2089
2090 /* Resolve a procedure call not known to be generic nor specific.  */
2091
2092 static gfc_try
2093 resolve_unknown_f (gfc_expr *expr)
2094 {
2095   gfc_symbol *sym;
2096   gfc_typespec *ts;
2097
2098   sym = expr->symtree->n.sym;
2099
2100   if (sym->attr.dummy)
2101     {
2102       sym->attr.proc = PROC_DUMMY;
2103       expr->value.function.name = sym->name;
2104       goto set_type;
2105     }
2106
2107   /* See if we have an intrinsic function reference.  */
2108
2109   if (gfc_is_intrinsic (sym, 0, expr->where))
2110     {
2111       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2112         return SUCCESS;
2113       return FAILURE;
2114     }
2115
2116   /* The reference is to an external name.  */
2117
2118   sym->attr.proc = PROC_EXTERNAL;
2119   expr->value.function.name = sym->name;
2120   expr->value.function.esym = expr->symtree->n.sym;
2121
2122   if (sym->as != NULL)
2123     expr->rank = sym->as->rank;
2124
2125   /* Type of the expression is either the type of the symbol or the
2126      default type of the symbol.  */
2127
2128 set_type:
2129   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2130
2131   if (sym->ts.type != BT_UNKNOWN)
2132     expr->ts = sym->ts;
2133   else
2134     {
2135       ts = gfc_get_default_type (sym->name, sym->ns);
2136
2137       if (ts->type == BT_UNKNOWN)
2138         {
2139           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2140                      sym->name, &expr->where);
2141           return FAILURE;
2142         }
2143       else
2144         expr->ts = *ts;
2145     }
2146
2147   return SUCCESS;
2148 }
2149
2150
2151 /* Return true, if the symbol is an external procedure.  */
2152 static bool
2153 is_external_proc (gfc_symbol *sym)
2154 {
2155   if (!sym->attr.dummy && !sym->attr.contained
2156         && !(sym->attr.intrinsic
2157               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2158         && sym->attr.proc != PROC_ST_FUNCTION
2159         && !sym->attr.use_assoc
2160         && sym->name)
2161     return true;
2162
2163   return false;
2164 }
2165
2166
2167 /* Figure out if a function reference is pure or not.  Also set the name
2168    of the function for a potential error message.  Return nonzero if the
2169    function is PURE, zero if not.  */
2170 static int
2171 pure_stmt_function (gfc_expr *, gfc_symbol *);
2172
2173 static int
2174 pure_function (gfc_expr *e, const char **name)
2175 {
2176   int pure;
2177
2178   *name = NULL;
2179
2180   if (e->symtree != NULL
2181         && e->symtree->n.sym != NULL
2182         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2183     return pure_stmt_function (e, e->symtree->n.sym);
2184
2185   if (e->value.function.esym)
2186     {
2187       pure = gfc_pure (e->value.function.esym);
2188       *name = e->value.function.esym->name;
2189     }
2190   else if (e->value.function.isym)
2191     {
2192       pure = e->value.function.isym->pure
2193              || e->value.function.isym->elemental;
2194       *name = e->value.function.isym->name;
2195     }
2196   else
2197     {
2198       /* Implicit functions are not pure.  */
2199       pure = 0;
2200       *name = e->value.function.name;
2201     }
2202
2203   return pure;
2204 }
2205
2206
2207 static bool
2208 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2209                  int *f ATTRIBUTE_UNUSED)
2210 {
2211   const char *name;
2212
2213   /* Don't bother recursing into other statement functions
2214      since they will be checked individually for purity.  */
2215   if (e->expr_type != EXPR_FUNCTION
2216         || !e->symtree
2217         || e->symtree->n.sym == sym
2218         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2219     return false;
2220
2221   return pure_function (e, &name) ? false : true;
2222 }
2223
2224
2225 static int
2226 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2227 {
2228   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2229 }
2230
2231
2232 static gfc_try
2233 is_scalar_expr_ptr (gfc_expr *expr)
2234 {
2235   gfc_try retval = SUCCESS;
2236   gfc_ref *ref;
2237   int start;
2238   int end;
2239
2240   /* See if we have a gfc_ref, which means we have a substring, array
2241      reference, or a component.  */
2242   if (expr->ref != NULL)
2243     {
2244       ref = expr->ref;
2245       while (ref->next != NULL)
2246         ref = ref->next;
2247
2248       switch (ref->type)
2249         {
2250         case REF_SUBSTRING:
2251           if (ref->u.ss.length != NULL 
2252               && ref->u.ss.length->length != NULL
2253               && ref->u.ss.start
2254               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2255               && ref->u.ss.end
2256               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2257             {
2258               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2259               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2260               if (end - start + 1 != 1)
2261                 retval = FAILURE;
2262             }
2263           else
2264             retval = FAILURE;
2265           break;
2266         case REF_ARRAY:
2267           if (ref->u.ar.type == AR_ELEMENT)
2268             retval = SUCCESS;
2269           else if (ref->u.ar.type == AR_FULL)
2270             {
2271               /* The user can give a full array if the array is of size 1.  */
2272               if (ref->u.ar.as != NULL
2273                   && ref->u.ar.as->rank == 1
2274                   && ref->u.ar.as->type == AS_EXPLICIT
2275                   && ref->u.ar.as->lower[0] != NULL
2276                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2277                   && ref->u.ar.as->upper[0] != NULL
2278                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2279                 {
2280                   /* If we have a character string, we need to check if
2281                      its length is one.  */
2282                   if (expr->ts.type == BT_CHARACTER)
2283                     {
2284                       if (expr->ts.u.cl == NULL
2285                           || expr->ts.u.cl->length == NULL
2286                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2287                           != 0)
2288                         retval = FAILURE;
2289                     }
2290                   else
2291                     {
2292                       /* We have constant lower and upper bounds.  If the
2293                          difference between is 1, it can be considered a
2294                          scalar.  */
2295                       start = (int) mpz_get_si
2296                                 (ref->u.ar.as->lower[0]->value.integer);
2297                       end = (int) mpz_get_si
2298                                 (ref->u.ar.as->upper[0]->value.integer);
2299                       if (end - start + 1 != 1)
2300                         retval = FAILURE;
2301                    }
2302                 }
2303               else
2304                 retval = FAILURE;
2305             }
2306           else
2307             retval = FAILURE;
2308           break;
2309         default:
2310           retval = SUCCESS;
2311           break;
2312         }
2313     }
2314   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2315     {
2316       /* Character string.  Make sure it's of length 1.  */
2317       if (expr->ts.u.cl == NULL
2318           || expr->ts.u.cl->length == NULL
2319           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2320         retval = FAILURE;
2321     }
2322   else if (expr->rank != 0)
2323     retval = FAILURE;
2324
2325   return retval;
2326 }
2327
2328
2329 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2330    and, in the case of c_associated, set the binding label based on
2331    the arguments.  */
2332
2333 static gfc_try
2334 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2335                           gfc_symbol **new_sym)
2336 {
2337   char name[GFC_MAX_SYMBOL_LEN + 1];
2338   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2339   int optional_arg = 0, is_pointer = 0;
2340   gfc_try retval = SUCCESS;
2341   gfc_symbol *args_sym;
2342   gfc_typespec *arg_ts;
2343
2344   if (args->expr->expr_type == EXPR_CONSTANT
2345       || args->expr->expr_type == EXPR_OP
2346       || args->expr->expr_type == EXPR_NULL)
2347     {
2348       gfc_error ("Argument to '%s' at %L is not a variable",
2349                  sym->name, &(args->expr->where));
2350       return FAILURE;
2351     }
2352
2353   args_sym = args->expr->symtree->n.sym;
2354
2355   /* The typespec for the actual arg should be that stored in the expr
2356      and not necessarily that of the expr symbol (args_sym), because
2357      the actual expression could be a part-ref of the expr symbol.  */
2358   arg_ts = &(args->expr->ts);
2359
2360   is_pointer = gfc_is_data_pointer (args->expr);
2361     
2362   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2363     {
2364       /* If the user gave two args then they are providing something for
2365          the optional arg (the second cptr).  Therefore, set the name and
2366          binding label to the c_associated for two cptrs.  Otherwise,
2367          set c_associated to expect one cptr.  */
2368       if (args->next)
2369         {
2370           /* two args.  */
2371           sprintf (name, "%s_2", sym->name);
2372           sprintf (binding_label, "%s_2", sym->binding_label);
2373           optional_arg = 1;
2374         }
2375       else
2376         {
2377           /* one arg.  */
2378           sprintf (name, "%s_1", sym->name);
2379           sprintf (binding_label, "%s_1", sym->binding_label);
2380           optional_arg = 0;
2381         }
2382
2383       /* Get a new symbol for the version of c_associated that
2384          will get called.  */
2385       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2386     }
2387   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2388            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2389     {
2390       sprintf (name, "%s", sym->name);
2391       sprintf (binding_label, "%s", sym->binding_label);
2392
2393       /* Error check the call.  */
2394       if (args->next != NULL)
2395         {
2396           gfc_error_now ("More actual than formal arguments in '%s' "
2397                          "call at %L", name, &(args->expr->where));
2398           retval = FAILURE;
2399         }
2400       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2401         {
2402           /* Make sure we have either the target or pointer attribute.  */
2403           if (!args_sym->attr.target && !is_pointer)
2404             {
2405               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2406                              "a TARGET or an associated pointer",
2407                              args_sym->name,
2408                              sym->name, &(args->expr->where));
2409               retval = FAILURE;
2410             }
2411
2412           /* See if we have interoperable type and type param.  */
2413           if (verify_c_interop (arg_ts) == SUCCESS
2414               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2415             {
2416               if (args_sym->attr.target == 1)
2417                 {
2418                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2419                      has the target attribute and is interoperable.  */
2420                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2421                      allocatable variable that has the TARGET attribute and
2422                      is not an array of zero size.  */
2423                   if (args_sym->attr.allocatable == 1)
2424                     {
2425                       if (args_sym->attr.dimension != 0 
2426                           && (args_sym->as && args_sym->as->rank == 0))
2427                         {
2428                           gfc_error_now ("Allocatable variable '%s' used as a "
2429                                          "parameter to '%s' at %L must not be "
2430                                          "an array of zero size",
2431                                          args_sym->name, sym->name,
2432                                          &(args->expr->where));
2433                           retval = FAILURE;
2434                         }
2435                     }
2436                   else
2437                     {
2438                       /* A non-allocatable target variable with C
2439                          interoperable type and type parameters must be
2440                          interoperable.  */
2441                       if (args_sym && args_sym->attr.dimension)
2442                         {
2443                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2444                             {
2445                               gfc_error ("Assumed-shape array '%s' at %L "
2446                                          "cannot be an argument to the "
2447                                          "procedure '%s' because "
2448                                          "it is not C interoperable",
2449                                          args_sym->name,
2450                                          &(args->expr->where), sym->name);
2451                               retval = FAILURE;
2452                             }
2453                           else if (args_sym->as->type == AS_DEFERRED)
2454                             {
2455                               gfc_error ("Deferred-shape array '%s' at %L "
2456                                          "cannot be an argument to the "
2457                                          "procedure '%s' because "
2458                                          "it is not C interoperable",
2459                                          args_sym->name,
2460                                          &(args->expr->where), sym->name);
2461                               retval = FAILURE;
2462                             }
2463                         }
2464                               
2465                       /* Make sure it's not a character string.  Arrays of
2466                          any type should be ok if the variable is of a C
2467                          interoperable type.  */
2468                       if (arg_ts->type == BT_CHARACTER)
2469                         if (arg_ts->u.cl != NULL
2470                             && (arg_ts->u.cl->length == NULL
2471                                 || arg_ts->u.cl->length->expr_type
2472                                    != EXPR_CONSTANT
2473                                 || mpz_cmp_si
2474                                     (arg_ts->u.cl->length->value.integer, 1)
2475                                    != 0)
2476                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2477                           {
2478                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2479                                            "at %L must have a length of 1",
2480                                            args_sym->name, sym->name,
2481                                            &(args->expr->where));
2482                             retval = FAILURE;
2483                           }
2484                     }
2485                 }
2486               else if (is_pointer
2487                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2488                 {
2489                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2490                      scalar pointer.  */
2491                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2492                                  "associated scalar POINTER", args_sym->name,
2493                                  sym->name, &(args->expr->where));
2494                   retval = FAILURE;
2495                 }
2496             }
2497           else
2498             {
2499               /* The parameter is not required to be C interoperable.  If it
2500                  is not C interoperable, it must be a nonpolymorphic scalar
2501                  with no length type parameters.  It still must have either
2502                  the pointer or target attribute, and it can be
2503                  allocatable (but must be allocated when c_loc is called).  */
2504               if (args->expr->rank != 0 
2505                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2506                 {
2507                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2508                                  "scalar", args_sym->name, sym->name,
2509                                  &(args->expr->where));
2510                   retval = FAILURE;
2511                 }
2512               else if (arg_ts->type == BT_CHARACTER 
2513                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2514                 {
2515                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2516                                  "%L must have a length of 1",
2517                                  args_sym->name, sym->name,
2518                                  &(args->expr->where));
2519                   retval = FAILURE;
2520                 }
2521             }
2522         }
2523       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2524         {
2525           if (args_sym->attr.flavor != FL_PROCEDURE)
2526             {
2527               /* TODO: Update this error message to allow for procedure
2528                  pointers once they are implemented.  */
2529               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2530                              "procedure",
2531                              args_sym->name, sym->name,
2532                              &(args->expr->where));
2533               retval = FAILURE;
2534             }
2535           else if (args_sym->attr.is_bind_c != 1)
2536             {
2537               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2538                              "BIND(C)",
2539                              args_sym->name, sym->name,
2540                              &(args->expr->where));
2541               retval = FAILURE;
2542             }
2543         }
2544       
2545       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2546       *new_sym = sym;
2547     }
2548   else
2549     {
2550       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2551                           "iso_c_binding function: '%s'!\n", sym->name);
2552     }
2553
2554   return retval;
2555 }
2556
2557
2558 /* Resolve a function call, which means resolving the arguments, then figuring
2559    out which entity the name refers to.  */
2560 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2561    to INTENT(OUT) or INTENT(INOUT).  */
2562
2563 static gfc_try
2564 resolve_function (gfc_expr *expr)
2565 {
2566   gfc_actual_arglist *arg;
2567   gfc_symbol *sym;
2568   const char *name;
2569   gfc_try t;
2570   int temp;
2571   procedure_type p = PROC_INTRINSIC;
2572   bool no_formal_args;
2573
2574   sym = NULL;
2575   if (expr->symtree)
2576     sym = expr->symtree->n.sym;
2577
2578   /* If this is a procedure pointer component, it has already been resolved.  */
2579   if (gfc_is_proc_ptr_comp (expr, NULL))
2580     return SUCCESS;
2581   
2582   if (sym && sym->attr.intrinsic
2583       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2584     return FAILURE;
2585
2586   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2587     {
2588       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2589       return FAILURE;
2590     }
2591
2592   /* If this ia a deferred TBP with an abstract interface (which may
2593      of course be referenced), expr->value.function.esym will be set.  */
2594   if (sym && sym->attr.abstract && !expr->value.function.esym)
2595     {
2596       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2597                  sym->name, &expr->where);
2598       return FAILURE;
2599     }
2600
2601   /* Switch off assumed size checking and do this again for certain kinds
2602      of procedure, once the procedure itself is resolved.  */
2603   need_full_assumed_size++;
2604
2605   if (expr->symtree && expr->symtree->n.sym)
2606     p = expr->symtree->n.sym->attr.proc;
2607
2608   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2609     inquiry_argument = true;
2610   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2611
2612   if (resolve_actual_arglist (expr->value.function.actual,
2613                               p, no_formal_args) == FAILURE)
2614     {
2615       inquiry_argument = false;
2616       return FAILURE;
2617     }
2618
2619   inquiry_argument = false;
2620  
2621   /* Need to setup the call to the correct c_associated, depending on
2622      the number of cptrs to user gives to compare.  */
2623   if (sym && sym->attr.is_iso_c == 1)
2624     {
2625       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2626           == FAILURE)
2627         return FAILURE;
2628       
2629       /* Get the symtree for the new symbol (resolved func).
2630          the old one will be freed later, when it's no longer used.  */
2631       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2632     }
2633   
2634   /* Resume assumed_size checking.  */
2635   need_full_assumed_size--;
2636
2637   /* If the procedure is external, check for usage.  */
2638   if (sym && is_external_proc (sym))
2639     resolve_global_procedure (sym, &expr->where,
2640                               &expr->value.function.actual, 0);
2641
2642   if (sym && sym->ts.type == BT_CHARACTER
2643       && sym->ts.u.cl
2644       && sym->ts.u.cl->length == NULL
2645       && !sym->attr.dummy
2646       && expr->value.function.esym == NULL
2647       && !sym->attr.contained)
2648     {
2649       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2650       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2651                  "be used at %L since it is not a dummy argument",
2652                  sym->name, &expr->where);
2653       return FAILURE;
2654     }
2655
2656   /* See if function is already resolved.  */
2657
2658   if (expr->value.function.name != NULL)
2659     {
2660       if (expr->ts.type == BT_UNKNOWN)
2661         expr->ts = sym->ts;
2662       t = SUCCESS;
2663     }
2664   else
2665     {
2666       /* Apply the rules of section 14.1.2.  */
2667
2668       switch (procedure_kind (sym))
2669         {
2670         case PTYPE_GENERIC:
2671           t = resolve_generic_f (expr);
2672           break;
2673
2674         case PTYPE_SPECIFIC:
2675           t = resolve_specific_f (expr);
2676           break;
2677
2678         case PTYPE_UNKNOWN:
2679           t = resolve_unknown_f (expr);
2680           break;
2681
2682         default:
2683           gfc_internal_error ("resolve_function(): bad function type");
2684         }
2685     }
2686
2687   /* If the expression is still a function (it might have simplified),
2688      then we check to see if we are calling an elemental function.  */
2689
2690   if (expr->expr_type != EXPR_FUNCTION)
2691     return t;
2692
2693   temp = need_full_assumed_size;
2694   need_full_assumed_size = 0;
2695
2696   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2697     return FAILURE;
2698
2699   if (omp_workshare_flag
2700       && expr->value.function.esym
2701       && ! gfc_elemental (expr->value.function.esym))
2702     {
2703       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2704                  "in WORKSHARE construct", expr->value.function.esym->name,
2705                  &expr->where);
2706       t = FAILURE;
2707     }
2708
2709 #define GENERIC_ID expr->value.function.isym->id
2710   else if (expr->value.function.actual != NULL
2711            && expr->value.function.isym != NULL
2712            && GENERIC_ID != GFC_ISYM_LBOUND
2713            && GENERIC_ID != GFC_ISYM_LEN
2714            && GENERIC_ID != GFC_ISYM_LOC
2715            && GENERIC_ID != GFC_ISYM_PRESENT)
2716     {
2717       /* Array intrinsics must also have the last upper bound of an
2718          assumed size array argument.  UBOUND and SIZE have to be
2719          excluded from the check if the second argument is anything
2720          than a constant.  */
2721
2722       for (arg = expr->value.function.actual; arg; arg = arg->next)
2723         {
2724           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2725               && arg->next != NULL && arg->next->expr)
2726             {
2727               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2728                 break;
2729
2730               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2731                 break;
2732
2733               if ((int)mpz_get_si (arg->next->expr->value.integer)
2734                         < arg->expr->rank)
2735                 break;
2736             }
2737
2738           if (arg->expr != NULL
2739               && arg->expr->rank > 0
2740               && resolve_assumed_size_actual (arg->expr))
2741             return FAILURE;
2742         }
2743     }
2744 #undef GENERIC_ID
2745
2746   need_full_assumed_size = temp;
2747   name = NULL;
2748
2749   if (!pure_function (expr, &name) && name)
2750     {
2751       if (forall_flag)
2752         {
2753           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2754                      "FORALL %s", name, &expr->where,
2755                      forall_flag == 2 ? "mask" : "block");
2756           t = FAILURE;
2757         }
2758       else if (gfc_pure (NULL))
2759         {
2760           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2761                      "procedure within a PURE procedure", name, &expr->where);
2762           t = FAILURE;
2763         }
2764     }
2765
2766   /* Functions without the RECURSIVE attribution are not allowed to
2767    * call themselves.  */
2768   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2769     {
2770       gfc_symbol *esym;
2771       esym = expr->value.function.esym;
2772
2773       if (is_illegal_recursion (esym, gfc_current_ns))
2774       {
2775         if (esym->attr.entry && esym->ns->entries)
2776           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2777                      " function '%s' is not RECURSIVE",
2778                      esym->name, &expr->where, esym->ns->entries->sym->name);
2779         else
2780           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2781                      " is not RECURSIVE", esym->name, &expr->where);
2782
2783         t = FAILURE;
2784       }
2785     }
2786
2787   /* Character lengths of use associated functions may contains references to
2788      symbols not referenced from the current program unit otherwise.  Make sure
2789      those symbols are marked as referenced.  */
2790
2791   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2792       && expr->value.function.esym->attr.use_assoc)
2793     {
2794       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2795     }
2796
2797   if (t == SUCCESS
2798         && !((expr->value.function.esym
2799                 && expr->value.function.esym->attr.elemental)
2800                         ||
2801              (expr->value.function.isym
2802                 && expr->value.function.isym->elemental)))
2803     find_noncopying_intrinsics (expr->value.function.esym,
2804                                 expr->value.function.actual);
2805
2806   /* Make sure that the expression has a typespec that works.  */
2807   if (expr->ts.type == BT_UNKNOWN)
2808     {
2809       if (expr->symtree->n.sym->result
2810             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2811             && !expr->symtree->n.sym->result->attr.proc_pointer)
2812         expr->ts = expr->symtree->n.sym->result->ts;
2813     }
2814
2815   return t;
2816 }
2817
2818
2819 /************* Subroutine resolution *************/
2820
2821 static void
2822 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2823 {
2824   if (gfc_pure (sym))
2825     return;
2826
2827   if (forall_flag)
2828     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2829                sym->name, &c->loc);
2830   else if (gfc_pure (NULL))
2831     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2832                &c->loc);
2833 }
2834
2835
2836 static match
2837 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2838 {
2839   gfc_symbol *s;
2840
2841   if (sym->attr.generic)
2842     {
2843       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2844       if (s != NULL)
2845         {
2846           c->resolved_sym = s;
2847           pure_subroutine (c, s);
2848           return MATCH_YES;
2849         }
2850
2851       /* TODO: Need to search for elemental references in generic interface.  */
2852     }
2853
2854   if (sym->attr.intrinsic)
2855     return gfc_intrinsic_sub_interface (c, 0);
2856
2857   return MATCH_NO;
2858 }
2859
2860
2861 static gfc_try
2862 resolve_generic_s (gfc_code *c)
2863 {
2864   gfc_symbol *sym;
2865   match m;
2866
2867   sym = c->symtree->n.sym;
2868
2869   for (;;)
2870     {
2871       m = resolve_generic_s0 (c, sym);
2872       if (m == MATCH_YES)
2873         return SUCCESS;
2874       else if (m == MATCH_ERROR)
2875         return FAILURE;
2876
2877 generic:
2878       if (sym->ns->parent == NULL)
2879         break;
2880       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2881
2882       if (sym == NULL)
2883         break;
2884       if (!generic_sym (sym))
2885         goto generic;
2886     }
2887
2888   /* Last ditch attempt.  See if the reference is to an intrinsic
2889      that possesses a matching interface.  14.1.2.4  */
2890   sym = c->symtree->n.sym;
2891
2892   if (!gfc_is_intrinsic (sym, 1, c->loc))
2893     {
2894       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2895                  sym->name, &c->loc);
2896       return FAILURE;
2897     }
2898
2899   m = gfc_intrinsic_sub_interface (c, 0);
2900   if (m == MATCH_YES)
2901     return SUCCESS;
2902   if (m == MATCH_NO)
2903     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2904                "intrinsic subroutine interface", sym->name, &c->loc);
2905
2906   return FAILURE;
2907 }
2908
2909
2910 /* Set the name and binding label of the subroutine symbol in the call
2911    expression represented by 'c' to include the type and kind of the
2912    second parameter.  This function is for resolving the appropriate
2913    version of c_f_pointer() and c_f_procpointer().  For example, a
2914    call to c_f_pointer() for a default integer pointer could have a
2915    name of c_f_pointer_i4.  If no second arg exists, which is an error
2916    for these two functions, it defaults to the generic symbol's name
2917    and binding label.  */
2918
2919 static void
2920 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2921                     char *name, char *binding_label)
2922 {
2923   gfc_expr *arg = NULL;
2924   char type;
2925   int kind;
2926
2927   /* The second arg of c_f_pointer and c_f_procpointer determines
2928      the type and kind for the procedure name.  */
2929   arg = c->ext.actual->next->expr;
2930
2931   if (arg != NULL)
2932     {
2933       /* Set up the name to have the given symbol's name,
2934          plus the type and kind.  */
2935       /* a derived type is marked with the type letter 'u' */
2936       if (arg->ts.type == BT_DERIVED)
2937         {
2938           type = 'd';
2939           kind = 0; /* set the kind as 0 for now */
2940         }
2941       else
2942         {
2943           type = gfc_type_letter (arg->ts.type);
2944           kind = arg->ts.kind;
2945         }
2946
2947       if (arg->ts.type == BT_CHARACTER)
2948         /* Kind info for character strings not needed.  */
2949         kind = 0;
2950
2951       sprintf (name, "%s_%c%d", sym->name, type, kind);
2952       /* Set up the binding label as the given symbol's label plus
2953          the type and kind.  */
2954       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2955     }
2956   else
2957     {
2958       /* If the second arg is missing, set the name and label as
2959          was, cause it should at least be found, and the missing
2960          arg error will be caught by compare_parameters().  */
2961       sprintf (name, "%s", sym->name);
2962       sprintf (binding_label, "%s", sym->binding_label);
2963     }
2964    
2965   return;
2966 }
2967
2968
2969 /* Resolve a generic version of the iso_c_binding procedure given
2970    (sym) to the specific one based on the type and kind of the
2971    argument(s).  Currently, this function resolves c_f_pointer() and
2972    c_f_procpointer based on the type and kind of the second argument
2973    (FPTR).  Other iso_c_binding procedures aren't specially handled.
2974    Upon successfully exiting, c->resolved_sym will hold the resolved
2975    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
2976    otherwise.  */
2977
2978 match
2979 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2980 {
2981   gfc_symbol *new_sym;
2982   /* this is fine, since we know the names won't use the max */
2983   char name[GFC_MAX_SYMBOL_LEN + 1];
2984   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2985   /* default to success; will override if find error */
2986   match m = MATCH_YES;
2987
2988   /* Make sure the actual arguments are in the necessary order (based on the 
2989      formal args) before resolving.  */
2990   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2991
2992   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2993       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2994     {
2995       set_name_and_label (c, sym, name, binding_label);
2996       
2997       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2998         {
2999           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3000             {
3001               /* Make sure we got a third arg if the second arg has non-zero
3002                  rank.  We must also check that the type and rank are
3003                  correct since we short-circuit this check in
3004                  gfc_procedure_use() (called above to sort actual args).  */
3005               if (c->ext.actual->next->expr->rank != 0)
3006                 {
3007                   if(c->ext.actual->next->next == NULL 
3008                      || c->ext.actual->next->next->expr == NULL)
3009                     {
3010                       m = MATCH_ERROR;
3011                       gfc_error ("Missing SHAPE parameter for call to %s "
3012                                  "at %L", sym->name, &(c->loc));
3013                     }
3014                   else if (c->ext.actual->next->next->expr->ts.type
3015                            != BT_INTEGER
3016                            || c->ext.actual->next->next->expr->rank != 1)
3017                     {
3018                       m = MATCH_ERROR;
3019                       gfc_error ("SHAPE parameter for call to %s at %L must "
3020                                  "be a rank 1 INTEGER array", sym->name,
3021                                  &(c->loc));
3022                     }
3023                 }
3024             }
3025         }
3026       
3027       if (m != MATCH_ERROR)
3028         {
3029           /* the 1 means to add the optional arg to formal list */
3030           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3031          
3032           /* for error reporting, say it's declared where the original was */
3033           new_sym->declared_at = sym->declared_at;
3034         }
3035     }
3036   else
3037     {
3038       /* no differences for c_loc or c_funloc */
3039       new_sym = sym;
3040     }
3041
3042   /* set the resolved symbol */
3043   if (m != MATCH_ERROR)
3044     c->resolved_sym = new_sym;
3045   else
3046     c->resolved_sym = sym;
3047   
3048   return m;
3049 }
3050
3051
3052 /* Resolve a subroutine call known to be specific.  */
3053
3054 static match
3055 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3056 {
3057   match m;
3058
3059   if(sym->attr.is_iso_c)
3060     {
3061       m = gfc_iso_c_sub_interface (c,sym);
3062       return m;
3063     }
3064   
3065   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3066     {
3067       if (sym->attr.dummy)
3068         {
3069           sym->attr.proc = PROC_DUMMY;
3070           goto found;
3071         }
3072
3073       sym->attr.proc = PROC_EXTERNAL;
3074       goto found;
3075     }
3076
3077   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3078     goto found;
3079
3080   if (sym->attr.intrinsic)
3081     {
3082       m = gfc_intrinsic_sub_interface (c, 1);
3083       if (m == MATCH_YES)
3084         return MATCH_YES;
3085       if (m == MATCH_NO)
3086         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3087                    "with an intrinsic", sym->name, &c->loc);
3088
3089       return MATCH_ERROR;
3090     }
3091
3092   return MATCH_NO;
3093
3094 found:
3095   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3096
3097   c->resolved_sym = sym;
3098   pure_subroutine (c, sym);
3099
3100   return MATCH_YES;
3101 }
3102
3103
3104 static gfc_try
3105 resolve_specific_s (gfc_code *c)
3106 {
3107   gfc_symbol *sym;
3108   match m;
3109
3110   sym = c->symtree->n.sym;
3111
3112   for (;;)
3113     {
3114       m = resolve_specific_s0 (c, sym);
3115       if (m == MATCH_YES)
3116         return SUCCESS;
3117       if (m == MATCH_ERROR)
3118         return FAILURE;
3119
3120       if (sym->ns->parent == NULL)
3121         break;
3122
3123       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3124
3125       if (sym == NULL)
3126         break;
3127     }
3128
3129   sym = c->symtree->n.sym;
3130   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3131              sym->name, &c->loc);
3132
3133   return FAILURE;
3134 }
3135
3136
3137 /* Resolve a subroutine call not known to be generic nor specific.  */
3138
3139 static gfc_try
3140 resolve_unknown_s (gfc_code *c)
3141 {
3142   gfc_symbol *sym;
3143
3144   sym = c->symtree->n.sym;
3145
3146   if (sym->attr.dummy)
3147     {
3148       sym->attr.proc = PROC_DUMMY;
3149       goto found;
3150     }
3151
3152   /* See if we have an intrinsic function reference.  */
3153
3154   if (gfc_is_intrinsic (sym, 1, c->loc))
3155     {
3156       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3157         return SUCCESS;
3158       return FAILURE;
3159     }
3160
3161   /* The reference is to an external name.  */
3162
3163 found:
3164   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3165
3166   c->resolved_sym = sym;
3167
3168   pure_subroutine (c, sym);
3169
3170   return SUCCESS;
3171 }
3172
3173
3174 /* Resolve a subroutine call.  Although it was tempting to use the same code
3175    for functions, subroutines and functions are stored differently and this
3176    makes things awkward.  */
3177
3178 static gfc_try
3179 resolve_call (gfc_code *c)
3180 {
3181   gfc_try t;
3182   procedure_type ptype = PROC_INTRINSIC;
3183   gfc_symbol *csym, *sym;
3184   bool no_formal_args;
3185
3186   csym = c->symtree ? c->symtree->n.sym : NULL;
3187
3188   if (csym && csym->ts.type != BT_UNKNOWN)
3189     {
3190       gfc_error ("'%s' at %L has a type, which is not consistent with "
3191                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3192       return FAILURE;
3193     }
3194
3195   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3196     {
3197       gfc_symtree *st;
3198       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3199       sym = st ? st->n.sym : NULL;
3200       if (sym && csym != sym
3201               && sym->ns == gfc_current_ns
3202               && sym->attr.flavor == FL_PROCEDURE
3203               && sym->attr.contained)
3204         {
3205           sym->refs++;
3206           if (csym->attr.generic)
3207             c->symtree->n.sym = sym;
3208           else
3209             c->symtree = st;
3210           csym = c->symtree->n.sym;
3211         }
3212     }
3213
3214   /* If this ia a deferred TBP with an abstract interface
3215      (which may of course be referenced), c->expr1 will be set.  */
3216   if (csym && csym->attr.abstract && !c->expr1)
3217     {
3218       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3219                  csym->name, &c->loc);
3220       return FAILURE;
3221     }
3222
3223   /* Subroutines without the RECURSIVE attribution are not allowed to
3224    * call themselves.  */
3225   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3226     {
3227       if (csym->attr.entry && csym->ns->entries)
3228         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3229                    " subroutine '%s' is not RECURSIVE",
3230                    csym->name, &c->loc, csym->ns->entries->sym->name);
3231       else
3232         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3233                    " is not RECURSIVE", csym->name, &c->loc);
3234
3235       t = FAILURE;
3236     }
3237
3238   /* Switch off assumed size checking and do this again for certain kinds
3239      of procedure, once the procedure itself is resolved.  */
3240   need_full_assumed_size++;
3241
3242   if (csym)
3243     ptype = csym->attr.proc;
3244
3245   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3246   if (resolve_actual_arglist (c->ext.actual, ptype,
3247                               no_formal_args) == FAILURE)
3248     return FAILURE;
3249
3250   /* Resume assumed_size checking.  */
3251   need_full_assumed_size--;
3252
3253   /* If external, check for usage.  */
3254   if (csym && is_external_proc (csym))
3255     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3256
3257   t = SUCCESS;
3258   if (c->resolved_sym == NULL)
3259     {
3260       c->resolved_isym = NULL;
3261       switch (procedure_kind (csym))
3262         {
3263         case PTYPE_GENERIC:
3264           t = resolve_generic_s (c);
3265           break;
3266
3267         case PTYPE_SPECIFIC:
3268           t = resolve_specific_s (c);
3269           break;
3270
3271         case PTYPE_UNKNOWN:
3272           t = resolve_unknown_s (c);
3273           break;
3274
3275         default:
3276           gfc_internal_error ("resolve_subroutine(): bad function type");
3277         }
3278     }
3279
3280   /* Some checks of elemental subroutine actual arguments.  */
3281   if (resolve_elemental_actual (NULL, c) == FAILURE)
3282     return FAILURE;
3283
3284   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3285     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3286   return t;
3287 }
3288
3289
3290 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3291    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3292    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3293    if their shapes do not match.  If either op1->shape or op2->shape is
3294    NULL, return SUCCESS.  */
3295
3296 static gfc_try
3297 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3298 {
3299   gfc_try t;
3300   int i;
3301
3302   t = SUCCESS;
3303
3304   if (op1->shape != NULL && op2->shape != NULL)
3305     {
3306       for (i = 0; i < op1->rank; i++)
3307         {
3308           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3309            {
3310              gfc_error ("Shapes for operands at %L and %L are not conformable",
3311                          &op1->where, &op2->where);
3312              t = FAILURE;
3313              break;
3314            }
3315         }
3316     }
3317
3318   return t;
3319 }
3320
3321
3322 /* Resolve an operator expression node.  This can involve replacing the
3323    operation with a user defined function call.  */
3324
3325 static gfc_try
3326 resolve_operator (gfc_expr *e)
3327 {
3328   gfc_expr *op1, *op2;
3329   char msg[200];
3330   bool dual_locus_error;
3331   gfc_try t;
3332
3333   /* Resolve all subnodes-- give them types.  */
3334
3335   switch (e->value.op.op)
3336     {
3337     default:
3338       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3339         return FAILURE;
3340
3341     /* Fall through...  */
3342
3343     case INTRINSIC_NOT:
3344     case INTRINSIC_UPLUS:
3345     case INTRINSIC_UMINUS:
3346     case INTRINSIC_PARENTHESES:
3347       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3348         return FAILURE;
3349       break;
3350     }
3351
3352   /* Typecheck the new node.  */
3353
3354   op1 = e->value.op.op1;
3355   op2 = e->value.op.op2;
3356   dual_locus_error = false;
3357
3358   if ((op1 && op1->expr_type == EXPR_NULL)
3359       || (op2 && op2->expr_type == EXPR_NULL))
3360     {
3361       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3362       goto bad_op;
3363     }
3364
3365   switch (e->value.op.op)
3366     {
3367     case INTRINSIC_UPLUS:
3368     case INTRINSIC_UMINUS:
3369       if (op1->ts.type == BT_INTEGER
3370           || op1->ts.type == BT_REAL
3371           || op1->ts.type == BT_COMPLEX)
3372         {
3373           e->ts = op1->ts;
3374           break;
3375         }
3376
3377       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3378                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3379       goto bad_op;
3380
3381     case INTRINSIC_PLUS:
3382     case INTRINSIC_MINUS:
3383     case INTRINSIC_TIMES:
3384     case INTRINSIC_DIVIDE:
3385     case INTRINSIC_POWER:
3386       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3387         {
3388           gfc_type_convert_binary (e, 1);
3389           break;
3390         }
3391
3392       sprintf (msg,
3393                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3394                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3395                gfc_typename (&op2->ts));
3396       goto bad_op;
3397
3398     case INTRINSIC_CONCAT:
3399       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3400           && op1->ts.kind == op2->ts.kind)
3401         {
3402           e->ts.type = BT_CHARACTER;
3403           e->ts.kind = op1->ts.kind;
3404           break;
3405         }
3406
3407       sprintf (msg,
3408                _("Operands of string concatenation operator at %%L are %s/%s"),
3409                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3410       goto bad_op;
3411
3412     case INTRINSIC_AND:
3413     case INTRINSIC_OR:
3414     case INTRINSIC_EQV:
3415     case INTRINSIC_NEQV:
3416       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3417         {
3418           e->ts.type = BT_LOGICAL;
3419           e->ts.kind = gfc_kind_max (op1, op2);
3420           if (op1->ts.kind < e->ts.kind)
3421             gfc_convert_type (op1, &e->ts, 2);
3422           else if (op2->ts.kind < e->ts.kind)
3423             gfc_convert_type (op2, &e->ts, 2);
3424           break;
3425         }
3426
3427       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3428                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3429                gfc_typename (&op2->ts));
3430
3431       goto bad_op;
3432
3433     case INTRINSIC_NOT:
3434       if (op1->ts.type == BT_LOGICAL)
3435         {
3436           e->ts.type = BT_LOGICAL;
3437           e->ts.kind = op1->ts.kind;
3438           break;
3439         }
3440
3441       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3442                gfc_typename (&op1->ts));
3443       goto bad_op;
3444
3445     case INTRINSIC_GT:
3446     case INTRINSIC_GT_OS:
3447     case INTRINSIC_GE:
3448     case INTRINSIC_GE_OS:
3449     case INTRINSIC_LT:
3450     case INTRINSIC_LT_OS:
3451     case INTRINSIC_LE:
3452     case INTRINSIC_LE_OS:
3453       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3454         {
3455           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3456           goto bad_op;
3457         }
3458
3459       /* Fall through...  */
3460
3461     case INTRINSIC_EQ:
3462     case INTRINSIC_EQ_OS:
3463     case INTRINSIC_NE:
3464     case INTRINSIC_NE_OS:
3465       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3466           && op1->ts.kind == op2->ts.kind)
3467         {
3468           e->ts.type = BT_LOGICAL;
3469           e->ts.kind = gfc_default_logical_kind;
3470           break;
3471         }
3472
3473       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3474         {
3475           gfc_type_convert_binary (e, 1);
3476
3477           e->ts.type = BT_LOGICAL;
3478           e->ts.kind = gfc_default_logical_kind;
3479           break;
3480         }
3481
3482       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3483         sprintf (msg,
3484                  _("Logicals at %%L must be compared with %s instead of %s"),
3485                  (e->value.op.op == INTRINSIC_EQ 
3486                   || e->value.op.op == INTRINSIC_EQ_OS)
3487                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3488       else
3489         sprintf (msg,
3490                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3491                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3492                  gfc_typename (&op2->ts));
3493
3494       goto bad_op;
3495
3496     case INTRINSIC_USER:
3497       if (e->value.op.uop->op == NULL)
3498         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3499       else if (op2 == NULL)
3500         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3501                  e->value.op.uop->name, gfc_typename (&op1->ts));
3502       else
3503         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3504                  e->value.op.uop->name, gfc_typename (&op1->ts),
3505                  gfc_typename (&op2->ts));
3506
3507       goto bad_op;
3508
3509     case INTRINSIC_PARENTHESES:
3510       e->ts = op1->ts;
3511       if (e->ts.type == BT_CHARACTER)
3512         e->ts.u.cl = op1->ts.u.cl;
3513       break;
3514
3515     default:
3516       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3517     }
3518
3519   /* Deal with arrayness of an operand through an operator.  */
3520
3521   t = SUCCESS;
3522
3523   switch (e->value.op.op)
3524     {
3525     case INTRINSIC_PLUS:
3526     case INTRINSIC_MINUS:
3527     case INTRINSIC_TIMES:
3528     case INTRINSIC_DIVIDE:
3529     case INTRINSIC_POWER:
3530     case INTRINSIC_CONCAT:
3531     case INTRINSIC_AND:
3532     case INTRINSIC_OR:
3533     case INTRINSIC_EQV:
3534     case INTRINSIC_NEQV:
3535     case INTRINSIC_EQ:
3536     case INTRINSIC_EQ_OS:
3537     case INTRINSIC_NE:
3538     case INTRINSIC_NE_OS:
3539     case INTRINSIC_GT:
3540     case INTRINSIC_GT_OS:
3541     case INTRINSIC_GE:
3542     case INTRINSIC_GE_OS:
3543     case INTRINSIC_LT:
3544     case INTRINSIC_LT_OS:
3545     case INTRINSIC_LE:
3546     case INTRINSIC_LE_OS:
3547
3548       if (op1->rank == 0 && op2->rank == 0)
3549         e->rank = 0;
3550
3551       if (op1->rank == 0 && op2->rank != 0)
3552         {
3553           e->rank = op2->rank;
3554
3555           if (e->shape == NULL)
3556             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3557         }
3558
3559       if (op1->rank != 0 && op2->rank == 0)
3560         {
3561           e->rank = op1->rank;
3562
3563           if (e->shape == NULL)
3564             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3565         }
3566
3567       if (op1->rank != 0 && op2->rank != 0)
3568         {
3569           if (op1->rank == op2->rank)
3570             {
3571               e->rank = op1->rank;
3572               if (e->shape == NULL)
3573                 {
3574                   t = compare_shapes(op1, op2);
3575                   if (t == FAILURE)
3576                     e->shape = NULL;
3577                   else
3578                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3579                 }
3580             }
3581           else
3582             {
3583               /* Allow higher level expressions to work.  */
3584               e->rank = 0;
3585
3586               /* Try user-defined operators, and otherwise throw an error.  */
3587               dual_locus_error = true;
3588               sprintf (msg,
3589                        _("Inconsistent ranks for operator at %%L and %%L"));
3590               goto bad_op;
3591             }
3592         }
3593
3594       break;
3595
3596     case INTRINSIC_PARENTHESES:
3597     case INTRINSIC_NOT:
3598     case INTRINSIC_UPLUS:
3599     case INTRINSIC_UMINUS:
3600       /* Simply copy arrayness attribute */
3601       e->rank = op1->rank;
3602
3603       if (e->shape == NULL)
3604         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3605
3606       break;
3607
3608     default:
3609       break;
3610     }
3611
3612   /* Attempt to simplify the expression.  */
3613   if (t == SUCCESS)
3614     {
3615       t = gfc_simplify_expr (e, 0);
3616       /* Some calls do not succeed in simplification and return FAILURE
3617          even though there is no error; e.g. variable references to
3618          PARAMETER arrays.  */
3619       if (!gfc_is_constant_expr (e))
3620         t = SUCCESS;
3621     }
3622   return t;
3623
3624 bad_op:
3625
3626   {
3627     bool real_error;
3628     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3629       return SUCCESS;
3630
3631     if (real_error)
3632       return FAILURE;
3633   }
3634
3635   if (dual_locus_error)
3636     gfc_error (msg, &op1->where, &op2->where);
3637   else
3638     gfc_error (msg, &e->where);
3639
3640   return FAILURE;
3641 }
3642
3643
3644 /************** Array resolution subroutines **************/
3645
3646 typedef enum
3647 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3648 comparison;
3649
3650 /* Compare two integer expressions.  */
3651
3652 static comparison
3653 compare_bound (gfc_expr *a, gfc_expr *b)
3654 {
3655   int i;
3656
3657   if (a == NULL || a->expr_type != EXPR_CONSTANT
3658       || b == NULL || b->expr_type != EXPR_CONSTANT)
3659     return CMP_UNKNOWN;
3660
3661   /* If either of the types isn't INTEGER, we must have
3662      raised an error earlier.  */
3663
3664   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3665     return CMP_UNKNOWN;
3666
3667   i = mpz_cmp (a->value.integer, b->value.integer);
3668
3669   if (i < 0)
3670     return CMP_LT;
3671   if (i > 0)
3672     return CMP_GT;
3673   return CMP_EQ;
3674 }
3675
3676
3677 /* Compare an integer expression with an integer.  */
3678
3679 static comparison
3680 compare_bound_int (gfc_expr *a, int b)
3681 {
3682   int i;
3683
3684   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3685     return CMP_UNKNOWN;
3686
3687   if (a->ts.type != BT_INTEGER)
3688     gfc_internal_error ("compare_bound_int(): Bad expression");
3689
3690   i = mpz_cmp_si (a->value.integer, b);
3691
3692   if (i < 0)
3693     return CMP_LT;
3694   if (i > 0)
3695     return CMP_GT;
3696   return CMP_EQ;
3697 }
3698
3699
3700 /* Compare an integer expression with a mpz_t.  */
3701
3702 static comparison
3703 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3704 {
3705   int i;
3706
3707   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3708     return CMP_UNKNOWN;
3709
3710   if (a->ts.type != BT_INTEGER)
3711     gfc_internal_error ("compare_bound_int(): Bad expression");
3712
3713   i = mpz_cmp (a->value.integer, b);
3714
3715   if (i < 0)
3716     return CMP_LT;
3717   if (i > 0)
3718     return CMP_GT;
3719   return CMP_EQ;
3720 }
3721
3722
3723 /* Compute the last value of a sequence given by a triplet.  
3724    Return 0 if it wasn't able to compute the last value, or if the
3725    sequence if empty, and 1 otherwise.  */
3726
3727 static int
3728 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3729                                 gfc_expr *stride, mpz_t last)
3730 {
3731   mpz_t rem;
3732
3733   if (start == NULL || start->expr_type != EXPR_CONSTANT
3734       || end == NULL || end->expr_type != EXPR_CONSTANT
3735       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3736     return 0;
3737
3738   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3739       || (stride != NULL && stride->ts.type != BT_INTEGER))
3740     return 0;
3741
3742   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3743     {
3744       if (compare_bound (start, end) == CMP_GT)
3745         return 0;
3746       mpz_set (last, end->value.integer);
3747       return 1;
3748     }
3749
3750   if (compare_bound_int (stride, 0) == CMP_GT)
3751     {
3752       /* Stride is positive */
3753       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3754         return 0;
3755     }
3756   else
3757     {
3758       /* Stride is negative */
3759       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3760         return 0;
3761     }
3762
3763   mpz_init (rem);
3764   mpz_sub (rem, end->value.integer, start->value.integer);
3765   mpz_tdiv_r (rem, rem, stride->value.integer);
3766   mpz_sub (last, end->value.integer, rem);
3767   mpz_clear (rem);
3768
3769   return 1;
3770 }
3771
3772
3773 /* Compare a single dimension of an array reference to the array
3774    specification.  */
3775
3776 static gfc_try
3777 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3778 {
3779   mpz_t last_value;
3780
3781   if (ar->dimen_type[i] == DIMEN_STAR)
3782     {
3783       gcc_assert (ar->stride[i] == NULL);
3784       /* This implies [*] as [*:] and [*:3] are not possible.  */
3785       if (ar->start[i] == NULL)
3786         {
3787           gcc_assert (ar->end[i] == NULL);
3788           return SUCCESS;
3789         }
3790     }
3791
3792 /* Given start, end and stride values, calculate the minimum and
3793    maximum referenced indexes.  */
3794
3795   switch (ar->dimen_type[i])
3796     {
3797     case DIMEN_VECTOR:
3798       break;
3799
3800     case DIMEN_STAR:
3801     case DIMEN_ELEMENT:
3802       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3803         {
3804           if (i < as->rank)
3805             gfc_warning ("Array reference at %L is out of bounds "
3806                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
3807                          mpz_get_si (ar->start[i]->value.integer),
3808                          mpz_get_si (as->lower[i]->value.integer), i+1);
3809           else
3810             gfc_warning ("Array reference at %L is out of bounds "
3811                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
3812                          mpz_get_si (ar->start[i]->value.integer),
3813                          mpz_get_si (as->lower[i]->value.integer),
3814                          i + 1 - as->rank);
3815           return SUCCESS;
3816         }
3817       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3818         {
3819           if (i < as->rank)
3820             gfc_warning ("Array reference at %L is out of bounds "
3821                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
3822                          mpz_get_si (ar->start[i]->value.integer),
3823                          mpz_get_si (as->upper[i]->value.integer), i+1);
3824           else
3825             gfc_warning ("Array reference at %L is out of bounds "
3826                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
3827                          mpz_get_si (ar->start[i]->value.integer),
3828                          mpz_get_si (as->upper[i]->value.integer),
3829                          i + 1 - as->rank);
3830           return SUCCESS;
3831         }
3832
3833       break;
3834
3835     case DIMEN_RANGE:
3836       {
3837 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3838 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3839
3840         comparison comp_start_end = compare_bound (AR_START, AR_END);
3841
3842         /* Check for zero stride, which is not allowed.  */
3843         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3844           {
3845             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3846             return FAILURE;
3847           }
3848
3849         /* if start == len || (stride > 0 && start < len)
3850                            || (stride < 0 && start > len),
3851            then the array section contains at least one element.  In this
3852            case, there is an out-of-bounds access if
3853            (start < lower || start > upper).  */
3854         if (compare_bound (AR_START, AR_END) == CMP_EQ
3855             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3856                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3857             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3858                 && comp_start_end == CMP_GT))
3859           {
3860             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3861               {
3862                 gfc_warning ("Lower array reference at %L is out of bounds "
3863                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3864                        mpz_get_si (AR_START->value.integer),
3865                        mpz_get_si (as->lower[i]->value.integer), i+1);
3866                 return SUCCESS;
3867               }
3868             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3869               {
3870                 gfc_warning ("Lower array reference at %L is out of bounds "
3871                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3872                        mpz_get_si (AR_START->value.integer),
3873                        mpz_get_si (as->upper[i]->value.integer), i+1);
3874                 return SUCCESS;
3875               }
3876           }
3877
3878         /* If we can compute the highest index of the array section,
3879            then it also has to be between lower and upper.  */
3880         mpz_init (last_value);
3881         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3882                                             last_value))
3883           {
3884             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3885               {
3886                 gfc_warning ("Upper array reference at %L is out of bounds "
3887                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3888                        mpz_get_si (last_value),
3889                        mpz_get_si (as->lower[i]->value.integer), i+1);
3890                 mpz_clear (last_value);
3891                 return SUCCESS;
3892               }
3893             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3894               {
3895                 gfc_warning ("Upper array reference at %L is out of bounds "
3896                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3897                        mpz_get_si (last_value),
3898                        mpz_get_si (as->upper[i]->value.integer), i+1);
3899                 mpz_clear (last_value);
3900                 return SUCCESS;
3901               }
3902           }
3903         mpz_clear (last_value);
3904
3905 #undef AR_START
3906 #undef AR_END
3907       }
3908       break;
3909
3910     default:
3911       gfc_internal_error ("check_dimension(): Bad array reference");
3912     }
3913
3914   return SUCCESS;
3915 }
3916
3917
3918 /* Compare an array reference with an array specification.  */
3919
3920 static gfc_try
3921 compare_spec_to_ref (gfc_array_ref *ar)
3922 {
3923   gfc_array_spec *as;
3924   int i;
3925
3926   as = ar->as;
3927   i = as->rank - 1;
3928   /* TODO: Full array sections are only allowed as actual parameters.  */
3929   if (as->type == AS_ASSUMED_SIZE
3930       && (/*ar->type == AR_FULL
3931           ||*/ (ar->type == AR_SECTION
3932               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3933     {
3934       gfc_error ("Rightmost upper bound of assumed size array section "
3935                  "not specified at %L", &ar->where);
3936       return FAILURE;
3937     }
3938
3939   if (ar->type == AR_FULL)
3940     return SUCCESS;
3941
3942   if (as->rank != ar->dimen)
3943     {
3944       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3945                  &ar->where, ar->dimen, as->rank);
3946       return FAILURE;
3947     }
3948
3949   /* ar->codimen == 0 is a local array.  */
3950   if (as->corank != ar->codimen && ar->codimen != 0)
3951     {
3952       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
3953                  &ar->where, ar->codimen, as->corank);
3954       return FAILURE;
3955     }
3956
3957   for (i = 0; i < as->rank; i++)
3958     if (check_dimension (i, ar, as) == FAILURE)
3959       return FAILURE;
3960
3961   /* Local access has no coarray spec.  */
3962   if (ar->codimen != 0)
3963     for (i = as->rank; i < as->rank + as->corank; i++)
3964       {
3965         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
3966           {
3967             gfc_error ("Coindex of codimension %d must be a scalar at %L",
3968                        i + 1 - as->rank, &ar->where);
3969             return FAILURE;
3970           }
3971         if (check_dimension (i, ar, as) == FAILURE)
3972           return FAILURE;
3973       }
3974
3975   return SUCCESS;
3976 }
3977
3978
3979 /* Resolve one part of an array index.  */
3980
3981 gfc_try
3982 gfc_resolve_index (gfc_expr *index, int check_scalar)
3983 {
3984   gfc_typespec ts;
3985
3986   if (index == NULL)
3987     return SUCCESS;
3988
3989   if (gfc_resolve_expr (index) == FAILURE)
3990     return FAILURE;
3991
3992   if (check_scalar && index->rank != 0)
3993     {
3994       gfc_error ("Array index at %L must be scalar", &index->where);
3995       return FAILURE;
3996     }
3997
3998   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3999     {
4000       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4001                  &index->where, gfc_basic_typename (index->ts.type));
4002       return FAILURE;
4003     }
4004
4005   if (index->ts.type == BT_REAL)
4006     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4007                         &index->where) == FAILURE)
4008       return FAILURE;
4009
4010   if (index->ts.kind != gfc_index_integer_kind
4011       || index->ts.type != BT_INTEGER)
4012     {
4013       gfc_clear_ts (&ts);
4014       ts.type = BT_INTEGER;
4015       ts.kind = gfc_index_integer_kind;
4016
4017       gfc_convert_type_warn (index, &ts, 2, 0);
4018     }
4019
4020   return SUCCESS;
4021 }
4022
4023 /* Resolve a dim argument to an intrinsic function.  */
4024
4025 gfc_try
4026 gfc_resolve_dim_arg (gfc_expr *dim)
4027 {
4028   if (dim == NULL)
4029     return SUCCESS;
4030
4031   if (gfc_resolve_expr (dim) == FAILURE)
4032     return FAILURE;
4033
4034   if (dim->rank != 0)
4035     {
4036       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4037       return FAILURE;
4038
4039     }
4040
4041   if (dim->ts.type != BT_INTEGER)
4042     {
4043       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4044       return FAILURE;
4045     }
4046
4047   if (dim->ts.kind != gfc_index_integer_kind)
4048     {
4049       gfc_typespec ts;
4050
4051       gfc_clear_ts (&ts);
4052       ts.type = BT_INTEGER;
4053       ts.kind = gfc_index_integer_kind;
4054
4055       gfc_convert_type_warn (dim, &ts, 2, 0);
4056     }
4057
4058   return SUCCESS;
4059 }
4060
4061 /* Given an expression that contains array references, update those array
4062    references to point to the right array specifications.  While this is
4063    filled in during matching, this information is difficult to save and load
4064    in a module, so we take care of it here.
4065
4066    The idea here is that the original array reference comes from the
4067    base symbol.  We traverse the list of reference structures, setting
4068    the stored reference to references.  Component references can
4069    provide an additional array specification.  */
4070
4071 static void
4072 find_array_spec (gfc_expr *e)
4073 {
4074   gfc_array_spec *as;
4075   gfc_component *c;
4076   gfc_symbol *derived;
4077   gfc_ref *ref;
4078
4079   if (e->symtree->n.sym->ts.type == BT_CLASS)
4080     as = e->symtree->n.sym->ts.u.derived->components->as;
4081   else
4082     as = e->symtree->n.sym->as;
4083   derived = NULL;
4084
4085   for (ref = e->ref; ref; ref = ref->next)
4086     switch (ref->type)
4087       {
4088       case REF_ARRAY:
4089         if (as == NULL)
4090           gfc_internal_error ("find_array_spec(): Missing spec");
4091
4092         ref->u.ar.as = as;
4093         as = NULL;
4094         break;
4095
4096       case REF_COMPONENT:
4097         if (derived == NULL)
4098           derived = e->symtree->n.sym->ts.u.derived;
4099
4100         if (derived->attr.is_class)
4101           derived = derived->components->ts.u.derived;
4102
4103         c = derived->components;
4104
4105         for (; c; c = c->next)
4106           if (c == ref->u.c.component)
4107             {
4108               /* Track the sequence of component references.  */
4109               if (c->ts.type == BT_DERIVED)
4110                 derived = c->ts.u.derived;
4111               break;
4112             }
4113
4114         if (c == NULL)
4115           gfc_internal_error ("find_array_spec(): Component not found");
4116
4117         if (c->attr.dimension)
4118           {
4119             if (as != NULL)
4120               gfc_internal_error ("find_array_spec(): unused as(1)");
4121             as = c->as;
4122           }
4123
4124         break;
4125
4126       case REF_SUBSTRING:
4127         break;
4128       }
4129
4130   if (as != NULL)
4131     gfc_internal_error ("find_array_spec(): unused as(2)");
4132 }
4133
4134
4135 /* Resolve an array reference.  */
4136
4137 static gfc_try
4138 resolve_array_ref (gfc_array_ref *ar)
4139 {
4140   int i, check_scalar;
4141   gfc_expr *e;
4142
4143   for (i = 0; i < ar->dimen + ar->codimen; i++)
4144     {
4145       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4146
4147       if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
4148         return FAILURE;
4149       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4150         return FAILURE;
4151       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4152         return FAILURE;
4153
4154       e = ar->start[i];
4155
4156       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4157         switch (e->rank)
4158           {
4159           case 0:
4160             ar->dimen_type[i] = DIMEN_ELEMENT;
4161             break;
4162
4163           case 1:
4164             ar->dimen_type[i] = DIMEN_VECTOR;
4165             if (e->expr_type == EXPR_VARIABLE
4166                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4167               ar->start[i] = gfc_get_parentheses (e);
4168             break;
4169
4170           default:
4171             gfc_error ("Array index at %L is an array of rank %d",
4172                        &ar->c_where[i], e->rank);
4173             return FAILURE;
4174           }
4175     }
4176
4177   if (ar->type == AR_FULL && ar->as->rank == 0)
4178     ar->type = AR_ELEMENT;
4179
4180   /* If the reference type is unknown, figure out what kind it is.  */
4181
4182   if (ar->type == AR_UNKNOWN)
4183     {
4184       ar->type = AR_ELEMENT;
4185       for (i = 0; i < ar->dimen; i++)
4186         if (ar->dimen_type[i] == DIMEN_RANGE
4187             || ar->dimen_type[i] == DIMEN_VECTOR)
4188           {
4189             ar->type = AR_SECTION;
4190             break;
4191           }
4192     }
4193
4194   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4195     return FAILURE;
4196
4197   return SUCCESS;
4198 }
4199
4200
4201 static gfc_try
4202 resolve_substring (gfc_ref *ref)
4203 {
4204   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4205
4206   if (ref->u.ss.start != NULL)
4207     {
4208       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4209         return FAILURE;
4210
4211       if (ref->u.ss.start->ts.type != BT_INTEGER)
4212         {
4213           gfc_error ("Substring start index at %L must be of type INTEGER",
4214                      &ref->u.ss.start->where);
4215           return FAILURE;
4216         }
4217
4218       if (ref->u.ss.start->rank != 0)
4219         {
4220           gfc_error ("Substring start index at %L must be scalar",
4221                      &ref->u.ss.start->where);
4222           return FAILURE;
4223         }
4224
4225       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4226           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4227               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4228         {
4229           gfc_error ("Substring start index at %L is less than one",
4230                      &ref->u.ss.start->where);
4231           return FAILURE;
4232         }
4233     }
4234
4235   if (ref->u.ss.end != NULL)
4236     {
4237       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4238         return FAILURE;
4239
4240       if (ref->u.ss.end->ts.type != BT_INTEGER)
4241         {
4242           gfc_error ("Substring end index at %L must be of type INTEGER",
4243                      &ref->u.ss.end->where);
4244           return FAILURE;
4245         }
4246
4247       if (ref->u.ss.end->rank != 0)
4248         {
4249           gfc_error ("Substring end index at %L must be scalar",
4250                      &ref->u.ss.end->where);
4251           return FAILURE;
4252         }
4253
4254       if (ref->u.ss.length != NULL
4255           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4256           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4257               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4258         {
4259           gfc_error ("Substring end index at %L exceeds the string length",
4260                      &ref->u.ss.start->where);
4261           return FAILURE;
4262         }
4263
4264       if (compare_bound_mpz_t (ref->u.ss.end,
4265                                gfc_integer_kinds[k].huge) == CMP_GT
4266           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4267               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4268         {
4269           gfc_error ("Substring end index at %L is too large",
4270                      &ref->u.ss.end->where);
4271           return FAILURE;
4272         }
4273     }
4274
4275   return SUCCESS;
4276 }
4277
4278
4279 /* This function supplies missing substring charlens.  */
4280
4281 void
4282 gfc_resolve_substring_charlen (gfc_expr *e)
4283 {
4284   gfc_ref *char_ref;
4285   gfc_expr *start, *end;
4286
4287   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4288     if (char_ref->type == REF_SUBSTRING)
4289       break;
4290
4291   if (!char_ref)
4292     return;
4293
4294   gcc_assert (char_ref->next == NULL);
4295
4296   if (e->ts.u.cl)
4297     {
4298       if (e->ts.u.cl->length)
4299         gfc_free_expr (e->ts.u.cl->length);
4300       else if (e->expr_type == EXPR_VARIABLE
4301                  && e->symtree->n.sym->attr.dummy)
4302         return;
4303     }
4304
4305   e->ts.type = BT_CHARACTER;
4306   e->ts.kind = gfc_default_character_kind;
4307
4308   if (!e->ts.u.cl)
4309     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4310
4311   if (char_ref->u.ss.start)
4312     start = gfc_copy_expr (char_ref->u.ss.start);
4313   else
4314     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4315
4316   if (char_ref->u.ss.end)
4317     end = gfc_copy_expr (char_ref->u.ss.end);
4318   else if (e->expr_type == EXPR_VARIABLE)
4319     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4320   else
4321     end = NULL;
4322
4323   if (!start || !end)
4324     return;
4325
4326   /* Length = (end - start +1).  */
4327   e->ts.u.cl->length = gfc_subtract (end, start);
4328   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4329                                 gfc_get_int_expr (gfc_default_integer_kind,
4330                                                   NULL, 1));
4331
4332   e->ts.u.cl->length->ts.type = BT_INTEGER;
4333   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4334
4335   /* Make sure that the length is simplified.  */
4336   gfc_simplify_expr (e->ts.u.cl->length, 1);
4337   gfc_resolve_expr (e->ts.u.cl->length);
4338 }
4339
4340
4341 /* Resolve subtype references.  */
4342
4343 static gfc_try
4344 resolve_ref (gfc_expr *expr)
4345 {
4346   int current_part_dimension, n_components, seen_part_dimension;
4347   gfc_ref *ref;
4348
4349   for (ref = expr->ref; ref; ref = ref->next)
4350     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4351       {
4352         find_array_spec (expr);
4353         break;
4354       }
4355
4356   for (ref = expr->ref; ref; ref = ref->next)
4357     switch (ref->type)
4358       {
4359       case REF_ARRAY:
4360         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4361           return FAILURE;
4362         break;
4363
4364       case REF_COMPONENT:
4365         break;
4366
4367       case REF_SUBSTRING:
4368         resolve_substring (ref);
4369         break;
4370       }
4371
4372   /* Check constraints on part references.  */
4373
4374   current_part_dimension = 0;
4375   seen_part_dimension = 0;
4376   n_components = 0;
4377
4378   for (ref = expr->ref; ref; ref = ref->next)
4379     {
4380       switch (ref->type)
4381         {
4382         case REF_ARRAY:
4383           switch (ref->u.ar.type)
4384             {
4385             case AR_FULL:
4386               /* Coarray scalar.  */
4387               if (ref->u.ar.as->rank == 0)
4388                 {
4389                   current_part_dimension = 0;
4390                   break;
4391                 }
4392               /* Fall through.  */
4393             case AR_SECTION:
4394               current_part_dimension = 1;
4395               break;
4396
4397             case AR_ELEMENT:
4398               current_part_dimension = 0;
4399               break;
4400
4401             case AR_UNKNOWN:
4402               gfc_internal_error ("resolve_ref(): Bad array reference");
4403             }
4404
4405           break;
4406
4407         case REF_COMPONENT:
4408           if (current_part_dimension || seen_part_dimension)
4409             {
4410               /* F03:C614.  */
4411               if (ref->u.c.component->attr.pointer
4412                   || ref->u.c.component->attr.proc_pointer)
4413                 {
4414                   gfc_error ("Component to the right of a part reference "
4415                              "with nonzero rank must not have the POINTER "
4416                              "attribute at %L", &expr->where);
4417                   return FAILURE;
4418                 }
4419               else if (ref->u.c.component->attr.allocatable)
4420                 {
4421                   gfc_error ("Component to the right of a part reference "
4422                              "with nonzero rank must not have the ALLOCATABLE "
4423                              "attribute at %L", &expr->where);
4424                   return FAILURE;
4425                 }
4426             }
4427
4428           n_components++;
4429           break;
4430
4431         case REF_SUBSTRING:
4432           break;
4433         }
4434
4435       if (((ref->type == REF_COMPONENT && n_components > 1)
4436            || ref->next == NULL)
4437           && current_part_dimension
4438           && seen_part_dimension)
4439         {
4440           gfc_error ("Two or more part references with nonzero rank must "
4441                      "not be specified at %L", &expr->where);
4442           return FAILURE;
4443         }
4444
4445       if (ref->type == REF_COMPONENT)
4446         {
4447           if (current_part_dimension)
4448             seen_part_dimension = 1;
4449
4450           /* reset to make sure */
4451           current_part_dimension = 0;
4452         }
4453     }
4454
4455   return SUCCESS;
4456 }
4457
4458
4459 /* Given an expression, determine its shape.  This is easier than it sounds.
4460    Leaves the shape array NULL if it is not possible to determine the shape.  */
4461
4462 static void
4463 expression_shape (gfc_expr *e)
4464 {
4465   mpz_t array[GFC_MAX_DIMENSIONS];
4466   int i;
4467
4468   if (e->rank == 0 || e->shape != NULL)
4469     return;
4470
4471   for (i = 0; i < e->rank; i++)
4472     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4473       goto fail;
4474
4475   e->shape = gfc_get_shape (e->rank);
4476
4477   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4478
4479   return;
4480
4481 fail:
4482   for (i--; i >= 0; i--)
4483     mpz_clear (array[i]);
4484 }
4485
4486
4487 /* Given a variable expression node, compute the rank of the expression by
4488    examining the base symbol and any reference structures it may have.  */
4489
4490 static void
4491 expression_rank (gfc_expr *e)
4492 {
4493   gfc_ref *ref;
4494   int i, rank;
4495
4496   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4497      could lead to serious confusion...  */
4498   gcc_assert (e->expr_type != EXPR_COMPCALL);
4499
4500   if (e->ref == NULL)
4501     {
4502       if (e->expr_type == EXPR_ARRAY)
4503         goto done;
4504       /* Constructors can have a rank different from one via RESHAPE().  */
4505
4506       if (e->symtree == NULL)
4507         {
4508           e->rank = 0;
4509           goto done;
4510         }
4511
4512       e->rank = (e->symtree->n.sym->as == NULL)
4513                 ? 0 : e->symtree->n.sym->as->rank;
4514       goto done;
4515     }
4516
4517   rank = 0;
4518
4519   for (ref = e->ref; ref; ref = ref->next)
4520     {
4521       if (ref->type != REF_ARRAY)
4522         continue;
4523
4524       if (ref->u.ar.type == AR_FULL)
4525         {
4526           rank = ref->u.ar.as->rank;
4527           break;
4528         }
4529
4530       if (ref->u.ar.type == AR_SECTION)
4531         {
4532           /* Figure out the rank of the section.  */
4533           if (rank != 0)
4534             gfc_internal_error ("expression_rank(): Two array specs");
4535
4536           for (i = 0; i < ref->u.ar.dimen; i++)
4537             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4538                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4539               rank++;
4540
4541           break;
4542         }
4543     }
4544
4545   e->rank = rank;
4546
4547 done:
4548   expression_shape (e);
4549 }
4550
4551
4552 /* Resolve a variable expression.  */
4553
4554 static gfc_try
4555 resolve_variable (gfc_expr *e)
4556 {
4557   gfc_symbol *sym;
4558   gfc_try t;
4559
4560   t = SUCCESS;
4561
4562   if (e->symtree == NULL)
4563     return FAILURE;
4564
4565   if (e->ref && resolve_ref (e) == FAILURE)
4566     return FAILURE;
4567
4568   sym = e->symtree->n.sym;
4569   if (sym->attr.flavor == FL_PROCEDURE
4570       && (!sym->attr.function
4571           || (sym->attr.function && sym->result
4572               && sym->result->attr.proc_pointer
4573               && !sym->result->attr.function)))
4574     {
4575       e->ts.type = BT_PROCEDURE;
4576       goto resolve_procedure;
4577     }
4578
4579   if (sym->ts.type != BT_UNKNOWN)
4580     gfc_variable_attr (e, &e->ts);
4581   else
4582     {
4583       /* Must be a simple variable reference.  */
4584       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4585         return FAILURE;
4586       e->ts = sym->ts;
4587     }
4588
4589   if (check_assumed_size_reference (sym, e))
4590     return FAILURE;
4591
4592   /* Deal with forward references to entries during resolve_code, to
4593      satisfy, at least partially, 12.5.2.5.  */
4594   if (gfc_current_ns->entries
4595       && current_entry_id == sym->entry_id
4596       && cs_base
4597       && cs_base->current
4598       && cs_base->current->op != EXEC_ENTRY)
4599     {
4600       gfc_entry_list *entry;
4601       gfc_formal_arglist *formal;
4602       int n;
4603       bool seen;
4604
4605       /* If the symbol is a dummy...  */
4606       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4607         {
4608           entry = gfc_current_ns->entries;
4609           seen = false;
4610
4611           /* ...test if the symbol is a parameter of previous entries.  */
4612           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4613             for (formal = entry->sym->formal; formal; formal = formal->next)
4614               {
4615                 if (formal->sym && sym->name == formal->sym->name)
4616                   seen = true;
4617               }
4618
4619           /*  If it has not been seen as a dummy, this is an error.  */
4620           if (!seen)
4621             {
4622               if (specification_expr)
4623                 gfc_error ("Variable '%s', used in a specification expression"
4624                            ", is referenced at %L before the ENTRY statement "
4625                            "in which it is a parameter",
4626                            sym->name, &cs_base->current->loc);
4627               else
4628                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4629                            "statement in which it is a parameter",
4630                            sym->name, &cs_base->current->loc);
4631               t = FAILURE;
4632             }
4633         }
4634
4635       /* Now do the same check on the specification expressions.  */
4636       specification_expr = 1;
4637       if (sym->ts.type == BT_CHARACTER
4638           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4639         t = FAILURE;
4640
4641       if (sym->as)
4642         for (n = 0; n < sym->as->rank; n++)
4643           {
4644              specification_expr = 1;
4645              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4646                t = FAILURE;
4647              specification_expr = 1;
4648              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4649                t = FAILURE;
4650           }
4651       specification_expr = 0;
4652
4653       if (t == SUCCESS)
4654         /* Update the symbol's entry level.  */
4655         sym->entry_id = current_entry_id + 1;
4656     }
4657
4658 resolve_procedure:
4659   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4660     t = FAILURE;
4661
4662   /* F2008, C617 and C1229.  */
4663   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
4664       && gfc_is_coindexed (e))
4665     {
4666       gfc_ref *ref, *ref2 = NULL;
4667
4668       if (e->ts.type == BT_CLASS)
4669         {
4670           gfc_error ("Polymorphic subobject of coindexed object at %L",
4671                      &e->where);
4672           t = FAILURE;
4673         }
4674
4675       for (ref = e->ref; ref; ref = ref->next)
4676         {
4677           if (ref->type == REF_COMPONENT)
4678             ref2 = ref;
4679           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
4680             break;
4681         }
4682
4683       for ( ; ref; ref = ref->next)
4684         if (ref->type == REF_COMPONENT)
4685           break;
4686
4687       /* Expression itself is coindexed object.  */
4688       if (ref == NULL)
4689         {
4690           gfc_component *c;
4691           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
4692           for ( ; c; c = c->next)
4693             if (c->attr.allocatable && c->ts.type == BT_CLASS)
4694               {
4695                 gfc_error ("Coindexed object with polymorphic allocatable "
4696                          "subcomponent at %L", &e->where);
4697                 t = FAILURE;
4698                 break;
4699               }
4700         }
4701     }
4702
4703   return t;
4704 }
4705
4706
4707 /* Checks to see that the correct symbol has been host associated.
4708    The only situation where this arises is that in which a twice
4709    contained function is parsed after the host association is made.
4710    Therefore, on detecting this, change the symbol in the expression
4711    and convert the array reference into an actual arglist if the old
4712    symbol is a variable.  */
4713 static bool
4714 check_host_association (gfc_expr *e)
4715 {
4716   gfc_symbol *sym, *old_sym;
4717   gfc_symtree *st;
4718   int n;
4719   gfc_ref *ref;
4720   gfc_actual_arglist *arg, *tail = NULL;
4721   bool retval = e->expr_type == EXPR_FUNCTION;
4722
4723   /*  If the expression is the result of substitution in
4724       interface.c(gfc_extend_expr) because there is no way in
4725       which the host association can be wrong.  */
4726   if (e->symtree == NULL
4727         || e->symtree->n.sym == NULL
4728         || e->user_operator)
4729     return retval;
4730
4731   old_sym = e->symtree->n.sym;
4732
4733   if (gfc_current_ns->parent
4734         && old_sym->ns != gfc_current_ns)
4735     {
4736       /* Use the 'USE' name so that renamed module symbols are
4737          correctly handled.  */
4738       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4739
4740       if (sym && old_sym != sym
4741               && sym->ts.type == old_sym->ts.type
4742               && sym->attr.flavor == FL_PROCEDURE
4743               && sym->attr.contained)
4744         {
4745           /* Clear the shape, since it might not be valid.  */
4746           if (e->shape != NULL)
4747             {
4748               for (n = 0; n < e->rank; n++)
4749                 mpz_clear (e->shape[n]);
4750
4751               gfc_free (e->shape);
4752             }
4753
4754           /* Give the expression the right symtree!  */
4755           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4756           gcc_assert (st != NULL);
4757
4758           if (old_sym->attr.flavor == FL_PROCEDURE
4759                 || e->expr_type == EXPR_FUNCTION)
4760             {
4761               /* Original was function so point to the new symbol, since
4762                  the actual argument list is already attached to the
4763                  expression. */
4764               e->value.function.esym = NULL;
4765               e->symtree = st;
4766             }
4767           else
4768             {
4769               /* Original was variable so convert array references into
4770                  an actual arglist. This does not need any checking now
4771                  since gfc_resolve_function will take care of it.  */
4772               e->value.function.actual = NULL;
4773               e->expr_type = EXPR_FUNCTION;
4774               e->symtree = st;
4775
4776               /* Ambiguity will not arise if the array reference is not
4777                  the last reference.  */
4778               for (ref = e->ref; ref; ref = ref->next)
4779                 if (ref->type == REF_ARRAY && ref->next == NULL)
4780                   break;
4781
4782               gcc_assert (ref->type == REF_ARRAY);
4783
4784               /* Grab the start expressions from the array ref and
4785                  copy them into actual arguments.  */
4786               for (n = 0; n < ref->u.ar.dimen; n++)
4787                 {
4788                   arg = gfc_get_actual_arglist ();
4789                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4790                   if (e->value.function.actual == NULL)
4791                     tail = e->value.function.actual = arg;
4792                   else
4793                     {
4794                       tail->next = arg;
4795                       tail = arg;
4796                     }
4797                 }
4798
4799               /* Dump the reference list and set the rank.  */
4800               gfc_free_ref_list (e->ref);
4801               e->ref = NULL;
4802               e->rank = sym->as ? sym->as->rank : 0;
4803             }
4804
4805           gfc_resolve_expr (e);
4806           sym->refs++;
4807         }
4808     }
4809   /* This might have changed!  */
4810   return e->expr_type == EXPR_FUNCTION;
4811 }
4812
4813
4814 static void
4815 gfc_resolve_character_operator (gfc_expr *e)
4816 {
4817   gfc_expr *op1 = e->value.op.op1;
4818   gfc_expr *op2 = e->value.op.op2;
4819   gfc_expr *e1 = NULL;
4820   gfc_expr *e2 = NULL;
4821
4822   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4823
4824   if (op1->ts.u.cl && op1->ts.u.cl->length)
4825     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4826   else if (op1->expr_type == EXPR_CONSTANT)
4827     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4828                            op1->value.character.length);
4829
4830   if (op2->ts.u.cl && op2->ts.u.cl->length)
4831     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4832   else if (op2->expr_type == EXPR_CONSTANT)
4833     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4834                            op2->value.character.length);
4835
4836   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4837
4838   if (!e1 || !e2)
4839     return;
4840
4841   e->ts.u.cl->length = gfc_add (e1, e2);
4842   e->ts.u.cl->length->ts.type = BT_INTEGER;
4843   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4844   gfc_simplify_expr (e->ts.u.cl->length, 0);
4845   gfc_resolve_expr (e->ts.u.cl->length);
4846
4847   return;
4848 }
4849
4850
4851 /*  Ensure that an character expression has a charlen and, if possible, a
4852     length expression.  */
4853
4854 static void
4855 fixup_charlen (gfc_expr *e)
4856 {
4857   /* The cases fall through so that changes in expression type and the need
4858      for multiple fixes are picked up.  In all circumstances, a charlen should
4859      be available for the middle end to hang a backend_decl on.  */
4860   switch (e->expr_type)
4861     {
4862     case EXPR_OP:
4863       gfc_resolve_character_operator (e);
4864
4865     case EXPR_ARRAY:
4866       if (e->expr_type == EXPR_ARRAY)
4867         gfc_resolve_character_array_constructor (e);
4868
4869     case EXPR_SUBSTRING:
4870       if (!e->ts.u.cl && e->ref)
4871         gfc_resolve_substring_charlen (e);
4872
4873     default:
4874       if (!e->ts.u.cl)
4875         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4876
4877       break;
4878     }
4879 }
4880
4881
4882 /* Update an actual argument to include the passed-object for type-bound
4883    procedures at the right position.  */
4884
4885 static gfc_actual_arglist*
4886 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
4887                      const char *name)
4888 {
4889   gcc_assert (argpos > 0);
4890
4891   if (argpos == 1)
4892     {
4893       gfc_actual_arglist* result;
4894
4895       result = gfc_get_actual_arglist ();
4896       result->expr = po;
4897       result->next = lst;
4898       if (name)
4899         result->name = name;
4900
4901       return result;
4902     }
4903
4904   if (lst)
4905     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
4906   else
4907     lst = update_arglist_pass (NULL, po, argpos - 1, name);
4908   return lst;
4909 }
4910
4911
4912 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
4913
4914 static gfc_expr*
4915 extract_compcall_passed_object (gfc_expr* e)
4916 {
4917   gfc_expr* po;
4918
4919   gcc_assert (e->expr_type == EXPR_COMPCALL);
4920
4921   if (e->value.compcall.base_object)
4922     po = gfc_copy_expr (e->value.compcall.base_object);
4923   else
4924     {
4925       po = gfc_get_expr ();
4926       po->expr_type = EXPR_VARIABLE;
4927       po->symtree = e->symtree;
4928       po->ref = gfc_copy_ref (e->ref);
4929       po->where = e->where;
4930     }
4931
4932   if (gfc_resolve_expr (po) == FAILURE)
4933     return NULL;
4934
4935   return po;
4936 }
4937
4938
4939 /* Update the arglist of an EXPR_COMPCALL expression to include the
4940    passed-object.  */
4941
4942 static gfc_try
4943 update_compcall_arglist (gfc_expr* e)
4944 {
4945   gfc_expr* po;
4946   gfc_typebound_proc* tbp;
4947
4948   tbp = e->value.compcall.tbp;
4949
4950   if (tbp->error)
4951     return FAILURE;
4952
4953   po = extract_compcall_passed_object (e);
4954   if (!po)
4955     return FAILURE;
4956
4957   if (tbp->nopass || e->value.compcall.ignore_pass)
4958     {
4959       gfc_free_expr (po);
4960       return SUCCESS;
4961     }
4962
4963   gcc_assert (tbp->pass_arg_num > 0);
4964   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
4965                                                   tbp->pass_arg_num,
4966                                                   tbp->pass_arg);
4967
4968   return SUCCESS;
4969 }
4970
4971
4972 /* Extract the passed object from a PPC call (a copy of it).  */
4973
4974 static gfc_expr*
4975 extract_ppc_passed_object (gfc_expr *e)
4976 {
4977   gfc_expr *po;
4978   gfc_ref **ref;
4979
4980   po = gfc_get_expr ();
4981   po->expr_type = EXPR_VARIABLE;
4982   po->symtree = e->symtree;
4983   po->ref = gfc_copy_ref (e->ref);
4984   po->where = e->where;
4985
4986   /* Remove PPC reference.  */
4987   ref = &po->ref;
4988   while ((*ref)->next)
4989     ref = &(*ref)->next;
4990   gfc_free_ref_list (*ref);
4991   *ref = NULL;
4992
4993   if (gfc_resolve_expr (po) == FAILURE)
4994     return NULL;
4995
4996   return po;
4997 }
4998
4999
5000 /* Update the actual arglist of a procedure pointer component to include the
5001    passed-object.  */
5002
5003 static gfc_try
5004 update_ppc_arglist (gfc_expr* e)
5005 {
5006   gfc_expr* po;
5007   gfc_component *ppc;
5008   gfc_typebound_proc* tb;
5009
5010   if (!gfc_is_proc_ptr_comp (e, &ppc))
5011     return FAILURE;
5012
5013   tb = ppc->tb;
5014
5015   if (tb->error)
5016     return FAILURE;
5017   else if (tb->nopass)
5018     return SUCCESS;
5019
5020   po = extract_ppc_passed_object (e);
5021   if (!po)
5022     return FAILURE;
5023
5024   if (po->rank > 0)
5025     {
5026       gfc_error ("Passed-object at %L must be scalar", &e->where);
5027       return FAILURE;
5028     }
5029
5030   gcc_assert (tb->pass_arg_num > 0);
5031   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5032                                                   tb->pass_arg_num,
5033                                                   tb->pass_arg);
5034
5035   return SUCCESS;
5036 }
5037
5038
5039 /* Check that the object a TBP is called on is valid, i.e. it must not be
5040    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5041
5042 static gfc_try
5043 check_typebound_baseobject (gfc_expr* e)
5044 {
5045   gfc_expr* base;
5046
5047   base = extract_compcall_passed_object (e);
5048   if (!base)
5049     return FAILURE;
5050
5051   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5052
5053   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5054     {
5055       gfc_error ("Base object for type-bound procedure call at %L is of"
5056                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5057       return FAILURE;
5058     }
5059
5060   /* If the procedure called is NOPASS, the base object must be scalar.  */
5061   if (e->value.compcall.tbp->nopass && base->rank > 0)
5062     {
5063       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5064                  " be scalar", &e->where);
5065       return FAILURE;
5066     }
5067
5068   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5069   if (base->rank > 0)
5070     {
5071       gfc_error ("Non-scalar base object at %L currently not implemented",
5072                  &e->where);
5073       return FAILURE;
5074     }
5075
5076   return SUCCESS;
5077 }
5078
5079
5080 /* Resolve a call to a type-bound procedure, either function or subroutine,
5081    statically from the data in an EXPR_COMPCALL expression.  The adapted
5082    arglist and the target-procedure symtree are returned.  */
5083
5084 static gfc_try
5085 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5086                           gfc_actual_arglist** actual)
5087 {
5088   gcc_assert (e->expr_type == EXPR_COMPCALL);
5089   gcc_assert (!e->value.compcall.tbp->is_generic);
5090
5091   /* Update the actual arglist for PASS.  */
5092   if (update_compcall_arglist (e) == FAILURE)
5093     return FAILURE;
5094
5095   *actual = e->value.compcall.actual;
5096   *target = e->value.compcall.tbp->u.specific;
5097
5098   gfc_free_ref_list (e->ref);
5099   e->ref = NULL;
5100   e->value.compcall.actual = NULL;
5101
5102   return SUCCESS;
5103 }
5104
5105
5106 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5107    which of the specific bindings (if any) matches the arglist and transform
5108    the expression into a call of that binding.  */
5109
5110 static gfc_try
5111 resolve_typebound_generic_call (gfc_expr* e)
5112 {
5113   gfc_typebound_proc* genproc;
5114   const char* genname;
5115
5116   gcc_assert (e->expr_type == EXPR_COMPCALL);
5117   genname = e->value.compcall.name;
5118   genproc = e->value.compcall.tbp;
5119
5120   if (!genproc->is_generic)
5121     return SUCCESS;
5122
5123   /* Try the bindings on this type and in the inheritance hierarchy.  */
5124   for (; genproc; genproc = genproc->overridden)
5125     {
5126       gfc_tbp_generic* g;
5127
5128       gcc_assert (genproc->is_generic);
5129       for (g = genproc->u.generic; g; g = g->next)
5130         {
5131           gfc_symbol* target;
5132           gfc_actual_arglist* args;
5133           bool matches;
5134
5135           gcc_assert (g->specific);
5136
5137           if (g->specific->error)
5138             continue;
5139
5140           target = g->specific->u.specific->n.sym;
5141
5142           /* Get the right arglist by handling PASS/NOPASS.  */
5143           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5144           if (!g->specific->nopass)
5145             {
5146               gfc_expr* po;
5147               po = extract_compcall_passed_object (e);
5148               if (!po)
5149                 return FAILURE;
5150
5151               gcc_assert (g->specific->pass_arg_num > 0);
5152               gcc_assert (!g->specific->error);
5153               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5154                                           g->specific->pass_arg);
5155             }
5156           resolve_actual_arglist (args, target->attr.proc,
5157                                   is_external_proc (target) && !target->formal);
5158
5159           /* Check if this arglist matches the formal.  */
5160           matches = gfc_arglist_matches_symbol (&args, target);
5161
5162           /* Clean up and break out of the loop if we've found it.  */
5163           gfc_free_actual_arglist (args);
5164           if (matches)
5165             {
5166               e->value.compcall.tbp = g->specific;
5167               goto success;
5168             }
5169         }
5170     }
5171
5172   /* Nothing matching found!  */
5173   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5174              " '%s' at %L", genname, &e->where);
5175   return FAILURE;
5176
5177 success:
5178   return SUCCESS;
5179 }
5180
5181
5182 /* Resolve a call to a type-bound subroutine.  */
5183
5184 static gfc_try
5185 resolve_typebound_call (gfc_code* c)
5186 {
5187   gfc_actual_arglist* newactual;
5188   gfc_symtree* target;
5189
5190   /* Check that's really a SUBROUTINE.  */
5191   if (!c->expr1->value.compcall.tbp->subroutine)
5192     {
5193       gfc_error ("'%s' at %L should be a SUBROUTINE",
5194                  c->expr1->value.compcall.name, &c->loc);
5195       return FAILURE;
5196     }
5197
5198   if (check_typebound_baseobject (c->expr1) == FAILURE)
5199     return FAILURE;
5200
5201   if (resolve_typebound_generic_call (c->expr1) == FAILURE)
5202     return FAILURE;
5203
5204   /* Transform into an ordinary EXEC_CALL for now.  */
5205
5206   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5207     return FAILURE;
5208
5209   c->ext.actual = newactual;
5210   c->symtree = target;
5211   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5212
5213   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5214
5215   gfc_free_expr (c->expr1);
5216   c->expr1 = gfc_get_expr ();
5217   c->expr1->expr_type = EXPR_FUNCTION;
5218   c->expr1->symtree = target;
5219   c->expr1->where = c->loc;
5220
5221   return resolve_call (c);
5222 }
5223
5224
5225 /* Resolve a component-call expression.  This originally was intended
5226    only to see functions.  However, it is convenient to use it in 
5227    resolving subroutine class methods, since we do not have to add a
5228    gfc_code each time. */
5229 static gfc_try
5230 resolve_compcall (gfc_expr* e, bool fcn, bool class_members)
5231 {
5232   gfc_actual_arglist* newactual;
5233   gfc_symtree* target;
5234
5235   /* Check that's really a FUNCTION.  */
5236   if (fcn && !e->value.compcall.tbp->function)
5237     {
5238       gfc_error ("'%s' at %L should be a FUNCTION",
5239                  e->value.compcall.name, &e->where);
5240       return FAILURE;
5241     }
5242   else if (!fcn && !e->value.compcall.tbp->subroutine)
5243     {
5244       /* To resolve class member calls, we borrow this bit
5245          of code to select the specific procedures.  */
5246       gfc_error ("'%s' at %L should be a SUBROUTINE",
5247                  e->value.compcall.name, &e->where);
5248       return FAILURE;
5249     }
5250
5251   /* These must not be assign-calls!  */
5252   gcc_assert (!e->value.compcall.assign);
5253
5254   if (check_typebound_baseobject (e) == FAILURE)
5255     return FAILURE;
5256
5257   if (resolve_typebound_generic_call (e) == FAILURE)
5258     return FAILURE;
5259   gcc_assert (!e->value.compcall.tbp->is_generic);
5260
5261   /* Take the rank from the function's symbol.  */
5262   if (e->value.compcall.tbp->u.specific->n.sym->as)
5263     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5264
5265   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5266      arglist to the TBP's binding target.  */
5267
5268   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5269     return FAILURE;
5270
5271   e->value.function.actual = newactual;
5272   e->value.function.name = NULL;
5273   e->value.function.esym = target->n.sym;
5274   e->value.function.class_esym = NULL;
5275   e->value.function.isym = NULL;
5276   e->symtree = target;
5277   e->ts = target->n.sym->ts;
5278   e->expr_type = EXPR_FUNCTION;
5279
5280   /* Resolution is not necessary when constructing component calls
5281      for class members, since this must only be done for the
5282      declared type, which is done afterwards.  */
5283   return !class_members ? gfc_resolve_expr (e) : SUCCESS;
5284 }
5285
5286
5287 /* Resolve a typebound call for the members in a class.  This group of
5288    functions implements dynamic dispatch in the provisional version
5289    of f03 OOP.  As soon as vtables are in place and contain pointers
5290    to methods, this will no longer be necessary.  */
5291 static gfc_expr *list_e;
5292 static gfc_try check_class_members (gfc_symbol *);
5293 static gfc_try class_try;
5294 static bool fcn_flag;
5295
5296
5297 static void
5298 check_members (gfc_symbol *derived)
5299 {
5300   if (derived->attr.flavor == FL_DERIVED)
5301     (void) check_class_members (derived);
5302 }
5303
5304
5305 static gfc_try 
5306 check_class_members (gfc_symbol *derived)
5307 {
5308   gfc_expr *e;
5309   gfc_symtree *tbp;
5310   gfc_class_esym_list *etmp;
5311
5312   e = gfc_copy_expr (list_e);
5313
5314   tbp = gfc_find_typebound_proc (derived, &class_try,
5315                                  e->value.compcall.name,
5316                                  false, &e->where);
5317
5318   if (tbp == NULL)
5319     {
5320       gfc_error ("no typebound available procedure named '%s' at %L",
5321                  e->value.compcall.name, &e->where);
5322       return FAILURE;
5323     }
5324
5325   /* If we have to match a passed class member, force the actual
5326       expression to have the correct type.  */
5327   if (!tbp->n.tb->nopass)
5328     {
5329       if (e->value.compcall.base_object == NULL)
5330         e->value.compcall.base_object = extract_compcall_passed_object (e);
5331
5332       if (e->value.compcall.base_object == NULL)
5333         return FAILURE;
5334
5335       if (!derived->attr.abstract)
5336         {
5337           e->value.compcall.base_object->ts.type = BT_DERIVED;
5338           e->value.compcall.base_object->ts.u.derived = derived;
5339         }
5340     }
5341
5342   e->value.compcall.tbp = tbp->n.tb;
5343   e->value.compcall.name = tbp->name;
5344
5345   /* Let the original expresssion catch the assertion in
5346      resolve_compcall, since this flag does not appear to be reset or
5347      copied in some systems.  */
5348   e->value.compcall.assign = 0;
5349
5350   /* Do the renaming, PASSing, generic => specific and other
5351      good things for each class member.  */
5352   class_try = (resolve_compcall (e, fcn_flag, true) == SUCCESS)
5353                                 ? class_try : FAILURE;
5354
5355   /* Now transfer the found symbol to the esym list.  */
5356   if (class_try == SUCCESS)
5357     {
5358       etmp = list_e->value.function.class_esym;
5359       list_e->value.function.class_esym
5360                 = gfc_get_class_esym_list();
5361       list_e->value.function.class_esym->next = etmp;
5362       list_e->value.function.class_esym->derived = derived;
5363       list_e->value.function.class_esym->esym
5364                 = e->value.function.esym;
5365     }
5366
5367   gfc_free_expr (e);
5368   
5369   /* Burrow down into grandchildren types.  */
5370   if (derived->f2k_derived)
5371     gfc_traverse_ns (derived->f2k_derived, check_members);
5372
5373   return SUCCESS;
5374 }
5375
5376
5377 /* Eliminate esym_lists where all the members point to the
5378    typebound procedure of the declared type; ie. one where
5379    type selection has no effect..  */
5380 static void
5381 resolve_class_esym (gfc_expr *e)
5382 {
5383   gfc_class_esym_list *p, *q;
5384   bool empty = true;
5385
5386   gcc_assert (e && e->expr_type == EXPR_FUNCTION);
5387
5388   p = e->value.function.class_esym;
5389   if (p == NULL)
5390     return;
5391
5392   for (; p; p = p->next)
5393     empty = empty && (e->value.function.esym == p->esym);
5394
5395   if (empty)
5396     {
5397       p = e->value.function.class_esym;
5398       for (; p; p = q)
5399         {
5400           q = p->next;
5401           gfc_free (p);
5402         }
5403       e->value.function.class_esym = NULL;
5404    }
5405 }
5406
5407
5408 /* Generate an expression for the hash value, given the reference to
5409    the class of the final expression (class_ref), the base of the
5410    full reference list (new_ref), the declared type and the class
5411    object (st).  */
5412 static gfc_expr*
5413 hash_value_expr (gfc_ref *class_ref, gfc_ref *new_ref, gfc_symtree *st)
5414 {
5415   gfc_expr *hash_value;
5416
5417   /* Build an expression for the correct hash_value; ie. that of the last
5418      CLASS reference.  */
5419   if (class_ref)
5420     {
5421       class_ref->next = NULL;
5422     }
5423   else
5424     {
5425       gfc_free_ref_list (new_ref);
5426       new_ref = NULL;
5427     }
5428   hash_value = gfc_get_expr ();
5429   hash_value->expr_type = EXPR_VARIABLE;
5430   hash_value->symtree = st;
5431   hash_value->symtree->n.sym->refs++;
5432   hash_value->ref = new_ref;
5433   gfc_add_component_ref (hash_value, "$vptr");
5434   gfc_add_component_ref (hash_value, "$hash");
5435
5436   return hash_value;
5437 }
5438
5439
5440 /* Get the ultimate declared type from an expression.  In addition,
5441    return the last class/derived type reference and the copy of the
5442    reference list.  */
5443 static gfc_symbol*
5444 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5445                         gfc_expr *e)
5446 {
5447   gfc_symbol *declared;
5448   gfc_ref *ref;
5449
5450   declared = NULL;
5451   *class_ref = NULL;
5452   *new_ref = gfc_copy_ref (e->ref);
5453   for (ref = *new_ref; ref; ref = ref->next)
5454     {
5455       if (ref->type != REF_COMPONENT)
5456         continue;
5457
5458       if (ref->u.c.component->ts.type == BT_CLASS
5459             || ref->u.c.component->ts.type == BT_DERIVED)
5460         {
5461           declared = ref->u.c.component->ts.u.derived;
5462           *class_ref = ref;
5463         }
5464     }
5465
5466   if (declared == NULL)
5467     declared = e->symtree->n.sym->ts.u.derived;
5468
5469   return declared;
5470 }
5471
5472
5473 /* Resolve the argument expressions so that any arguments expressions
5474    that include class methods are resolved before the current call.
5475    This is necessary because of the static variables used in CLASS
5476    method resolution.  */
5477 static void
5478 resolve_arg_exprs (gfc_actual_arglist *arg)
5479
5480   /* Resolve the actual arglist expressions.  */
5481   for (; arg; arg = arg->next)
5482     {
5483       if (arg->expr)
5484         gfc_resolve_expr (arg->expr);
5485     }
5486 }
5487
5488
5489 /* Resolve a typebound function, or 'method'.  First separate all
5490    the non-CLASS references by calling resolve_compcall directly.
5491    Then treat the CLASS references by resolving for each of the class
5492    members in turn.  */
5493
5494 static gfc_try
5495 resolve_typebound_function (gfc_expr* e)
5496 {
5497   gfc_symbol *derived, *declared;
5498   gfc_ref *new_ref;
5499   gfc_ref *class_ref;
5500   gfc_symtree *st;
5501
5502   st = e->symtree;
5503   if (st == NULL)
5504     return resolve_compcall (e, true, false);
5505
5506   /* Get the CLASS declared type.  */
5507   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5508
5509   /* Weed out cases of the ultimate component being a derived type.  */
5510   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5511         || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5512     {
5513       gfc_free_ref_list (new_ref);
5514       return resolve_compcall (e, true, false);
5515     }
5516
5517   /* Resolve the argument expressions,  */
5518   resolve_arg_exprs (e->value.function.actual); 
5519
5520   /* Get the data component, which is of the declared type.  */
5521   derived = declared->components->ts.u.derived;
5522
5523   /* Resolve the function call for each member of the class.  */
5524   class_try = SUCCESS;
5525   fcn_flag = true;
5526   list_e = gfc_copy_expr (e);
5527
5528   if (check_class_members (derived) == FAILURE)
5529     return FAILURE;
5530
5531   class_try = (resolve_compcall (e, true, false) == SUCCESS)
5532                  ? class_try : FAILURE;
5533
5534   /* Transfer the class list to the original expression.  Note that
5535      the class_esym list is cleaned up in trans-expr.c, as the calls
5536      are translated.  */
5537   e->value.function.class_esym = list_e->value.function.class_esym;
5538   list_e->value.function.class_esym = NULL;
5539   gfc_free_expr (list_e);
5540
5541   resolve_class_esym (e);
5542
5543   /* More than one typebound procedure so transmit an expression for
5544      the hash_value as the selector.  */
5545   if (e->value.function.class_esym != NULL)
5546     e->value.function.class_esym->hash_value
5547                 = hash_value_expr (class_ref, new_ref, st);
5548
5549   return class_try;
5550 }
5551
5552 /* Resolve a typebound subroutine, or 'method'.  First separate all
5553    the non-CLASS references by calling resolve_typebound_call directly.
5554    Then treat the CLASS references by resolving for each of the class
5555    members in turn.  */
5556
5557 static gfc_try
5558 resolve_typebound_subroutine (gfc_code *code)
5559 {
5560   gfc_symbol *derived, *declared;
5561   gfc_ref *new_ref;
5562   gfc_ref *class_ref;
5563   gfc_symtree *st;
5564
5565   st = code->expr1->symtree;
5566   if (st == NULL)
5567     return resolve_typebound_call (code);
5568
5569   /* Get the CLASS declared type.  */
5570   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5571
5572   /* Weed out cases of the ultimate component being a derived type.  */
5573   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5574         || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5575     {
5576       gfc_free_ref_list (new_ref);
5577       return resolve_typebound_call (code);
5578     } 
5579
5580   /* Resolve the argument expressions,  */
5581   resolve_arg_exprs (code->expr1->value.compcall.actual); 
5582
5583   /* Get the data component, which is of the declared type.  */
5584   derived = declared->components->ts.u.derived;
5585
5586   class_try = SUCCESS;
5587   fcn_flag = false;
5588   list_e = gfc_copy_expr (code->expr1);
5589
5590   if (check_class_members (derived) == FAILURE)
5591     return FAILURE;
5592
5593   class_try = (resolve_typebound_call (code) == SUCCESS)
5594                  ? class_try : FAILURE;
5595
5596   /* Transfer the class list to the original expression.  Note that
5597      the class_esym list is cleaned up in trans-expr.c, as the calls
5598      are translated.  */
5599   code->expr1->value.function.class_esym
5600                         = list_e->value.function.class_esym;
5601   list_e->value.function.class_esym = NULL;
5602   gfc_free_expr (list_e);
5603
5604   resolve_class_esym (code->expr1);
5605
5606   /* More than one typebound procedure so transmit an expression for
5607      the hash_value as the selector.  */
5608   if (code->expr1->value.function.class_esym != NULL)
5609     code->expr1->value.function.class_esym->hash_value
5610                 = hash_value_expr (class_ref, new_ref, st);
5611
5612   return class_try;
5613 }
5614
5615
5616 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5617
5618 static gfc_try
5619 resolve_ppc_call (gfc_code* c)
5620 {
5621   gfc_component *comp;
5622   bool b;
5623
5624   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5625   gcc_assert (b);
5626
5627   c->resolved_sym = c->expr1->symtree->n.sym;
5628   c->expr1->expr_type = EXPR_VARIABLE;
5629
5630   if (!comp->attr.subroutine)
5631     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5632
5633   if (resolve_ref (c->expr1) == FAILURE)
5634     return FAILURE;
5635
5636   if (update_ppc_arglist (c->expr1) == FAILURE)
5637     return FAILURE;
5638
5639   c->ext.actual = c->expr1->value.compcall.actual;
5640
5641   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5642                               comp->formal == NULL) == FAILURE)
5643     return FAILURE;
5644
5645   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5646
5647   return SUCCESS;
5648 }
5649
5650
5651 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5652
5653 static gfc_try
5654 resolve_expr_ppc (gfc_expr* e)
5655 {
5656   gfc_component *comp;
5657   bool b;
5658
5659   b = gfc_is_proc_ptr_comp (e, &comp);
5660   gcc_assert (b);
5661
5662   /* Convert to EXPR_FUNCTION.  */
5663   e->expr_type = EXPR_FUNCTION;
5664   e->value.function.isym = NULL;
5665   e->value.function.actual = e->value.compcall.actual;
5666   e->ts = comp->ts;
5667   if (comp->as != NULL)
5668     e->rank = comp->as->rank;
5669
5670   if (!comp->attr.function)
5671     gfc_add_function (&comp->attr, comp->name, &e->where);
5672
5673   if (resolve_ref (e) == FAILURE)
5674     return FAILURE;
5675
5676   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5677                               comp->formal == NULL) == FAILURE)
5678     return FAILURE;
5679
5680   if (update_ppc_arglist (e) == FAILURE)
5681     return FAILURE;
5682
5683   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5684
5685   return SUCCESS;
5686 }
5687
5688
5689 static bool
5690 gfc_is_expandable_expr (gfc_expr *e)
5691 {
5692   gfc_constructor *con;
5693
5694   if (e->expr_type == EXPR_ARRAY)
5695     {
5696       /* Traverse the constructor looking for variables that are flavor
5697          parameter.  Parameters must be expanded since they are fully used at
5698          compile time.  */
5699       con = gfc_constructor_first (e->value.constructor);
5700       for (; con; con = gfc_constructor_next (con))
5701         {
5702           if (con->expr->expr_type == EXPR_VARIABLE
5703               && con->expr->symtree
5704               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5705               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5706             return true;
5707           if (con->expr->expr_type == EXPR_ARRAY
5708               && gfc_is_expandable_expr (con->expr))
5709             return true;
5710         }
5711     }
5712
5713   return false;
5714 }
5715
5716 /* Resolve an expression.  That is, make sure that types of operands agree
5717    with their operators, intrinsic operators are converted to function calls
5718    for overloaded types and unresolved function references are resolved.  */
5719
5720 gfc_try
5721 gfc_resolve_expr (gfc_expr *e)
5722 {
5723   gfc_try t;
5724   bool inquiry_save;
5725
5726   if (e == NULL)
5727     return SUCCESS;
5728
5729   /* inquiry_argument only applies to variables.  */
5730   inquiry_save = inquiry_argument;
5731   if (e->expr_type != EXPR_VARIABLE)
5732     inquiry_argument = false;
5733
5734   switch (e->expr_type)
5735     {
5736     case EXPR_OP:
5737       t = resolve_operator (e);
5738       break;
5739
5740     case EXPR_FUNCTION:
5741     case EXPR_VARIABLE:
5742
5743       if (check_host_association (e))
5744         t = resolve_function (e);
5745       else
5746         {
5747           t = resolve_variable (e);
5748           if (t == SUCCESS)
5749             expression_rank (e);
5750         }
5751
5752       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5753           && e->ref->type != REF_SUBSTRING)
5754         gfc_resolve_substring_charlen (e);
5755
5756       break;
5757
5758     case EXPR_COMPCALL:
5759       t = resolve_typebound_function (e);
5760       break;
5761
5762     case EXPR_SUBSTRING:
5763       t = resolve_ref (e);
5764       break;
5765
5766     case EXPR_CONSTANT:
5767     case EXPR_NULL:
5768       t = SUCCESS;
5769       break;
5770
5771     case EXPR_PPC:
5772       t = resolve_expr_ppc (e);
5773       break;
5774
5775     case EXPR_ARRAY:
5776       t = FAILURE;
5777       if (resolve_ref (e) == FAILURE)
5778         break;
5779
5780       t = gfc_resolve_array_constructor (e);
5781       /* Also try to expand a constructor.  */
5782       if (t == SUCCESS)
5783         {
5784           expression_rank (e);
5785           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5786             gfc_expand_constructor (e);
5787         }
5788
5789       /* This provides the opportunity for the length of constructors with
5790          character valued function elements to propagate the string length
5791          to the expression.  */
5792       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5793         {
5794           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5795              here rather then add a duplicate test for it above.  */ 
5796           gfc_expand_constructor (e);
5797           t = gfc_resolve_character_array_constructor (e);
5798         }
5799
5800       break;
5801
5802     case EXPR_STRUCTURE:
5803       t = resolve_ref (e);
5804       if (t == FAILURE)
5805         break;
5806
5807       t = resolve_structure_cons (e);
5808       if (t == FAILURE)
5809         break;
5810
5811       t = gfc_simplify_expr (e, 0);
5812       break;
5813
5814     default:
5815       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5816     }
5817
5818   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5819     fixup_charlen (e);
5820
5821   inquiry_argument = inquiry_save;
5822
5823   return t;
5824 }
5825
5826
5827 /* Resolve an expression from an iterator.  They must be scalar and have
5828    INTEGER or (optionally) REAL type.  */
5829
5830 static gfc_try
5831 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5832                            const char *name_msgid)
5833 {
5834   if (gfc_resolve_expr (expr) == FAILURE)
5835     return FAILURE;
5836
5837   if (expr->rank != 0)
5838     {
5839       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5840       return FAILURE;
5841     }
5842
5843   if (expr->ts.type != BT_INTEGER)
5844     {
5845       if (expr->ts.type == BT_REAL)
5846         {
5847           if (real_ok)
5848             return gfc_notify_std (GFC_STD_F95_DEL,
5849                                    "Deleted feature: %s at %L must be integer",
5850                                    _(name_msgid), &expr->where);
5851           else
5852             {
5853               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5854                          &expr->where);
5855               return FAILURE;
5856             }
5857         }
5858       else
5859         {
5860           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5861           return FAILURE;
5862         }
5863     }
5864   return SUCCESS;
5865 }
5866
5867
5868 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5869    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5870
5871 gfc_try
5872 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5873 {
5874   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5875       == FAILURE)
5876     return FAILURE;
5877
5878   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5879     {
5880       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5881                  &iter->var->where);
5882       return FAILURE;
5883     }
5884
5885   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5886                                  "Start expression in DO loop") == FAILURE)
5887     return FAILURE;
5888
5889   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5890                                  "End expression in DO loop") == FAILURE)
5891     return FAILURE;
5892
5893   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5894                                  "Step expression in DO loop") == FAILURE)
5895     return FAILURE;
5896
5897   if (iter->step->expr_type == EXPR_CONSTANT)
5898     {
5899       if ((iter->step->ts.type == BT_INTEGER
5900            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5901           || (iter->step->ts.type == BT_REAL
5902               && mpfr_sgn (iter->step->value.real) == 0))
5903         {
5904           gfc_error ("Step expression in DO loop at %L cannot be zero",
5905                      &iter->step->where);
5906           return FAILURE;
5907         }
5908     }
5909
5910   /* Convert start, end, and step to the same type as var.  */
5911   if (iter->start->ts.kind != iter->var->ts.kind
5912       || iter->start->ts.type != iter->var->ts.type)
5913     gfc_convert_type (iter->start, &iter->var->ts, 2);
5914
5915   if (iter->end->ts.kind != iter->var->ts.kind
5916       || iter->end->ts.type != iter->var->ts.type)
5917     gfc_convert_type (iter->end, &iter->var->ts, 2);
5918
5919   if (iter->step->ts.kind != iter->var->ts.kind
5920       || iter->step->ts.type != iter->var->ts.type)
5921     gfc_convert_type (iter->step, &iter->var->ts, 2);
5922
5923   if (iter->start->expr_type == EXPR_CONSTANT
5924       && iter->end->expr_type == EXPR_CONSTANT
5925       && iter->step->expr_type == EXPR_CONSTANT)
5926     {
5927       int sgn, cmp;
5928       if (iter->start->ts.type == BT_INTEGER)
5929         {
5930           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5931           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5932         }
5933       else
5934         {
5935           sgn = mpfr_sgn (iter->step->value.real);
5936           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5937         }
5938       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5939         gfc_warning ("DO loop at %L will be executed zero times",
5940                      &iter->step->where);
5941     }
5942
5943   return SUCCESS;
5944 }
5945
5946
5947 /* Traversal function for find_forall_index.  f == 2 signals that
5948    that variable itself is not to be checked - only the references.  */
5949
5950 static bool
5951 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5952 {
5953   if (expr->expr_type != EXPR_VARIABLE)
5954     return false;
5955   
5956   /* A scalar assignment  */
5957   if (!expr->ref || *f == 1)
5958     {
5959       if (expr->symtree->n.sym == sym)
5960         return true;
5961       else
5962         return false;
5963     }
5964
5965   if (*f == 2)
5966     *f = 1;
5967   return false;
5968 }
5969
5970
5971 /* Check whether the FORALL index appears in the expression or not.
5972    Returns SUCCESS if SYM is found in EXPR.  */
5973
5974 gfc_try
5975 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5976 {
5977   if (gfc_traverse_expr (expr, sym, forall_index, f))
5978     return SUCCESS;
5979   else
5980     return FAILURE;
5981 }
5982
5983
5984 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5985    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5986    INTEGERs, and if stride is a constant it must be nonzero.
5987    Furthermore "A subscript or stride in a forall-triplet-spec shall
5988    not contain a reference to any index-name in the
5989    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5990
5991 static void
5992 resolve_forall_iterators (gfc_forall_iterator *it)
5993 {
5994   gfc_forall_iterator *iter, *iter2;
5995
5996   for (iter = it; iter; iter = iter->next)
5997     {
5998       if (gfc_resolve_expr (iter->var) == SUCCESS
5999           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6000         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6001                    &iter->var->where);
6002
6003       if (gfc_resolve_expr (iter->start) == SUCCESS
6004           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6005         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6006                    &iter->start->where);
6007       if (iter->var->ts.kind != iter->start->ts.kind)
6008         gfc_convert_type (iter->start, &iter->var->ts, 2);
6009
6010       if (gfc_resolve_expr (iter->end) == SUCCESS
6011           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6012         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6013                    &iter->end->where);
6014       if (iter->var->ts.kind != iter->end->ts.kind)
6015         gfc_convert_type (iter->end, &iter->var->ts, 2);
6016
6017       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6018         {
6019           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6020             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6021                        &iter->stride->where, "INTEGER");
6022
6023           if (iter->stride->expr_type == EXPR_CONSTANT
6024               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6025             gfc_error ("FORALL stride expression at %L cannot be zero",
6026                        &iter->stride->where);
6027         }
6028       if (iter->var->ts.kind != iter->stride->ts.kind)
6029         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6030     }
6031
6032   for (iter = it; iter; iter = iter->next)
6033     for (iter2 = iter; iter2; iter2 = iter2->next)
6034       {
6035         if (find_forall_index (iter2->start,
6036                                iter->var->symtree->n.sym, 0) == SUCCESS
6037             || find_forall_index (iter2->end,
6038                                   iter->var->symtree->n.sym, 0) == SUCCESS
6039             || find_forall_index (iter2->stride,
6040                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6041           gfc_error ("FORALL index '%s' may not appear in triplet "
6042                      "specification at %L", iter->var->symtree->name,
6043                      &iter2->start->where);
6044       }
6045 }
6046
6047
6048 /* Given a pointer to a symbol that is a derived type, see if it's
6049    inaccessible, i.e. if it's defined in another module and the components are
6050    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6051    inaccessible components are found, nonzero otherwise.  */
6052
6053 static int
6054 derived_inaccessible (gfc_symbol *sym)
6055 {
6056   gfc_component *c;
6057
6058   if (sym->attr.use_assoc && sym->attr.private_comp)
6059     return 1;
6060
6061   for (c = sym->components; c; c = c->next)
6062     {
6063         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6064           return 1;
6065     }
6066
6067   return 0;
6068 }
6069
6070
6071 /* Resolve the argument of a deallocate expression.  The expression must be
6072    a pointer or a full array.  */
6073
6074 static gfc_try
6075 resolve_deallocate_expr (gfc_expr *e)
6076 {
6077   symbol_attribute attr;
6078   int allocatable, pointer, check_intent_in;
6079   gfc_ref *ref;
6080   gfc_symbol *sym;
6081   gfc_component *c;
6082
6083   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6084   check_intent_in = 1;
6085
6086   if (gfc_resolve_expr (e) == FAILURE)
6087     return FAILURE;
6088
6089   if (e->expr_type != EXPR_VARIABLE)
6090     goto bad;
6091
6092   sym = e->symtree->n.sym;
6093
6094   if (sym->ts.type == BT_CLASS)
6095     {
6096       allocatable = sym->ts.u.derived->components->attr.allocatable;
6097       pointer = sym->ts.u.derived->components->attr.pointer;
6098     }
6099   else
6100     {
6101       allocatable = sym->attr.allocatable;
6102       pointer = sym->attr.pointer;
6103     }
6104   for (ref = e->ref; ref; ref = ref->next)
6105     {
6106       if (pointer)
6107         check_intent_in = 0;
6108
6109       switch (ref->type)
6110         {
6111         case REF_ARRAY:
6112           if (ref->u.ar.type != AR_FULL)
6113             allocatable = 0;
6114           break;
6115
6116         case REF_COMPONENT:
6117           c = ref->u.c.component;
6118           if (c->ts.type == BT_CLASS)
6119             {
6120               allocatable = c->ts.u.derived->components->attr.allocatable;
6121               pointer = c->ts.u.derived->components->attr.pointer;
6122             }
6123           else
6124             {
6125               allocatable = c->attr.allocatable;
6126               pointer = c->attr.pointer;
6127             }
6128           break;
6129
6130         case REF_SUBSTRING:
6131           allocatable = 0;
6132           break;
6133         }
6134     }
6135
6136   attr = gfc_expr_attr (e);
6137
6138   if (allocatable == 0 && attr.pointer == 0)
6139     {
6140     bad:
6141       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6142                  &e->where);
6143     }
6144
6145   if (check_intent_in && sym->attr.intent == INTENT_IN)
6146     {
6147       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
6148                  sym->name, &e->where);
6149       return FAILURE;
6150     }
6151
6152   if (e->ts.type == BT_CLASS)
6153     {
6154       /* Only deallocate the DATA component.  */
6155       gfc_add_component_ref (e, "$data");
6156     }
6157
6158   return SUCCESS;
6159 }
6160
6161
6162 /* Returns true if the expression e contains a reference to the symbol sym.  */
6163 static bool
6164 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6165 {
6166   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6167     return true;
6168
6169   return false;
6170 }
6171
6172 bool
6173 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6174 {
6175   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6176 }
6177
6178
6179 /* Given the expression node e for an allocatable/pointer of derived type to be
6180    allocated, get the expression node to be initialized afterwards (needed for
6181    derived types with default initializers, and derived types with allocatable
6182    components that need nullification.)  */
6183
6184 gfc_expr *
6185 gfc_expr_to_initialize (gfc_expr *e)
6186 {
6187   gfc_expr *result;
6188   gfc_ref *ref;
6189   int i;
6190
6191   result = gfc_copy_expr (e);
6192
6193   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6194   for (ref = result->ref; ref; ref = ref->next)
6195     if (ref->type == REF_ARRAY && ref->next == NULL)
6196       {
6197         ref->u.ar.type = AR_FULL;
6198
6199         for (i = 0; i < ref->u.ar.dimen; i++)
6200           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6201
6202         result->rank = ref->u.ar.dimen;
6203         break;
6204       }
6205
6206   return result;
6207 }
6208
6209
6210 /* Used in resolve_allocate_expr to check that a allocation-object and
6211    a source-expr are conformable.  This does not catch all possible 
6212    cases; in particular a runtime checking is needed.  */
6213
6214 static gfc_try
6215 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6216 {
6217   /* First compare rank.  */
6218   if (e2->ref && e1->rank != e2->ref->u.ar.as->rank)
6219     {
6220       gfc_error ("Source-expr at %L must be scalar or have the "
6221                  "same rank as the allocate-object at %L",
6222                  &e1->where, &e2->where);
6223       return FAILURE;
6224     }
6225
6226   if (e1->shape)
6227     {
6228       int i;
6229       mpz_t s;
6230
6231       mpz_init (s);
6232
6233       for (i = 0; i < e1->rank; i++)
6234         {
6235           if (e2->ref->u.ar.end[i])
6236             {
6237               mpz_set (s, e2->ref->u.ar.end[i]->value.integer);
6238               mpz_sub (s, s, e2->ref->u.ar.start[i]->value.integer);
6239               mpz_add_ui (s, s, 1);
6240             }
6241           else
6242             {
6243               mpz_set (s, e2->ref->u.ar.start[i]->value.integer);
6244             }
6245
6246           if (mpz_cmp (e1->shape[i], s) != 0)
6247             {
6248               gfc_error ("Source-expr at %L and allocate-object at %L must "
6249                          "have the same shape", &e1->where, &e2->where);
6250               mpz_clear (s);
6251               return FAILURE;
6252             }
6253         }
6254
6255       mpz_clear (s);
6256     }
6257
6258   return SUCCESS;
6259 }
6260
6261
6262 /* Resolve the expression in an ALLOCATE statement, doing the additional
6263    checks to see whether the expression is OK or not.  The expression must
6264    have a trailing array reference that gives the size of the array.  */
6265
6266 static gfc_try
6267 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6268 {
6269   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6270   int codimension;
6271   symbol_attribute attr;
6272   gfc_ref *ref, *ref2;
6273   gfc_array_ref *ar;
6274   gfc_symbol *sym;
6275   gfc_alloc *a;
6276   gfc_component *c;
6277   gfc_expr *init_e;
6278
6279   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6280   check_intent_in = 1;
6281
6282   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6283      checking of coarrays.  */
6284   for (ref = e->ref; ref; ref = ref->next)
6285     if (ref->next == NULL)
6286       break;
6287
6288   if (ref && ref->type == REF_ARRAY)
6289     ref->u.ar.in_allocate = true;
6290
6291   if (gfc_resolve_expr (e) == FAILURE)
6292     goto failure;
6293
6294   /* Make sure the expression is allocatable or a pointer.  If it is
6295      pointer, the next-to-last reference must be a pointer.  */
6296
6297   ref2 = NULL;
6298   if (e->symtree)
6299     sym = e->symtree->n.sym;
6300
6301   /* Check whether ultimate component is abstract and CLASS.  */
6302   is_abstract = 0;
6303
6304   if (e->expr_type != EXPR_VARIABLE)
6305     {
6306       allocatable = 0;
6307       attr = gfc_expr_attr (e);
6308       pointer = attr.pointer;
6309       dimension = attr.dimension;
6310       codimension = attr.codimension;
6311     }
6312   else
6313     {
6314       if (sym->ts.type == BT_CLASS)
6315         {
6316           allocatable = sym->ts.u.derived->components->attr.allocatable;
6317           pointer = sym->ts.u.derived->components->attr.pointer;
6318           dimension = sym->ts.u.derived->components->attr.dimension;
6319           codimension = sym->ts.u.derived->components->attr.codimension;
6320           is_abstract = sym->ts.u.derived->components->attr.abstract;
6321         }
6322       else
6323         {
6324           allocatable = sym->attr.allocatable;
6325           pointer = sym->attr.pointer;
6326           dimension = sym->attr.dimension;
6327           codimension = sym->attr.codimension;
6328         }
6329
6330       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6331         {
6332           if (pointer)
6333             check_intent_in = 0;
6334
6335           switch (ref->type)
6336             {
6337               case REF_ARRAY:
6338                 if (ref->next != NULL)
6339                   pointer = 0;
6340                 break;
6341
6342               case REF_COMPONENT:
6343                 /* F2008, C644.  */
6344                 if (gfc_is_coindexed (e))
6345                   {
6346                     gfc_error ("Coindexed allocatable object at %L",
6347                                &e->where);
6348                     goto failure;
6349                   }
6350
6351                 c = ref->u.c.component;
6352                 if (c->ts.type == BT_CLASS)
6353                   {
6354                     allocatable = c->ts.u.derived->components->attr.allocatable;
6355                     pointer = c->ts.u.derived->components->attr.pointer;
6356                     dimension = c->ts.u.derived->components->attr.dimension;
6357                     codimension = c->ts.u.derived->components->attr.codimension;
6358                     is_abstract = c->ts.u.derived->components->attr.abstract;
6359                   }
6360                 else
6361                   {
6362                     allocatable = c->attr.allocatable;
6363                     pointer = c->attr.pointer;
6364                     dimension = c->attr.dimension;
6365                     codimension = c->attr.codimension;
6366                     is_abstract = c->attr.abstract;
6367                   }
6368                 break;
6369
6370               case REF_SUBSTRING:
6371                 allocatable = 0;
6372                 pointer = 0;
6373                 break;
6374             }
6375         }
6376     }
6377
6378   if (allocatable == 0 && pointer == 0)
6379     {
6380       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6381                  &e->where);
6382       goto failure;
6383     }
6384
6385   /* Some checks for the SOURCE tag.  */
6386   if (code->expr3)
6387     {
6388       /* Check F03:C631.  */
6389       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6390         {
6391           gfc_error ("Type of entity at %L is type incompatible with "
6392                       "source-expr at %L", &e->where, &code->expr3->where);
6393           goto failure;
6394         }
6395
6396       /* Check F03:C632 and restriction following Note 6.18.  */
6397       if (code->expr3->rank > 0
6398           && conformable_arrays (code->expr3, e) == FAILURE)
6399         goto failure;
6400
6401       /* Check F03:C633.  */
6402       if (code->expr3->ts.kind != e->ts.kind)
6403         {
6404           gfc_error ("The allocate-object at %L and the source-expr at %L "
6405                       "shall have the same kind type parameter",
6406                       &e->where, &code->expr3->where);
6407           goto failure;
6408         }
6409     }
6410   else if (is_abstract&& code->ext.alloc.ts.type == BT_UNKNOWN)
6411     {
6412       gcc_assert (e->ts.type == BT_CLASS);
6413       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6414                  "type-spec or SOURCE=", sym->name, &e->where);
6415       goto failure;
6416     }
6417
6418   if (check_intent_in && sym->attr.intent == INTENT_IN)
6419     {
6420       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6421                  sym->name, &e->where);
6422       goto failure;
6423     }
6424     
6425   if (!code->expr3)
6426     {
6427       /* Add default initializer for those derived types that need them.  */
6428       if (e->ts.type == BT_DERIVED
6429           && (init_e = gfc_default_initializer (&e->ts)))
6430         {
6431           gfc_code *init_st = gfc_get_code ();
6432           init_st->loc = code->loc;
6433           init_st->op = EXEC_INIT_ASSIGN;
6434           init_st->expr1 = gfc_expr_to_initialize (e);
6435           init_st->expr2 = init_e;
6436           init_st->next = code->next;
6437           code->next = init_st;
6438         }
6439       else if (e->ts.type == BT_CLASS
6440                && ((code->ext.alloc.ts.type == BT_UNKNOWN
6441                     && (init_e = gfc_default_initializer (&e->ts.u.derived->components->ts)))
6442                    || (code->ext.alloc.ts.type == BT_DERIVED
6443                        && (init_e = gfc_default_initializer (&code->ext.alloc.ts)))))
6444         {
6445           gfc_code *init_st = gfc_get_code ();
6446           init_st->loc = code->loc;
6447           init_st->op = EXEC_INIT_ASSIGN;
6448           init_st->expr1 = gfc_expr_to_initialize (e);
6449           init_st->expr2 = init_e;
6450           init_st->next = code->next;
6451           code->next = init_st;
6452         }
6453     }
6454
6455   if (pointer || (dimension == 0 && codimension == 0))
6456     goto success;
6457
6458   /* Make sure the next-to-last reference node is an array specification.  */
6459
6460   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6461       || (dimension && ref2->u.ar.dimen == 0))
6462     {
6463       gfc_error ("Array specification required in ALLOCATE statement "
6464                  "at %L", &e->where);
6465       goto failure;
6466     }
6467
6468   /* Make sure that the array section reference makes sense in the
6469     context of an ALLOCATE specification.  */
6470
6471   ar = &ref2->u.ar;
6472
6473   if (codimension && ar->codimen == 0)
6474     {
6475       gfc_error ("Coarray specification required in ALLOCATE statement "
6476                  "at %L", &e->where);
6477       goto failure;
6478     }
6479
6480   for (i = 0; i < ar->dimen; i++)
6481     {
6482       if (ref2->u.ar.type == AR_ELEMENT)
6483         goto check_symbols;
6484
6485       switch (ar->dimen_type[i])
6486         {
6487         case DIMEN_ELEMENT:
6488           break;
6489
6490         case DIMEN_RANGE:
6491           if (ar->start[i] != NULL
6492               && ar->end[i] != NULL
6493               && ar->stride[i] == NULL)
6494             break;
6495
6496           /* Fall Through...  */
6497
6498         case DIMEN_UNKNOWN:
6499         case DIMEN_VECTOR:
6500         case DIMEN_STAR:
6501           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6502                      &e->where);
6503           goto failure;
6504         }
6505
6506 check_symbols:
6507       for (a = code->ext.alloc.list; a; a = a->next)
6508         {
6509           sym = a->expr->symtree->n.sym;
6510
6511           /* TODO - check derived type components.  */
6512           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6513             continue;
6514
6515           if ((ar->start[i] != NULL
6516                && gfc_find_sym_in_expr (sym, ar->start[i]))
6517               || (ar->end[i] != NULL
6518                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6519             {
6520               gfc_error ("'%s' must not appear in the array specification at "
6521                          "%L in the same ALLOCATE statement where it is "
6522                          "itself allocated", sym->name, &ar->where);
6523               goto failure;
6524             }
6525         }
6526     }
6527
6528   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6529     {
6530       if (ar->dimen_type[i] == DIMEN_ELEMENT
6531           || ar->dimen_type[i] == DIMEN_RANGE)
6532         {
6533           if (i == (ar->dimen + ar->codimen - 1))
6534             {
6535               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6536                          "statement at %L", &e->where);
6537               goto failure;
6538             }
6539           break;
6540         }
6541
6542       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6543           && ar->stride[i] == NULL)
6544         break;
6545
6546       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6547                  &e->where);
6548       goto failure;
6549     }
6550
6551   if (codimension)
6552     {
6553       gfc_error ("Sorry, allocatable coarrays are no yet supported coarray "
6554                  "at %L", &e->where);
6555       goto failure;
6556     }
6557
6558 success:
6559   return SUCCESS;
6560
6561 failure:
6562   return FAILURE;
6563 }
6564
6565 static void
6566 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6567 {
6568   gfc_expr *stat, *errmsg, *pe, *qe;
6569   gfc_alloc *a, *p, *q;
6570
6571   stat = code->expr1 ? code->expr1 : NULL;
6572
6573   errmsg = code->expr2 ? code->expr2 : NULL;
6574
6575   /* Check the stat variable.  */
6576   if (stat)
6577     {
6578       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6579         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6580                    stat->symtree->n.sym->name, &stat->where);
6581
6582       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6583         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6584                    &stat->where);
6585
6586       if ((stat->ts.type != BT_INTEGER
6587            && !(stat->ref && (stat->ref->type == REF_ARRAY
6588                               || stat->ref->type == REF_COMPONENT)))
6589           || stat->rank > 0)
6590         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6591                    "variable", &stat->where);
6592
6593       for (p = code->ext.alloc.list; p; p = p->next)
6594         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6595           gfc_error ("Stat-variable at %L shall not be %sd within "
6596                      "the same %s statement", &stat->where, fcn, fcn);
6597     }
6598
6599   /* Check the errmsg variable.  */
6600   if (errmsg)
6601     {
6602       if (!stat)
6603         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6604                      &errmsg->where);
6605
6606       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6607         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6608                    errmsg->symtree->n.sym->name, &errmsg->where);
6609
6610       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6611         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6612                    &errmsg->where);
6613
6614       if ((errmsg->ts.type != BT_CHARACTER
6615            && !(errmsg->ref
6616                 && (errmsg->ref->type == REF_ARRAY
6617                     || errmsg->ref->type == REF_COMPONENT)))
6618           || errmsg->rank > 0 )
6619         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6620                    "variable", &errmsg->where);
6621
6622       for (p = code->ext.alloc.list; p; p = p->next)
6623         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6624           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6625                      "the same %s statement", &errmsg->where, fcn, fcn);
6626     }
6627
6628   /* Check that an allocate-object appears only once in the statement.  
6629      FIXME: Checking derived types is disabled.  */
6630   for (p = code->ext.alloc.list; p; p = p->next)
6631     {
6632       pe = p->expr;
6633       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6634            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6635         {
6636           for (q = p->next; q; q = q->next)
6637             {
6638               qe = q->expr;
6639               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6640                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6641                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6642                 gfc_error ("Allocate-object at %L also appears at %L",
6643                            &pe->where, &qe->where);
6644             }
6645         }
6646     }
6647
6648   if (strcmp (fcn, "ALLOCATE") == 0)
6649     {
6650       for (a = code->ext.alloc.list; a; a = a->next)
6651         resolve_allocate_expr (a->expr, code);
6652     }
6653   else
6654     {
6655       for (a = code->ext.alloc.list; a; a = a->next)
6656         resolve_deallocate_expr (a->expr);
6657     }
6658 }
6659
6660
6661 /************ SELECT CASE resolution subroutines ************/
6662
6663 /* Callback function for our mergesort variant.  Determines interval
6664    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6665    op1 > op2.  Assumes we're not dealing with the default case.  
6666    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6667    There are nine situations to check.  */
6668
6669 static int
6670 compare_cases (const gfc_case *op1, const gfc_case *op2)
6671 {
6672   int retval;
6673
6674   if (op1->low == NULL) /* op1 = (:L)  */
6675     {
6676       /* op2 = (:N), so overlap.  */
6677       retval = 0;
6678       /* op2 = (M:) or (M:N),  L < M  */
6679       if (op2->low != NULL
6680           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6681         retval = -1;
6682     }
6683   else if (op1->high == NULL) /* op1 = (K:)  */
6684     {
6685       /* op2 = (M:), so overlap.  */
6686       retval = 0;
6687       /* op2 = (:N) or (M:N), K > N  */
6688       if (op2->high != NULL
6689           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6690         retval = 1;
6691     }
6692   else /* op1 = (K:L)  */
6693     {
6694       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6695         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6696                  ? 1 : 0;
6697       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6698         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6699                  ? -1 : 0;
6700       else                      /* op2 = (M:N)  */
6701         {
6702           retval =  0;
6703           /* L < M  */
6704           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6705             retval =  -1;
6706           /* K > N  */
6707           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6708             retval =  1;
6709         }
6710     }
6711
6712   return retval;
6713 }
6714
6715
6716 /* Merge-sort a double linked case list, detecting overlap in the
6717    process.  LIST is the head of the double linked case list before it
6718    is sorted.  Returns the head of the sorted list if we don't see any
6719    overlap, or NULL otherwise.  */
6720
6721 static gfc_case *
6722 check_case_overlap (gfc_case *list)
6723 {
6724   gfc_case *p, *q, *e, *tail;
6725   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6726
6727   /* If the passed list was empty, return immediately.  */
6728   if (!list)
6729     return NULL;
6730
6731   overlap_seen = 0;
6732   insize = 1;
6733
6734   /* Loop unconditionally.  The only exit from this loop is a return
6735      statement, when we've finished sorting the case list.  */
6736   for (;;)
6737     {
6738       p = list;
6739       list = NULL;
6740       tail = NULL;
6741
6742       /* Count the number of merges we do in this pass.  */
6743       nmerges = 0;
6744
6745       /* Loop while there exists a merge to be done.  */
6746       while (p)
6747         {
6748           int i;
6749
6750           /* Count this merge.  */
6751           nmerges++;
6752
6753           /* Cut the list in two pieces by stepping INSIZE places
6754              forward in the list, starting from P.  */
6755           psize = 0;
6756           q = p;
6757           for (i = 0; i < insize; i++)
6758             {
6759               psize++;
6760               q = q->right;
6761               if (!q)
6762                 break;
6763             }
6764           qsize = insize;
6765
6766           /* Now we have two lists.  Merge them!  */
6767           while (psize > 0 || (qsize > 0 && q != NULL))
6768             {
6769               /* See from which the next case to merge comes from.  */
6770               if (psize == 0)
6771                 {
6772                   /* P is empty so the next case must come from Q.  */
6773                   e = q;
6774                   q = q->right;
6775                   qsize--;
6776                 }
6777               else if (qsize == 0 || q == NULL)
6778                 {
6779                   /* Q is empty.  */
6780                   e = p;
6781                   p = p->right;
6782                   psize--;
6783                 }
6784               else
6785                 {
6786                   cmp = compare_cases (p, q);
6787                   if (cmp < 0)
6788                     {
6789                       /* The whole case range for P is less than the
6790                          one for Q.  */
6791                       e = p;
6792                       p = p->right;
6793                       psize--;
6794                     }
6795                   else if (cmp > 0)
6796                     {
6797                       /* The whole case range for Q is greater than
6798                          the case range for P.  */
6799                       e = q;
6800                       q = q->right;
6801                       qsize--;
6802                     }
6803                   else
6804                     {
6805                       /* The cases overlap, or they are the same
6806                          element in the list.  Either way, we must
6807                          issue an error and get the next case from P.  */
6808                       /* FIXME: Sort P and Q by line number.  */
6809                       gfc_error ("CASE label at %L overlaps with CASE "
6810                                  "label at %L", &p->where, &q->where);
6811                       overlap_seen = 1;
6812                       e = p;
6813                       p = p->right;
6814                       psize--;
6815                     }
6816                 }
6817
6818                 /* Add the next element to the merged list.  */
6819               if (tail)
6820                 tail->right = e;
6821               else
6822                 list = e;
6823               e->left = tail;
6824               tail = e;
6825             }
6826
6827           /* P has now stepped INSIZE places along, and so has Q.  So
6828              they're the same.  */
6829           p = q;
6830         }
6831       tail->right = NULL;
6832
6833       /* If we have done only one merge or none at all, we've
6834          finished sorting the cases.  */
6835       if (nmerges <= 1)
6836         {
6837           if (!overlap_seen)
6838             return list;
6839           else
6840             return NULL;
6841         }
6842
6843       /* Otherwise repeat, merging lists twice the size.  */
6844       insize *= 2;
6845     }
6846 }
6847
6848
6849 /* Check to see if an expression is suitable for use in a CASE statement.
6850    Makes sure that all case expressions are scalar constants of the same
6851    type.  Return FAILURE if anything is wrong.  */
6852
6853 static gfc_try
6854 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6855 {
6856   if (e == NULL) return SUCCESS;
6857
6858   if (e->ts.type != case_expr->ts.type)
6859     {
6860       gfc_error ("Expression in CASE statement at %L must be of type %s",
6861                  &e->where, gfc_basic_typename (case_expr->ts.type));
6862       return FAILURE;
6863     }
6864
6865   /* C805 (R808) For a given case-construct, each case-value shall be of
6866      the same type as case-expr.  For character type, length differences
6867      are allowed, but the kind type parameters shall be the same.  */
6868
6869   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6870     {
6871       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6872                  &e->where, case_expr->ts.kind);
6873       return FAILURE;
6874     }
6875
6876   /* Convert the case value kind to that of case expression kind, if needed.
6877      FIXME:  Should a warning be issued?  */
6878   if (e->ts.kind != case_expr->ts.kind)
6879     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6880
6881   if (e->rank != 0)
6882     {
6883       gfc_error ("Expression in CASE statement at %L must be scalar",
6884                  &e->where);
6885       return FAILURE;
6886     }
6887
6888   return SUCCESS;
6889 }
6890
6891
6892 /* Given a completely parsed select statement, we:
6893
6894      - Validate all expressions and code within the SELECT.
6895      - Make sure that the selection expression is not of the wrong type.
6896      - Make sure that no case ranges overlap.
6897      - Eliminate unreachable cases and unreachable code resulting from
6898        removing case labels.
6899
6900    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6901    they are a hassle for code generation, and to prevent that, we just
6902    cut them out here.  This is not necessary for overlapping cases
6903    because they are illegal and we never even try to generate code.
6904
6905    We have the additional caveat that a SELECT construct could have
6906    been a computed GOTO in the source code. Fortunately we can fairly
6907    easily work around that here: The case_expr for a "real" SELECT CASE
6908    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6909    we have to do is make sure that the case_expr is a scalar integer
6910    expression.  */
6911
6912 static void
6913 resolve_select (gfc_code *code)
6914 {
6915   gfc_code *body;
6916   gfc_expr *case_expr;
6917   gfc_case *cp, *default_case, *tail, *head;
6918   int seen_unreachable;
6919   int seen_logical;
6920   int ncases;
6921   bt type;
6922   gfc_try t;
6923
6924   if (code->expr1 == NULL)
6925     {
6926       /* This was actually a computed GOTO statement.  */
6927       case_expr = code->expr2;
6928       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6929         gfc_error ("Selection expression in computed GOTO statement "
6930                    "at %L must be a scalar integer expression",
6931                    &case_expr->where);
6932
6933       /* Further checking is not necessary because this SELECT was built
6934          by the compiler, so it should always be OK.  Just move the
6935          case_expr from expr2 to expr so that we can handle computed
6936          GOTOs as normal SELECTs from here on.  */
6937       code->expr1 = code->expr2;
6938       code->expr2 = NULL;
6939       return;
6940     }
6941
6942   case_expr = code->expr1;
6943
6944   type = case_expr->ts.type;
6945   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6946     {
6947       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6948                  &case_expr->where, gfc_typename (&case_expr->ts));
6949
6950       /* Punt. Going on here just produce more garbage error messages.  */
6951       return;
6952     }
6953
6954   if (case_expr->rank != 0)
6955     {
6956       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6957                  "expression", &case_expr->where);
6958
6959       /* Punt.  */
6960       return;
6961     }
6962
6963   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6964      of the SELECT CASE expression and its CASE values.  Walk the lists
6965      of case values, and if we find a mismatch, promote case_expr to
6966      the appropriate kind.  */
6967
6968   if (type == BT_LOGICAL || type == BT_INTEGER)
6969     {
6970       for (body = code->block; body; body = body->block)
6971         {
6972           /* Walk the case label list.  */
6973           for (cp = body->ext.case_list; cp; cp = cp->next)
6974             {
6975               /* Intercept the DEFAULT case.  It does not have a kind.  */
6976               if (cp->low == NULL && cp->high == NULL)
6977                 continue;
6978
6979               /* Unreachable case ranges are discarded, so ignore.  */
6980               if (cp->low != NULL && cp->high != NULL
6981                   && cp->low != cp->high
6982                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6983                 continue;
6984
6985               /* FIXME: Should a warning be issued?  */
6986               if (cp->low != NULL
6987                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6988                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6989
6990               if (cp->high != NULL
6991                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6992                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6993             }
6994          }
6995     }
6996
6997   /* Assume there is no DEFAULT case.  */
6998   default_case = NULL;
6999   head = tail = NULL;
7000   ncases = 0;
7001   seen_logical = 0;
7002
7003   for (body = code->block; body; body = body->block)
7004     {
7005       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7006       t = SUCCESS;
7007       seen_unreachable = 0;
7008
7009       /* Walk the case label list, making sure that all case labels
7010          are legal.  */
7011       for (cp = body->ext.case_list; cp; cp = cp->next)
7012         {
7013           /* Count the number of cases in the whole construct.  */
7014           ncases++;
7015
7016           /* Intercept the DEFAULT case.  */
7017           if (cp->low == NULL && cp->high == NULL)
7018             {
7019               if (default_case != NULL)
7020                 {
7021                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7022                              "by a second DEFAULT CASE at %L",
7023                              &default_case->where, &cp->where);
7024                   t = FAILURE;
7025                   break;
7026                 }
7027               else
7028                 {
7029                   default_case = cp;
7030                   continue;
7031                 }
7032             }
7033
7034           /* Deal with single value cases and case ranges.  Errors are
7035              issued from the validation function.  */
7036           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
7037              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7038             {
7039               t = FAILURE;
7040               break;
7041             }
7042
7043           if (type == BT_LOGICAL
7044               && ((cp->low == NULL || cp->high == NULL)
7045                   || cp->low != cp->high))
7046             {
7047               gfc_error ("Logical range in CASE statement at %L is not "
7048                          "allowed", &cp->low->where);
7049               t = FAILURE;
7050               break;
7051             }
7052
7053           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7054             {
7055               int value;
7056               value = cp->low->value.logical == 0 ? 2 : 1;
7057               if (value & seen_logical)
7058                 {
7059                   gfc_error ("constant logical value in CASE statement "
7060                              "is repeated at %L",
7061                              &cp->low->where);
7062                   t = FAILURE;
7063                   break;
7064                 }
7065               seen_logical |= value;
7066             }
7067
7068           if (cp->low != NULL && cp->high != NULL
7069               && cp->low != cp->high
7070               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7071             {
7072               if (gfc_option.warn_surprising)
7073                 gfc_warning ("Range specification at %L can never "
7074                              "be matched", &cp->where);
7075
7076               cp->unreachable = 1;
7077               seen_unreachable = 1;
7078             }
7079           else
7080             {
7081               /* If the case range can be matched, it can also overlap with
7082                  other cases.  To make sure it does not, we put it in a
7083                  double linked list here.  We sort that with a merge sort
7084                  later on to detect any overlapping cases.  */
7085               if (!head)
7086                 {
7087                   head = tail = cp;
7088                   head->right = head->left = NULL;
7089                 }
7090               else
7091                 {
7092                   tail->right = cp;
7093                   tail->right->left = tail;
7094                   tail = tail->right;
7095                   tail->right = NULL;
7096                 }
7097             }
7098         }
7099
7100       /* It there was a failure in the previous case label, give up
7101          for this case label list.  Continue with the next block.  */
7102       if (t == FAILURE)
7103         continue;
7104
7105       /* See if any case labels that are unreachable have been seen.
7106          If so, we eliminate them.  This is a bit of a kludge because
7107          the case lists for a single case statement (label) is a
7108          single forward linked lists.  */
7109       if (seen_unreachable)
7110       {
7111         /* Advance until the first case in the list is reachable.  */
7112         while (body->ext.case_list != NULL
7113                && body->ext.case_list->unreachable)
7114           {
7115             gfc_case *n = body->ext.case_list;
7116             body->ext.case_list = body->ext.case_list->next;
7117             n->next = NULL;
7118             gfc_free_case_list (n);
7119           }
7120
7121         /* Strip all other unreachable cases.  */
7122         if (body->ext.case_list)
7123           {
7124             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7125               {
7126                 if (cp->next->unreachable)
7127                   {
7128                     gfc_case *n = cp->next;
7129                     cp->next = cp->next->next;
7130                     n->next = NULL;
7131                     gfc_free_case_list (n);
7132                   }
7133               }
7134           }
7135       }
7136     }
7137
7138   /* See if there were overlapping cases.  If the check returns NULL,
7139      there was overlap.  In that case we don't do anything.  If head
7140      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7141      then used during code generation for SELECT CASE constructs with
7142      a case expression of a CHARACTER type.  */
7143   if (head)
7144     {
7145       head = check_case_overlap (head);
7146
7147       /* Prepend the default_case if it is there.  */
7148       if (head != NULL && default_case)
7149         {
7150           default_case->left = NULL;
7151           default_case->right = head;
7152           head->left = default_case;
7153         }
7154     }
7155
7156   /* Eliminate dead blocks that may be the result if we've seen
7157      unreachable case labels for a block.  */
7158   for (body = code; body && body->block; body = body->block)
7159     {
7160       if (body->block->ext.case_list == NULL)
7161         {
7162           /* Cut the unreachable block from the code chain.  */
7163           gfc_code *c = body->block;
7164           body->block = c->block;
7165
7166           /* Kill the dead block, but not the blocks below it.  */
7167           c->block = NULL;
7168           gfc_free_statements (c);
7169         }
7170     }
7171
7172   /* More than two cases is legal but insane for logical selects.
7173      Issue a warning for it.  */
7174   if (gfc_option.warn_surprising && type == BT_LOGICAL
7175       && ncases > 2)
7176     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7177                  &code->loc);
7178 }
7179
7180
7181 /* Check if a derived type is extensible.  */
7182
7183 bool
7184 gfc_type_is_extensible (gfc_symbol *sym)
7185 {
7186   return !(sym->attr.is_bind_c || sym->attr.sequence);
7187 }
7188
7189
7190 /* Resolve a SELECT TYPE statement.  */
7191
7192 static void
7193 resolve_select_type (gfc_code *code)
7194 {
7195   gfc_symbol *selector_type;
7196   gfc_code *body, *new_st, *if_st, *tail;
7197   gfc_code *class_is = NULL, *default_case = NULL;
7198   gfc_case *c;
7199   gfc_symtree *st;
7200   char name[GFC_MAX_SYMBOL_LEN];
7201   gfc_namespace *ns;
7202   int error = 0;
7203
7204   ns = code->ext.ns;
7205   gfc_resolve (ns);
7206
7207   if (code->expr2)
7208     selector_type = code->expr2->ts.u.derived->components->ts.u.derived;
7209   else
7210     selector_type = code->expr1->ts.u.derived->components->ts.u.derived;
7211
7212   /* Loop over TYPE IS / CLASS IS cases.  */
7213   for (body = code->block; body; body = body->block)
7214     {
7215       c = body->ext.case_list;
7216
7217       /* Check F03:C815.  */
7218       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7219           && !gfc_type_is_extensible (c->ts.u.derived))
7220         {
7221           gfc_error ("Derived type '%s' at %L must be extensible",
7222                      c->ts.u.derived->name, &c->where);
7223           error++;
7224           continue;
7225         }
7226
7227       /* Check F03:C816.  */
7228       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7229           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7230         {
7231           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7232                      c->ts.u.derived->name, &c->where, selector_type->name);
7233           error++;
7234           continue;
7235         }
7236
7237       /* Intercept the DEFAULT case.  */
7238       if (c->ts.type == BT_UNKNOWN)
7239         {
7240           /* Check F03:C818.  */
7241           if (default_case)
7242             {
7243               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7244                          "by a second DEFAULT CASE at %L",
7245                          &default_case->ext.case_list->where, &c->where);
7246               error++;
7247               continue;
7248             }
7249           else
7250             default_case = body;
7251         }
7252     }
7253     
7254   if (error>0)
7255     return;
7256
7257   if (code->expr2)
7258     {
7259       /* Insert assignment for selector variable.  */
7260       new_st = gfc_get_code ();
7261       new_st->op = EXEC_ASSIGN;
7262       new_st->expr1 = gfc_copy_expr (code->expr1);
7263       new_st->expr2 = gfc_copy_expr (code->expr2);
7264       ns->code = new_st;
7265     }
7266
7267   /* Put SELECT TYPE statement inside a BLOCK.  */
7268   new_st = gfc_get_code ();
7269   new_st->op = code->op;
7270   new_st->expr1 = code->expr1;
7271   new_st->expr2 = code->expr2;
7272   new_st->block = code->block;
7273   if (!ns->code)
7274     ns->code = new_st;
7275   else
7276     ns->code->next = new_st;
7277   code->op = EXEC_BLOCK;
7278   code->expr1 = code->expr2 =  NULL;
7279   code->block = NULL;
7280
7281   code = new_st;
7282
7283   /* Transform to EXEC_SELECT.  */
7284   code->op = EXEC_SELECT;
7285   gfc_add_component_ref (code->expr1, "$vptr");
7286   gfc_add_component_ref (code->expr1, "$hash");
7287
7288   /* Loop over TYPE IS / CLASS IS cases.  */
7289   for (body = code->block; body; body = body->block)
7290     {
7291       c = body->ext.case_list;
7292
7293       if (c->ts.type == BT_DERIVED)
7294         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7295                                              c->ts.u.derived->hash_value);
7296
7297       else if (c->ts.type == BT_UNKNOWN)
7298         continue;
7299
7300       /* Assign temporary to selector.  */
7301       if (c->ts.type == BT_CLASS)
7302         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7303       else
7304         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7305       st = gfc_find_symtree (ns->sym_root, name);
7306       new_st = gfc_get_code ();
7307       new_st->expr1 = gfc_get_variable_expr (st);
7308       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7309       if (c->ts.type == BT_DERIVED)
7310         {
7311           new_st->op = EXEC_POINTER_ASSIGN;
7312           gfc_add_component_ref (new_st->expr2, "$data");
7313         }
7314       else
7315         new_st->op = EXEC_POINTER_ASSIGN;
7316       new_st->next = body->next;
7317       body->next = new_st;
7318     }
7319     
7320   /* Take out CLASS IS cases for separate treatment.  */
7321   body = code;
7322   while (body && body->block)
7323     {
7324       if (body->block->ext.case_list->ts.type == BT_CLASS)
7325         {
7326           /* Add to class_is list.  */
7327           if (class_is == NULL)
7328             { 
7329               class_is = body->block;
7330               tail = class_is;
7331             }
7332           else
7333             {
7334               for (tail = class_is; tail->block; tail = tail->block) ;
7335               tail->block = body->block;
7336               tail = tail->block;
7337             }
7338           /* Remove from EXEC_SELECT list.  */
7339           body->block = body->block->block;
7340           tail->block = NULL;
7341         }
7342       else
7343         body = body->block;
7344     }
7345
7346   if (class_is)
7347     {
7348       gfc_symbol *vtab;
7349       
7350       if (!default_case)
7351         {
7352           /* Add a default case to hold the CLASS IS cases.  */
7353           for (tail = code; tail->block; tail = tail->block) ;
7354           tail->block = gfc_get_code ();
7355           tail = tail->block;
7356           tail->op = EXEC_SELECT_TYPE;
7357           tail->ext.case_list = gfc_get_case ();
7358           tail->ext.case_list->ts.type = BT_UNKNOWN;
7359           tail->next = NULL;
7360           default_case = tail;
7361         }
7362       
7363       /* More than one CLASS IS block?  */
7364       if (class_is->block)
7365         {
7366           gfc_code **c1,*c2;
7367           bool swapped;
7368           /* Sort CLASS IS blocks by extension level.  */
7369           do
7370             {
7371               swapped = false;
7372               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7373                 {
7374                   c2 = (*c1)->block;
7375                   /* F03:C817 (check for doubles).  */
7376                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7377                       == c2->ext.case_list->ts.u.derived->hash_value)
7378                     {
7379                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7380                                  "statement at %L", &c2->ext.case_list->where);
7381                       return;
7382                     }
7383                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7384                       < c2->ext.case_list->ts.u.derived->attr.extension)
7385                     {
7386                       /* Swap.  */
7387                       (*c1)->block = c2->block;
7388                       c2->block = *c1;
7389                       *c1 = c2;
7390                       swapped = true;
7391                     }
7392                 }
7393             }
7394           while (swapped);
7395         }
7396         
7397       /* Generate IF chain.  */
7398       if_st = gfc_get_code ();
7399       if_st->op = EXEC_IF;
7400       new_st = if_st;
7401       for (body = class_is; body; body = body->block)
7402         {
7403           new_st->block = gfc_get_code ();
7404           new_st = new_st->block;
7405           new_st->op = EXEC_IF;
7406           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7407           new_st->expr1 = gfc_get_expr ();
7408           new_st->expr1->expr_type = EXPR_FUNCTION;
7409           new_st->expr1->ts.type = BT_LOGICAL;
7410           new_st->expr1->ts.kind = 4;
7411           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7412           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7413           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7414           /* Set up arguments.  */
7415           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7416           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7417           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7418           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7419           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7420           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7421           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7422           new_st->next = body->next;
7423         }
7424         if (default_case->next)
7425           {
7426             new_st->block = gfc_get_code ();
7427             new_st = new_st->block;
7428             new_st->op = EXEC_IF;
7429             new_st->next = default_case->next;
7430           }
7431           
7432         /* Replace CLASS DEFAULT code by the IF chain.  */
7433         default_case->next = if_st;
7434     }
7435
7436   resolve_select (code);
7437
7438 }
7439
7440
7441 /* Resolve a transfer statement. This is making sure that:
7442    -- a derived type being transferred has only non-pointer components
7443    -- a derived type being transferred doesn't have private components, unless 
7444       it's being transferred from the module where the type was defined
7445    -- we're not trying to transfer a whole assumed size array.  */
7446
7447 static void
7448 resolve_transfer (gfc_code *code)
7449 {
7450   gfc_typespec *ts;
7451   gfc_symbol *sym;
7452   gfc_ref *ref;
7453   gfc_expr *exp;
7454
7455   exp = code->expr1;
7456
7457   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7458     return;
7459
7460   sym = exp->symtree->n.sym;
7461   ts = &sym->ts;
7462
7463   /* Go to actual component transferred.  */
7464   for (ref = code->expr1->ref; ref; ref = ref->next)
7465     if (ref->type == REF_COMPONENT)
7466       ts = &ref->u.c.component->ts;
7467
7468   if (ts->type == BT_DERIVED)
7469     {
7470       /* Check that transferred derived type doesn't contain POINTER
7471          components.  */
7472       if (ts->u.derived->attr.pointer_comp)
7473         {
7474           gfc_error ("Data transfer element at %L cannot have "
7475                      "POINTER components", &code->loc);
7476           return;
7477         }
7478
7479       if (ts->u.derived->attr.alloc_comp)
7480         {
7481           gfc_error ("Data transfer element at %L cannot have "
7482                      "ALLOCATABLE components", &code->loc);
7483           return;
7484         }
7485
7486       if (derived_inaccessible (ts->u.derived))
7487         {
7488           gfc_error ("Data transfer element at %L cannot have "
7489                      "PRIVATE components",&code->loc);
7490           return;
7491         }
7492     }
7493
7494   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7495       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7496     {
7497       gfc_error ("Data transfer element at %L cannot be a full reference to "
7498                  "an assumed-size array", &code->loc);
7499       return;
7500     }
7501 }
7502
7503
7504 /*********** Toplevel code resolution subroutines ***********/
7505
7506 /* Find the set of labels that are reachable from this block.  We also
7507    record the last statement in each block.  */
7508      
7509 static void
7510 find_reachable_labels (gfc_code *block)
7511 {
7512   gfc_code *c;
7513
7514   if (!block)
7515     return;
7516
7517   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7518
7519   /* Collect labels in this block.  We don't keep those corresponding
7520      to END {IF|SELECT}, these are checked in resolve_branch by going
7521      up through the code_stack.  */
7522   for (c = block; c; c = c->next)
7523     {
7524       if (c->here && c->op != EXEC_END_BLOCK)
7525         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7526     }
7527
7528   /* Merge with labels from parent block.  */
7529   if (cs_base->prev)
7530     {
7531       gcc_assert (cs_base->prev->reachable_labels);
7532       bitmap_ior_into (cs_base->reachable_labels,
7533                        cs_base->prev->reachable_labels);
7534     }
7535 }
7536
7537
7538 static void
7539 resolve_sync (gfc_code *code)
7540 {
7541   /* Check imageset. The * case matches expr1 == NULL.  */
7542   if (code->expr1)
7543     {
7544       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
7545         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
7546                    "INTEGER expression", &code->expr1->where);
7547       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
7548           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
7549         gfc_error ("Imageset argument at %L must between 1 and num_images()",
7550                    &code->expr1->where);
7551       else if (code->expr1->expr_type == EXPR_ARRAY
7552                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
7553         {
7554            gfc_constructor *cons;
7555            cons = gfc_constructor_first (code->expr1->value.constructor);
7556            for (; cons; cons = gfc_constructor_next (cons))
7557              if (cons->expr->expr_type == EXPR_CONSTANT
7558                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
7559                gfc_error ("Imageset argument at %L must between 1 and "
7560                           "num_images()", &cons->expr->where);
7561         }
7562     }
7563
7564   /* Check STAT.  */
7565   if (code->expr2
7566       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
7567           || code->expr2->expr_type != EXPR_VARIABLE))
7568     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
7569                &code->expr2->where);
7570
7571   /* Check ERRMSG.  */
7572   if (code->expr3
7573       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
7574           || code->expr3->expr_type != EXPR_VARIABLE))
7575     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
7576                &code->expr3->where);
7577 }
7578
7579
7580 /* Given a branch to a label, see if the branch is conforming.
7581    The code node describes where the branch is located.  */
7582
7583 static void
7584 resolve_branch (gfc_st_label *label, gfc_code *code)
7585 {
7586   code_stack *stack;
7587
7588   if (label == NULL)
7589     return;
7590
7591   /* Step one: is this a valid branching target?  */
7592
7593   if (label->defined == ST_LABEL_UNKNOWN)
7594     {
7595       gfc_error ("Label %d referenced at %L is never defined", label->value,
7596                  &label->where);
7597       return;
7598     }
7599
7600   if (label->defined != ST_LABEL_TARGET)
7601     {
7602       gfc_error ("Statement at %L is not a valid branch target statement "
7603                  "for the branch statement at %L", &label->where, &code->loc);
7604       return;
7605     }
7606
7607   /* Step two: make sure this branch is not a branch to itself ;-)  */
7608
7609   if (code->here == label)
7610     {
7611       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7612       return;
7613     }
7614
7615   /* Step three:  See if the label is in the same block as the
7616      branching statement.  The hard work has been done by setting up
7617      the bitmap reachable_labels.  */
7618
7619   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7620     {
7621       /* Check now whether there is a CRITICAL construct; if so, check
7622          whether the label is still visible outside of the CRITICAL block,
7623          which is invalid.  */
7624       for (stack = cs_base; stack; stack = stack->prev)
7625         if (stack->current->op == EXEC_CRITICAL
7626             && bitmap_bit_p (stack->reachable_labels, label->value))
7627           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7628                       " at %L", &code->loc, &label->where);
7629
7630       return;
7631     }
7632
7633   /* Step four:  If we haven't found the label in the bitmap, it may
7634     still be the label of the END of the enclosing block, in which
7635     case we find it by going up the code_stack.  */
7636
7637   for (stack = cs_base; stack; stack = stack->prev)
7638     {
7639       if (stack->current->next && stack->current->next->here == label)
7640         break;
7641       if (stack->current->op == EXEC_CRITICAL)
7642         {
7643           /* Note: A label at END CRITICAL does not leave the CRITICAL
7644              construct as END CRITICAL is still part of it.  */
7645           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7646                       " at %L", &code->loc, &label->where);
7647           return;
7648         }
7649     }
7650
7651   if (stack)
7652     {
7653       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7654       return;
7655     }
7656
7657   /* The label is not in an enclosing block, so illegal.  This was
7658      allowed in Fortran 66, so we allow it as extension.  No
7659      further checks are necessary in this case.  */
7660   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7661                   "as the GOTO statement at %L", &label->where,
7662                   &code->loc);
7663   return;
7664 }
7665
7666
7667 /* Check whether EXPR1 has the same shape as EXPR2.  */
7668
7669 static gfc_try
7670 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7671 {
7672   mpz_t shape[GFC_MAX_DIMENSIONS];
7673   mpz_t shape2[GFC_MAX_DIMENSIONS];
7674   gfc_try result = FAILURE;
7675   int i;
7676
7677   /* Compare the rank.  */
7678   if (expr1->rank != expr2->rank)
7679     return result;
7680
7681   /* Compare the size of each dimension.  */
7682   for (i=0; i<expr1->rank; i++)
7683     {
7684       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7685         goto ignore;
7686
7687       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7688         goto ignore;
7689
7690       if (mpz_cmp (shape[i], shape2[i]))
7691         goto over;
7692     }
7693
7694   /* When either of the two expression is an assumed size array, we
7695      ignore the comparison of dimension sizes.  */
7696 ignore:
7697   result = SUCCESS;
7698
7699 over:
7700   for (i--; i >= 0; i--)
7701     {
7702       mpz_clear (shape[i]);
7703       mpz_clear (shape2[i]);
7704     }
7705   return result;
7706 }
7707
7708
7709 /* Check whether a WHERE assignment target or a WHERE mask expression
7710    has the same shape as the outmost WHERE mask expression.  */
7711
7712 static void
7713 resolve_where (gfc_code *code, gfc_expr *mask)
7714 {
7715   gfc_code *cblock;
7716   gfc_code *cnext;
7717   gfc_expr *e = NULL;
7718
7719   cblock = code->block;
7720
7721   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7722      In case of nested WHERE, only the outmost one is stored.  */
7723   if (mask == NULL) /* outmost WHERE */
7724     e = cblock->expr1;
7725   else /* inner WHERE */
7726     e = mask;
7727
7728   while (cblock)
7729     {
7730       if (cblock->expr1)
7731         {
7732           /* Check if the mask-expr has a consistent shape with the
7733              outmost WHERE mask-expr.  */
7734           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7735             gfc_error ("WHERE mask at %L has inconsistent shape",
7736                        &cblock->expr1->where);
7737          }
7738
7739       /* the assignment statement of a WHERE statement, or the first
7740          statement in where-body-construct of a WHERE construct */
7741       cnext = cblock->next;
7742       while (cnext)
7743         {
7744           switch (cnext->op)
7745             {
7746             /* WHERE assignment statement */
7747             case EXEC_ASSIGN:
7748
7749               /* Check shape consistent for WHERE assignment target.  */
7750               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7751                gfc_error ("WHERE assignment target at %L has "
7752                           "inconsistent shape", &cnext->expr1->where);
7753               break;
7754
7755   
7756             case EXEC_ASSIGN_CALL:
7757               resolve_call (cnext);
7758               if (!cnext->resolved_sym->attr.elemental)
7759                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7760                           &cnext->ext.actual->expr->where);
7761               break;
7762
7763             /* WHERE or WHERE construct is part of a where-body-construct */
7764             case EXEC_WHERE:
7765               resolve_where (cnext, e);
7766               break;
7767
7768             default:
7769               gfc_error ("Unsupported statement inside WHERE at %L",
7770                          &cnext->loc);
7771             }
7772          /* the next statement within the same where-body-construct */
7773          cnext = cnext->next;
7774        }
7775     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7776     cblock = cblock->block;
7777   }
7778 }
7779
7780
7781 /* Resolve assignment in FORALL construct.
7782    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7783    FORALL index variables.  */
7784
7785 static void
7786 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7787 {
7788   int n;
7789
7790   for (n = 0; n < nvar; n++)
7791     {
7792       gfc_symbol *forall_index;
7793
7794       forall_index = var_expr[n]->symtree->n.sym;
7795
7796       /* Check whether the assignment target is one of the FORALL index
7797          variable.  */
7798       if ((code->expr1->expr_type == EXPR_VARIABLE)
7799           && (code->expr1->symtree->n.sym == forall_index))
7800         gfc_error ("Assignment to a FORALL index variable at %L",
7801                    &code->expr1->where);
7802       else
7803         {
7804           /* If one of the FORALL index variables doesn't appear in the
7805              assignment variable, then there could be a many-to-one
7806              assignment.  Emit a warning rather than an error because the
7807              mask could be resolving this problem.  */
7808           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7809             gfc_warning ("The FORALL with index '%s' is not used on the "
7810                          "left side of the assignment at %L and so might "
7811                          "cause multiple assignment to this object",
7812                          var_expr[n]->symtree->name, &code->expr1->where);
7813         }
7814     }
7815 }
7816
7817
7818 /* Resolve WHERE statement in FORALL construct.  */
7819
7820 static void
7821 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7822                                   gfc_expr **var_expr)
7823 {
7824   gfc_code *cblock;
7825   gfc_code *cnext;
7826
7827   cblock = code->block;
7828   while (cblock)
7829     {
7830       /* the assignment statement of a WHERE statement, or the first
7831          statement in where-body-construct of a WHERE construct */
7832       cnext = cblock->next;
7833       while (cnext)
7834         {
7835           switch (cnext->op)
7836             {
7837             /* WHERE assignment statement */
7838             case EXEC_ASSIGN:
7839               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7840               break;
7841   
7842             /* WHERE operator assignment statement */
7843             case EXEC_ASSIGN_CALL:
7844               resolve_call (cnext);
7845               if (!cnext->resolved_sym->attr.elemental)
7846                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7847                           &cnext->ext.actual->expr->where);
7848               break;
7849
7850             /* WHERE or WHERE construct is part of a where-body-construct */
7851             case EXEC_WHERE:
7852               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7853               break;
7854
7855             default:
7856               gfc_error ("Unsupported statement inside WHERE at %L",
7857                          &cnext->loc);
7858             }
7859           /* the next statement within the same where-body-construct */
7860           cnext = cnext->next;
7861         }
7862       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7863       cblock = cblock->block;
7864     }
7865 }
7866
7867
7868 /* Traverse the FORALL body to check whether the following errors exist:
7869    1. For assignment, check if a many-to-one assignment happens.
7870    2. For WHERE statement, check the WHERE body to see if there is any
7871       many-to-one assignment.  */
7872
7873 static void
7874 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7875 {
7876   gfc_code *c;
7877
7878   c = code->block->next;
7879   while (c)
7880     {
7881       switch (c->op)
7882         {
7883         case EXEC_ASSIGN:
7884         case EXEC_POINTER_ASSIGN:
7885           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7886           break;
7887
7888         case EXEC_ASSIGN_CALL:
7889           resolve_call (c);
7890           break;
7891
7892         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7893            there is no need to handle it here.  */
7894         case EXEC_FORALL:
7895           break;
7896         case EXEC_WHERE:
7897           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7898           break;
7899         default:
7900           break;
7901         }
7902       /* The next statement in the FORALL body.  */
7903       c = c->next;
7904     }
7905 }
7906
7907
7908 /* Counts the number of iterators needed inside a forall construct, including
7909    nested forall constructs. This is used to allocate the needed memory 
7910    in gfc_resolve_forall.  */
7911
7912 static int 
7913 gfc_count_forall_iterators (gfc_code *code)
7914 {
7915   int max_iters, sub_iters, current_iters;
7916   gfc_forall_iterator *fa;
7917
7918   gcc_assert(code->op == EXEC_FORALL);
7919   max_iters = 0;
7920   current_iters = 0;
7921
7922   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7923     current_iters ++;
7924   
7925   code = code->block->next;
7926
7927   while (code)
7928     {          
7929       if (code->op == EXEC_FORALL)
7930         {
7931           sub_iters = gfc_count_forall_iterators (code);
7932           if (sub_iters > max_iters)
7933             max_iters = sub_iters;
7934         }
7935       code = code->next;
7936     }
7937
7938   return current_iters + max_iters;
7939 }
7940
7941
7942 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7943    gfc_resolve_forall_body to resolve the FORALL body.  */
7944
7945 static void
7946 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7947 {
7948   static gfc_expr **var_expr;
7949   static int total_var = 0;
7950   static int nvar = 0;
7951   int old_nvar, tmp;
7952   gfc_forall_iterator *fa;
7953   int i;
7954
7955   old_nvar = nvar;
7956
7957   /* Start to resolve a FORALL construct   */
7958   if (forall_save == 0)
7959     {
7960       /* Count the total number of FORALL index in the nested FORALL
7961          construct in order to allocate the VAR_EXPR with proper size.  */
7962       total_var = gfc_count_forall_iterators (code);
7963
7964       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7965       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7966     }
7967
7968   /* The information about FORALL iterator, including FORALL index start, end
7969      and stride. The FORALL index can not appear in start, end or stride.  */
7970   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7971     {
7972       /* Check if any outer FORALL index name is the same as the current
7973          one.  */
7974       for (i = 0; i < nvar; i++)
7975         {
7976           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7977             {
7978               gfc_error ("An outer FORALL construct already has an index "
7979                          "with this name %L", &fa->var->where);
7980             }
7981         }
7982
7983       /* Record the current FORALL index.  */
7984       var_expr[nvar] = gfc_copy_expr (fa->var);
7985
7986       nvar++;
7987
7988       /* No memory leak.  */
7989       gcc_assert (nvar <= total_var);
7990     }
7991
7992   /* Resolve the FORALL body.  */
7993   gfc_resolve_forall_body (code, nvar, var_expr);
7994
7995   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7996   gfc_resolve_blocks (code->block, ns);
7997
7998   tmp = nvar;
7999   nvar = old_nvar;
8000   /* Free only the VAR_EXPRs allocated in this frame.  */
8001   for (i = nvar; i < tmp; i++)
8002      gfc_free_expr (var_expr[i]);
8003
8004   if (nvar == 0)
8005     {
8006       /* We are in the outermost FORALL construct.  */
8007       gcc_assert (forall_save == 0);
8008
8009       /* VAR_EXPR is not needed any more.  */
8010       gfc_free (var_expr);
8011       total_var = 0;
8012     }
8013 }
8014
8015
8016 /* Resolve a BLOCK construct statement.  */
8017
8018 static void
8019 resolve_block_construct (gfc_code* code)
8020 {
8021   /* Eventually, we may want to do some checks here or handle special stuff.
8022      But so far the only thing we can do is resolving the local namespace.  */
8023
8024   gfc_resolve (code->ext.ns);
8025 }
8026
8027
8028 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8029    DO code nodes.  */
8030
8031 static void resolve_code (gfc_code *, gfc_namespace *);
8032
8033 void
8034 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8035 {
8036   gfc_try t;
8037
8038   for (; b; b = b->block)
8039     {
8040       t = gfc_resolve_expr (b->expr1);
8041       if (gfc_resolve_expr (b->expr2) == FAILURE)
8042         t = FAILURE;
8043
8044       switch (b->op)
8045         {
8046         case EXEC_IF:
8047           if (t == SUCCESS && b->expr1 != NULL
8048               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8049             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8050                        &b->expr1->where);
8051           break;
8052
8053         case EXEC_WHERE:
8054           if (t == SUCCESS
8055               && b->expr1 != NULL
8056               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8057             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8058                        &b->expr1->where);
8059           break;
8060
8061         case EXEC_GOTO:
8062           resolve_branch (b->label1, b);
8063           break;
8064
8065         case EXEC_BLOCK:
8066           resolve_block_construct (b);
8067           break;
8068
8069         case EXEC_SELECT:
8070         case EXEC_SELECT_TYPE:
8071         case EXEC_FORALL:
8072         case EXEC_DO:
8073         case EXEC_DO_WHILE:
8074         case EXEC_CRITICAL:
8075         case EXEC_READ:
8076         case EXEC_WRITE:
8077         case EXEC_IOLENGTH:
8078         case EXEC_WAIT:
8079           break;
8080
8081         case EXEC_OMP_ATOMIC:
8082         case EXEC_OMP_CRITICAL:
8083         case EXEC_OMP_DO:
8084         case EXEC_OMP_MASTER:
8085         case EXEC_OMP_ORDERED:
8086         case EXEC_OMP_PARALLEL:
8087         case EXEC_OMP_PARALLEL_DO:
8088         case EXEC_OMP_PARALLEL_SECTIONS:
8089         case EXEC_OMP_PARALLEL_WORKSHARE:
8090         case EXEC_OMP_SECTIONS:
8091         case EXEC_OMP_SINGLE:
8092         case EXEC_OMP_TASK:
8093         case EXEC_OMP_TASKWAIT:
8094         case EXEC_OMP_WORKSHARE:
8095           break;
8096
8097         default:
8098           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8099         }
8100
8101       resolve_code (b->next, ns);
8102     }
8103 }
8104
8105
8106 /* Does everything to resolve an ordinary assignment.  Returns true
8107    if this is an interface assignment.  */
8108 static bool
8109 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8110 {
8111   bool rval = false;
8112   gfc_expr *lhs;
8113   gfc_expr *rhs;
8114   int llen = 0;
8115   int rlen = 0;
8116   int n;
8117   gfc_ref *ref;
8118
8119   if (gfc_extend_assign (code, ns) == SUCCESS)
8120     {
8121       gfc_expr** rhsptr;
8122
8123       if (code->op == EXEC_ASSIGN_CALL)
8124         {
8125           lhs = code->ext.actual->expr;
8126           rhsptr = &code->ext.actual->next->expr;
8127         }
8128       else
8129         {
8130           gfc_actual_arglist* args;
8131           gfc_typebound_proc* tbp;
8132
8133           gcc_assert (code->op == EXEC_COMPCALL);
8134
8135           args = code->expr1->value.compcall.actual;
8136           lhs = args->expr;
8137           rhsptr = &args->next->expr;
8138
8139           tbp = code->expr1->value.compcall.tbp;
8140           gcc_assert (!tbp->is_generic);
8141         }
8142
8143       /* Make a temporary rhs when there is a default initializer
8144          and rhs is the same symbol as the lhs.  */
8145       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8146             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8147             && has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8148             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8149         *rhsptr = gfc_get_parentheses (*rhsptr);
8150
8151       return true;
8152     }
8153
8154   lhs = code->expr1;
8155   rhs = code->expr2;
8156
8157   if (rhs->is_boz
8158       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8159                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8160                          &code->loc) == FAILURE)
8161     return false;
8162
8163   /* Handle the case of a BOZ literal on the RHS.  */
8164   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8165     {
8166       int rc;
8167       if (gfc_option.warn_surprising)
8168         gfc_warning ("BOZ literal at %L is bitwise transferred "
8169                      "non-integer symbol '%s'", &code->loc,
8170                      lhs->symtree->n.sym->name);
8171
8172       if (!gfc_convert_boz (rhs, &lhs->ts))
8173         return false;
8174       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8175         {
8176           if (rc == ARITH_UNDERFLOW)
8177             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8178                        ". This check can be disabled with the option "
8179                        "-fno-range-check", &rhs->where);
8180           else if (rc == ARITH_OVERFLOW)
8181             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8182                        ". This check can be disabled with the option "
8183                        "-fno-range-check", &rhs->where);
8184           else if (rc == ARITH_NAN)
8185             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8186                        ". This check can be disabled with the option "
8187                        "-fno-range-check", &rhs->where);
8188           return false;
8189         }
8190     }
8191
8192
8193   if (lhs->ts.type == BT_CHARACTER
8194         && gfc_option.warn_character_truncation)
8195     {
8196       if (lhs->ts.u.cl != NULL
8197             && lhs->ts.u.cl->length != NULL
8198             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8199         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8200
8201       if (rhs->expr_type == EXPR_CONSTANT)
8202         rlen = rhs->value.character.length;
8203
8204       else if (rhs->ts.u.cl != NULL
8205                  && rhs->ts.u.cl->length != NULL
8206                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8207         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8208
8209       if (rlen && llen && rlen > llen)
8210         gfc_warning_now ("CHARACTER expression will be truncated "
8211                          "in assignment (%d/%d) at %L",
8212                          llen, rlen, &code->loc);
8213     }
8214
8215   /* Ensure that a vector index expression for the lvalue is evaluated
8216      to a temporary if the lvalue symbol is referenced in it.  */
8217   if (lhs->rank)
8218     {
8219       for (ref = lhs->ref; ref; ref= ref->next)
8220         if (ref->type == REF_ARRAY)
8221           {
8222             for (n = 0; n < ref->u.ar.dimen; n++)
8223               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8224                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8225                                            ref->u.ar.start[n]))
8226                 ref->u.ar.start[n]
8227                         = gfc_get_parentheses (ref->u.ar.start[n]);
8228           }
8229     }
8230
8231   if (gfc_pure (NULL))
8232     {
8233       if (gfc_impure_variable (lhs->symtree->n.sym))
8234         {
8235           gfc_error ("Cannot assign to variable '%s' in PURE "
8236                      "procedure at %L",
8237                       lhs->symtree->n.sym->name,
8238                       &lhs->where);
8239           return rval;
8240         }
8241
8242       if (lhs->ts.type == BT_DERIVED
8243             && lhs->expr_type == EXPR_VARIABLE
8244             && lhs->ts.u.derived->attr.pointer_comp
8245             && rhs->expr_type == EXPR_VARIABLE
8246             && (gfc_impure_variable (rhs->symtree->n.sym)
8247                 || gfc_is_coindexed (rhs)))
8248         {
8249           /* F2008, C1283.  */
8250           if (gfc_is_coindexed (rhs))
8251             gfc_error ("Coindexed expression at %L is assigned to "
8252                         "a derived type variable with a POINTER "
8253                         "component in a PURE procedure",
8254                         &rhs->where);
8255           else
8256             gfc_error ("The impure variable at %L is assigned to "
8257                         "a derived type variable with a POINTER "
8258                         "component in a PURE procedure (12.6)",
8259                         &rhs->where);
8260           return rval;
8261         }
8262
8263       /* Fortran 2008, C1283.  */
8264       if (gfc_is_coindexed (lhs))
8265         {
8266           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8267                      "procedure", &rhs->where);
8268           return rval;
8269         }
8270     }
8271
8272   /* F03:7.4.1.2.  */
8273   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8274      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8275   if (lhs->ts.type == BT_CLASS)
8276     {
8277       gfc_error ("Variable must not be polymorphic in assignment at %L",
8278                  &lhs->where);
8279       return false;
8280     }
8281
8282   /* F2008, Section 7.2.1.2.  */
8283   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8284     {
8285       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8286                  "component in assignment at %L", &lhs->where);
8287       return false;
8288     }
8289
8290   gfc_check_assign (lhs, rhs, 1);
8291   return false;
8292 }
8293
8294
8295 /* Given a block of code, recursively resolve everything pointed to by this
8296    code block.  */
8297
8298 static void
8299 resolve_code (gfc_code *code, gfc_namespace *ns)
8300 {
8301   int omp_workshare_save;
8302   int forall_save;
8303   code_stack frame;
8304   gfc_try t;
8305
8306   frame.prev = cs_base;
8307   frame.head = code;
8308   cs_base = &frame;
8309
8310   find_reachable_labels (code);
8311
8312   for (; code; code = code->next)
8313     {
8314       frame.current = code;
8315       forall_save = forall_flag;
8316
8317       if (code->op == EXEC_FORALL)
8318         {
8319           forall_flag = 1;
8320           gfc_resolve_forall (code, ns, forall_save);
8321           forall_flag = 2;
8322         }
8323       else if (code->block)
8324         {
8325           omp_workshare_save = -1;
8326           switch (code->op)
8327             {
8328             case EXEC_OMP_PARALLEL_WORKSHARE:
8329               omp_workshare_save = omp_workshare_flag;
8330               omp_workshare_flag = 1;
8331               gfc_resolve_omp_parallel_blocks (code, ns);
8332               break;
8333             case EXEC_OMP_PARALLEL:
8334             case EXEC_OMP_PARALLEL_DO:
8335             case EXEC_OMP_PARALLEL_SECTIONS:
8336             case EXEC_OMP_TASK:
8337               omp_workshare_save = omp_workshare_flag;
8338               omp_workshare_flag = 0;
8339               gfc_resolve_omp_parallel_blocks (code, ns);
8340               break;
8341             case EXEC_OMP_DO:
8342               gfc_resolve_omp_do_blocks (code, ns);
8343               break;
8344             case EXEC_SELECT_TYPE:
8345               gfc_current_ns = code->ext.ns;
8346               gfc_resolve_blocks (code->block, gfc_current_ns);
8347               gfc_current_ns = ns;
8348               break;
8349             case EXEC_OMP_WORKSHARE:
8350               omp_workshare_save = omp_workshare_flag;
8351               omp_workshare_flag = 1;
8352               /* FALLTHROUGH */
8353             default:
8354               gfc_resolve_blocks (code->block, ns);
8355               break;
8356             }
8357
8358           if (omp_workshare_save != -1)
8359             omp_workshare_flag = omp_workshare_save;
8360         }
8361
8362       t = SUCCESS;
8363       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8364         t = gfc_resolve_expr (code->expr1);
8365       forall_flag = forall_save;
8366
8367       if (gfc_resolve_expr (code->expr2) == FAILURE)
8368         t = FAILURE;
8369
8370       if (code->op == EXEC_ALLOCATE
8371           && gfc_resolve_expr (code->expr3) == FAILURE)
8372         t = FAILURE;
8373
8374       switch (code->op)
8375         {
8376         case EXEC_NOP:
8377         case EXEC_END_BLOCK:
8378         case EXEC_CYCLE:
8379         case EXEC_PAUSE:
8380         case EXEC_STOP:
8381         case EXEC_ERROR_STOP:
8382         case EXEC_EXIT:
8383         case EXEC_CONTINUE:
8384         case EXEC_DT_END:
8385         case EXEC_ASSIGN_CALL:
8386         case EXEC_CRITICAL:
8387           break;
8388
8389         case EXEC_SYNC_ALL:
8390         case EXEC_SYNC_IMAGES:
8391         case EXEC_SYNC_MEMORY:
8392           resolve_sync (code);
8393           break;
8394
8395         case EXEC_ENTRY:
8396           /* Keep track of which entry we are up to.  */
8397           current_entry_id = code->ext.entry->id;
8398           break;
8399
8400         case EXEC_WHERE:
8401           resolve_where (code, NULL);
8402           break;
8403
8404         case EXEC_GOTO:
8405           if (code->expr1 != NULL)
8406             {
8407               if (code->expr1->ts.type != BT_INTEGER)
8408                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8409                            "INTEGER variable", &code->expr1->where);
8410               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8411                 gfc_error ("Variable '%s' has not been assigned a target "
8412                            "label at %L", code->expr1->symtree->n.sym->name,
8413                            &code->expr1->where);
8414             }
8415           else
8416             resolve_branch (code->label1, code);
8417           break;
8418
8419         case EXEC_RETURN:
8420           if (code->expr1 != NULL
8421                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8422             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8423                        "INTEGER return specifier", &code->expr1->where);
8424           break;
8425
8426         case EXEC_INIT_ASSIGN:
8427         case EXEC_END_PROCEDURE:
8428           break;
8429
8430         case EXEC_ASSIGN:
8431           if (t == FAILURE)
8432             break;
8433
8434           if (resolve_ordinary_assign (code, ns))
8435             {
8436               if (code->op == EXEC_COMPCALL)
8437                 goto compcall;
8438               else
8439                 goto call;
8440             }
8441           break;
8442
8443         case EXEC_LABEL_ASSIGN:
8444           if (code->label1->defined == ST_LABEL_UNKNOWN)
8445             gfc_error ("Label %d referenced at %L is never defined",
8446                        code->label1->value, &code->label1->where);
8447           if (t == SUCCESS
8448               && (code->expr1->expr_type != EXPR_VARIABLE
8449                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8450                   || code->expr1->symtree->n.sym->ts.kind
8451                      != gfc_default_integer_kind
8452                   || code->expr1->symtree->n.sym->as != NULL))
8453             gfc_error ("ASSIGN statement at %L requires a scalar "
8454                        "default INTEGER variable", &code->expr1->where);
8455           break;
8456
8457         case EXEC_POINTER_ASSIGN:
8458           if (t == FAILURE)
8459             break;
8460
8461           gfc_check_pointer_assign (code->expr1, code->expr2);
8462           break;
8463
8464         case EXEC_ARITHMETIC_IF:
8465           if (t == SUCCESS
8466               && code->expr1->ts.type != BT_INTEGER
8467               && code->expr1->ts.type != BT_REAL)
8468             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8469                        "expression", &code->expr1->where);
8470
8471           resolve_branch (code->label1, code);
8472           resolve_branch (code->label2, code);
8473           resolve_branch (code->label3, code);
8474           break;
8475
8476         case EXEC_IF:
8477           if (t == SUCCESS && code->expr1 != NULL
8478               && (code->expr1->ts.type != BT_LOGICAL
8479                   || code->expr1->rank != 0))
8480             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8481                        &code->expr1->where);
8482           break;
8483
8484         case EXEC_CALL:
8485         call:
8486           resolve_call (code);
8487           break;
8488
8489         case EXEC_COMPCALL:
8490         compcall:
8491           resolve_typebound_subroutine (code);
8492           break;
8493
8494         case EXEC_CALL_PPC:
8495           resolve_ppc_call (code);
8496           break;
8497
8498         case EXEC_SELECT:
8499           /* Select is complicated. Also, a SELECT construct could be
8500              a transformed computed GOTO.  */
8501           resolve_select (code);
8502           break;
8503
8504         case EXEC_SELECT_TYPE:
8505           resolve_select_type (code);
8506           break;
8507
8508         case EXEC_BLOCK:
8509           gfc_resolve (code->ext.ns);
8510           break;
8511
8512         case EXEC_DO:
8513           if (code->ext.iterator != NULL)
8514             {
8515               gfc_iterator *iter = code->ext.iterator;
8516               if (gfc_resolve_iterator (iter, true) != FAILURE)
8517                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8518             }
8519           break;
8520
8521         case EXEC_DO_WHILE:
8522           if (code->expr1 == NULL)
8523             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8524           if (t == SUCCESS
8525               && (code->expr1->rank != 0
8526                   || code->expr1->ts.type != BT_LOGICAL))
8527             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8528                        "a scalar LOGICAL expression", &code->expr1->where);
8529           break;
8530
8531         case EXEC_ALLOCATE:
8532           if (t == SUCCESS)
8533             resolve_allocate_deallocate (code, "ALLOCATE");
8534
8535           break;
8536
8537         case EXEC_DEALLOCATE:
8538           if (t == SUCCESS)
8539             resolve_allocate_deallocate (code, "DEALLOCATE");
8540
8541           break;
8542
8543         case EXEC_OPEN:
8544           if (gfc_resolve_open (code->ext.open) == FAILURE)
8545             break;
8546
8547           resolve_branch (code->ext.open->err, code);
8548           break;
8549
8550         case EXEC_CLOSE:
8551           if (gfc_resolve_close (code->ext.close) == FAILURE)
8552             break;
8553
8554           resolve_branch (code->ext.close->err, code);
8555           break;
8556
8557         case EXEC_BACKSPACE:
8558         case EXEC_ENDFILE:
8559         case EXEC_REWIND:
8560         case EXEC_FLUSH:
8561           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8562             break;
8563
8564           resolve_branch (code->ext.filepos->err, code);
8565           break;
8566
8567         case EXEC_INQUIRE:
8568           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8569               break;
8570
8571           resolve_branch (code->ext.inquire->err, code);
8572           break;
8573
8574         case EXEC_IOLENGTH:
8575           gcc_assert (code->ext.inquire != NULL);
8576           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8577             break;
8578
8579           resolve_branch (code->ext.inquire->err, code);
8580           break;
8581
8582         case EXEC_WAIT:
8583           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8584             break;
8585
8586           resolve_branch (code->ext.wait->err, code);
8587           resolve_branch (code->ext.wait->end, code);
8588           resolve_branch (code->ext.wait->eor, code);
8589           break;
8590
8591         case EXEC_READ:
8592         case EXEC_WRITE:
8593           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8594             break;
8595
8596           resolve_branch (code->ext.dt->err, code);
8597           resolve_branch (code->ext.dt->end, code);
8598           resolve_branch (code->ext.dt->eor, code);
8599           break;
8600
8601         case EXEC_TRANSFER:
8602           resolve_transfer (code);
8603           break;
8604
8605         case EXEC_FORALL:
8606           resolve_forall_iterators (code->ext.forall_iterator);
8607
8608           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8609             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8610                        "expression", &code->expr1->where);
8611           break;
8612
8613         case EXEC_OMP_ATOMIC:
8614         case EXEC_OMP_BARRIER:
8615         case EXEC_OMP_CRITICAL:
8616         case EXEC_OMP_FLUSH:
8617         case EXEC_OMP_DO:
8618         case EXEC_OMP_MASTER:
8619         case EXEC_OMP_ORDERED:
8620         case EXEC_OMP_SECTIONS:
8621         case EXEC_OMP_SINGLE:
8622         case EXEC_OMP_TASKWAIT:
8623         case EXEC_OMP_WORKSHARE:
8624           gfc_resolve_omp_directive (code, ns);
8625           break;
8626
8627         case EXEC_OMP_PARALLEL:
8628         case EXEC_OMP_PARALLEL_DO:
8629         case EXEC_OMP_PARALLEL_SECTIONS:
8630         case EXEC_OMP_PARALLEL_WORKSHARE:
8631         case EXEC_OMP_TASK:
8632           omp_workshare_save = omp_workshare_flag;
8633           omp_workshare_flag = 0;
8634           gfc_resolve_omp_directive (code, ns);
8635           omp_workshare_flag = omp_workshare_save;
8636           break;
8637
8638         default:
8639           gfc_internal_error ("resolve_code(): Bad statement code");
8640         }
8641     }
8642
8643   cs_base = frame.prev;
8644 }
8645
8646
8647 /* Resolve initial values and make sure they are compatible with
8648    the variable.  */
8649
8650 static void
8651 resolve_values (gfc_symbol *sym)
8652 {
8653   if (sym->value == NULL)
8654     return;
8655
8656   if (gfc_resolve_expr (sym->value) == FAILURE)
8657     return;
8658
8659   gfc_check_assign_symbol (sym, sym->value);
8660 }
8661
8662
8663 /* Verify the binding labels for common blocks that are BIND(C).  The label
8664    for a BIND(C) common block must be identical in all scoping units in which
8665    the common block is declared.  Further, the binding label can not collide
8666    with any other global entity in the program.  */
8667
8668 static void
8669 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8670 {
8671   if (comm_block_tree->n.common->is_bind_c == 1)
8672     {
8673       gfc_gsymbol *binding_label_gsym;
8674       gfc_gsymbol *comm_name_gsym;
8675
8676       /* See if a global symbol exists by the common block's name.  It may
8677          be NULL if the common block is use-associated.  */
8678       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8679                                          comm_block_tree->n.common->name);
8680       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8681         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8682                    "with the global entity '%s' at %L",
8683                    comm_block_tree->n.common->binding_label,
8684                    comm_block_tree->n.common->name,
8685                    &(comm_block_tree->n.common->where),
8686                    comm_name_gsym->name, &(comm_name_gsym->where));
8687       else if (comm_name_gsym != NULL
8688                && strcmp (comm_name_gsym->name,
8689                           comm_block_tree->n.common->name) == 0)
8690         {
8691           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8692              as expected.  */
8693           if (comm_name_gsym->binding_label == NULL)
8694             /* No binding label for common block stored yet; save this one.  */
8695             comm_name_gsym->binding_label =
8696               comm_block_tree->n.common->binding_label;
8697           else
8698             if (strcmp (comm_name_gsym->binding_label,
8699                         comm_block_tree->n.common->binding_label) != 0)
8700               {
8701                 /* Common block names match but binding labels do not.  */
8702                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8703                            "does not match the binding label '%s' for common "
8704                            "block '%s' at %L",
8705                            comm_block_tree->n.common->binding_label,
8706                            comm_block_tree->n.common->name,
8707                            &(comm_block_tree->n.common->where),
8708                            comm_name_gsym->binding_label,
8709                            comm_name_gsym->name,
8710                            &(comm_name_gsym->where));
8711                 return;
8712               }
8713         }
8714
8715       /* There is no binding label (NAME="") so we have nothing further to
8716          check and nothing to add as a global symbol for the label.  */
8717       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8718         return;
8719       
8720       binding_label_gsym =
8721         gfc_find_gsymbol (gfc_gsym_root,
8722                           comm_block_tree->n.common->binding_label);
8723       if (binding_label_gsym == NULL)
8724         {
8725           /* Need to make a global symbol for the binding label to prevent
8726              it from colliding with another.  */
8727           binding_label_gsym =
8728             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8729           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8730           binding_label_gsym->type = GSYM_COMMON;
8731         }
8732       else
8733         {
8734           /* If comm_name_gsym is NULL, the name common block is use
8735              associated and the name could be colliding.  */
8736           if (binding_label_gsym->type != GSYM_COMMON)
8737             gfc_error ("Binding label '%s' for common block '%s' at %L "
8738                        "collides with the global entity '%s' at %L",
8739                        comm_block_tree->n.common->binding_label,
8740                        comm_block_tree->n.common->name,
8741                        &(comm_block_tree->n.common->where),
8742                        binding_label_gsym->name,
8743                        &(binding_label_gsym->where));
8744           else if (comm_name_gsym != NULL
8745                    && (strcmp (binding_label_gsym->name,
8746                                comm_name_gsym->binding_label) != 0)
8747                    && (strcmp (binding_label_gsym->sym_name,
8748                                comm_name_gsym->name) != 0))
8749             gfc_error ("Binding label '%s' for common block '%s' at %L "
8750                        "collides with global entity '%s' at %L",
8751                        binding_label_gsym->name, binding_label_gsym->sym_name,
8752                        &(comm_block_tree->n.common->where),
8753                        comm_name_gsym->name, &(comm_name_gsym->where));
8754         }
8755     }
8756   
8757   return;
8758 }
8759
8760
8761 /* Verify any BIND(C) derived types in the namespace so we can report errors
8762    for them once, rather than for each variable declared of that type.  */
8763
8764 static void
8765 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8766 {
8767   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8768       && derived_sym->attr.is_bind_c == 1)
8769     verify_bind_c_derived_type (derived_sym);
8770   
8771   return;
8772 }
8773
8774
8775 /* Verify that any binding labels used in a given namespace do not collide 
8776    with the names or binding labels of any global symbols.  */
8777
8778 static void
8779 gfc_verify_binding_labels (gfc_symbol *sym)
8780 {
8781   int has_error = 0;
8782   
8783   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8784       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8785     {
8786       gfc_gsymbol *bind_c_sym;
8787
8788       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8789       if (bind_c_sym != NULL 
8790           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8791         {
8792           if (sym->attr.if_source == IFSRC_DECL 
8793               && (bind_c_sym->type != GSYM_SUBROUTINE 
8794                   && bind_c_sym->type != GSYM_FUNCTION) 
8795               && ((sym->attr.contained == 1 
8796                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8797                   || (sym->attr.use_assoc == 1 
8798                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8799             {
8800               /* Make sure global procedures don't collide with anything.  */
8801               gfc_error ("Binding label '%s' at %L collides with the global "
8802                          "entity '%s' at %L", sym->binding_label,
8803                          &(sym->declared_at), bind_c_sym->name,
8804                          &(bind_c_sym->where));
8805               has_error = 1;
8806             }
8807           else if (sym->attr.contained == 0 
8808                    && (sym->attr.if_source == IFSRC_IFBODY 
8809                        && sym->attr.flavor == FL_PROCEDURE) 
8810                    && (bind_c_sym->sym_name != NULL 
8811                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8812             {
8813               /* Make sure procedures in interface bodies don't collide.  */
8814               gfc_error ("Binding label '%s' in interface body at %L collides "
8815                          "with the global entity '%s' at %L",
8816                          sym->binding_label,
8817                          &(sym->declared_at), bind_c_sym->name,
8818                          &(bind_c_sym->where));
8819               has_error = 1;
8820             }
8821           else if (sym->attr.contained == 0 
8822                    && sym->attr.if_source == IFSRC_UNKNOWN)
8823             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8824                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8825                 || sym->attr.use_assoc == 0)
8826               {
8827                 gfc_error ("Binding label '%s' at %L collides with global "
8828                            "entity '%s' at %L", sym->binding_label,
8829                            &(sym->declared_at), bind_c_sym->name,
8830                            &(bind_c_sym->where));
8831                 has_error = 1;
8832               }
8833
8834           if (has_error != 0)
8835             /* Clear the binding label to prevent checking multiple times.  */
8836             sym->binding_label[0] = '\0';
8837         }
8838       else if (bind_c_sym == NULL)
8839         {
8840           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8841           bind_c_sym->where = sym->declared_at;
8842           bind_c_sym->sym_name = sym->name;
8843
8844           if (sym->attr.use_assoc == 1)
8845             bind_c_sym->mod_name = sym->module;
8846           else
8847             if (sym->ns->proc_name != NULL)
8848               bind_c_sym->mod_name = sym->ns->proc_name->name;
8849
8850           if (sym->attr.contained == 0)
8851             {
8852               if (sym->attr.subroutine)
8853                 bind_c_sym->type = GSYM_SUBROUTINE;
8854               else if (sym->attr.function)
8855                 bind_c_sym->type = GSYM_FUNCTION;
8856             }
8857         }
8858     }
8859   return;
8860 }
8861
8862
8863 /* Resolve an index expression.  */
8864
8865 static gfc_try
8866 resolve_index_expr (gfc_expr *e)
8867 {
8868   if (gfc_resolve_expr (e) == FAILURE)
8869     return FAILURE;
8870
8871   if (gfc_simplify_expr (e, 0) == FAILURE)
8872     return FAILURE;
8873
8874   if (gfc_specification_expr (e) == FAILURE)
8875     return FAILURE;
8876
8877   return SUCCESS;
8878 }
8879
8880 /* Resolve a charlen structure.  */
8881
8882 static gfc_try
8883 resolve_charlen (gfc_charlen *cl)
8884 {
8885   int i, k;
8886
8887   if (cl->resolved)
8888     return SUCCESS;
8889
8890   cl->resolved = 1;
8891
8892   specification_expr = 1;
8893
8894   if (resolve_index_expr (cl->length) == FAILURE)
8895     {
8896       specification_expr = 0;
8897       return FAILURE;
8898     }
8899
8900   /* "If the character length parameter value evaluates to a negative
8901      value, the length of character entities declared is zero."  */
8902   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8903     {
8904       if (gfc_option.warn_surprising)
8905         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
8906                          " the length has been set to zero",
8907                          &cl->length->where, i);
8908       gfc_replace_expr (cl->length,
8909                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
8910     }
8911
8912   /* Check that the character length is not too large.  */
8913   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8914   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8915       && cl->length->ts.type == BT_INTEGER
8916       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8917     {
8918       gfc_error ("String length at %L is too large", &cl->length->where);
8919       return FAILURE;
8920     }
8921
8922   return SUCCESS;
8923 }
8924
8925
8926 /* Test for non-constant shape arrays.  */
8927
8928 static bool
8929 is_non_constant_shape_array (gfc_symbol *sym)
8930 {
8931   gfc_expr *e;
8932   int i;
8933   bool not_constant;
8934
8935   not_constant = false;
8936   if (sym->as != NULL)
8937     {
8938       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8939          has not been simplified; parameter array references.  Do the
8940          simplification now.  */
8941       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
8942         {
8943           e = sym->as->lower[i];
8944           if (e && (resolve_index_expr (e) == FAILURE
8945                     || !gfc_is_constant_expr (e)))
8946             not_constant = true;
8947           e = sym->as->upper[i];
8948           if (e && (resolve_index_expr (e) == FAILURE
8949                     || !gfc_is_constant_expr (e)))
8950             not_constant = true;
8951         }
8952     }
8953   return not_constant;
8954 }
8955
8956 /* Given a symbol and an initialization expression, add code to initialize
8957    the symbol to the function entry.  */
8958 static void
8959 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8960 {
8961   gfc_expr *lval;
8962   gfc_code *init_st;
8963   gfc_namespace *ns = sym->ns;
8964
8965   /* Search for the function namespace if this is a contained
8966      function without an explicit result.  */
8967   if (sym->attr.function && sym == sym->result
8968       && sym->name != sym->ns->proc_name->name)
8969     {
8970       ns = ns->contained;
8971       for (;ns; ns = ns->sibling)
8972         if (strcmp (ns->proc_name->name, sym->name) == 0)
8973           break;
8974     }
8975
8976   if (ns == NULL)
8977     {
8978       gfc_free_expr (init);
8979       return;
8980     }
8981
8982   /* Build an l-value expression for the result.  */
8983   lval = gfc_lval_expr_from_sym (sym);
8984
8985   /* Add the code at scope entry.  */
8986   init_st = gfc_get_code ();
8987   init_st->next = ns->code;
8988   ns->code = init_st;
8989
8990   /* Assign the default initializer to the l-value.  */
8991   init_st->loc = sym->declared_at;
8992   init_st->op = EXEC_INIT_ASSIGN;
8993   init_st->expr1 = lval;
8994   init_st->expr2 = init;
8995 }
8996
8997 /* Assign the default initializer to a derived type variable or result.  */
8998
8999 static void
9000 apply_default_init (gfc_symbol *sym)
9001 {
9002   gfc_expr *init = NULL;
9003
9004   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9005     return;
9006
9007   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9008     init = gfc_default_initializer (&sym->ts);
9009
9010   if (init == NULL)
9011     return;
9012
9013   build_init_assign (sym, init);
9014 }
9015
9016 /* Build an initializer for a local integer, real, complex, logical, or
9017    character variable, based on the command line flags finit-local-zero,
9018    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9019    null if the symbol should not have a default initialization.  */
9020 static gfc_expr *
9021 build_default_init_expr (gfc_symbol *sym)
9022 {
9023   int char_len;
9024   gfc_expr *init_expr;
9025   int i;
9026
9027   /* These symbols should never have a default initialization.  */
9028   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9029       || sym->attr.external
9030       || sym->attr.dummy
9031       || sym->attr.pointer
9032       || sym->attr.in_equivalence
9033       || sym->attr.in_common
9034       || sym->attr.data
9035       || sym->module
9036       || sym->attr.cray_pointee
9037       || sym->attr.cray_pointer)
9038     return NULL;
9039
9040   /* Now we'll try to build an initializer expression.  */
9041   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9042                                      &sym->declared_at);
9043
9044   /* We will only initialize integers, reals, complex, logicals, and
9045      characters, and only if the corresponding command-line flags
9046      were set.  Otherwise, we free init_expr and return null.  */
9047   switch (sym->ts.type)
9048     {    
9049     case BT_INTEGER:
9050       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9051         mpz_init_set_si (init_expr->value.integer, 
9052                          gfc_option.flag_init_integer_value);
9053       else
9054         {
9055           gfc_free_expr (init_expr);
9056           init_expr = NULL;
9057         }
9058       break;
9059
9060     case BT_REAL:
9061       mpfr_init (init_expr->value.real);
9062       switch (gfc_option.flag_init_real)
9063         {
9064         case GFC_INIT_REAL_SNAN:
9065           init_expr->is_snan = 1;
9066           /* Fall through.  */
9067         case GFC_INIT_REAL_NAN:
9068           mpfr_set_nan (init_expr->value.real);
9069           break;
9070
9071         case GFC_INIT_REAL_INF:
9072           mpfr_set_inf (init_expr->value.real, 1);
9073           break;
9074
9075         case GFC_INIT_REAL_NEG_INF:
9076           mpfr_set_inf (init_expr->value.real, -1);
9077           break;
9078
9079         case GFC_INIT_REAL_ZERO:
9080           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9081           break;
9082
9083         default:
9084           gfc_free_expr (init_expr);
9085           init_expr = NULL;
9086           break;
9087         }
9088       break;
9089           
9090     case BT_COMPLEX:
9091       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
9092       switch (gfc_option.flag_init_real)
9093         {
9094         case GFC_INIT_REAL_SNAN:
9095           init_expr->is_snan = 1;
9096           /* Fall through.  */
9097         case GFC_INIT_REAL_NAN:
9098           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9099           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9100           break;
9101
9102         case GFC_INIT_REAL_INF:
9103           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9104           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9105           break;
9106
9107         case GFC_INIT_REAL_NEG_INF:
9108           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9109           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9110           break;
9111
9112         case GFC_INIT_REAL_ZERO:
9113           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9114           break;
9115
9116         default:
9117           gfc_free_expr (init_expr);
9118           init_expr = NULL;
9119           break;
9120         }
9121       break;
9122           
9123     case BT_LOGICAL:
9124       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9125         init_expr->value.logical = 0;
9126       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9127         init_expr->value.logical = 1;
9128       else
9129         {
9130           gfc_free_expr (init_expr);
9131           init_expr = NULL;
9132         }
9133       break;
9134           
9135     case BT_CHARACTER:
9136       /* For characters, the length must be constant in order to 
9137          create a default initializer.  */
9138       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9139           && sym->ts.u.cl->length
9140           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9141         {
9142           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9143           init_expr->value.character.length = char_len;
9144           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9145           for (i = 0; i < char_len; i++)
9146             init_expr->value.character.string[i]
9147               = (unsigned char) gfc_option.flag_init_character_value;
9148         }
9149       else
9150         {
9151           gfc_free_expr (init_expr);
9152           init_expr = NULL;
9153         }
9154       break;
9155           
9156     default:
9157      gfc_free_expr (init_expr);
9158      init_expr = NULL;
9159     }
9160   return init_expr;
9161 }
9162
9163 /* Add an initialization expression to a local variable.  */
9164 static void
9165 apply_default_init_local (gfc_symbol *sym)
9166 {
9167   gfc_expr *init = NULL;
9168
9169   /* The symbol should be a variable or a function return value.  */
9170   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9171       || (sym->attr.function && sym->result != sym))
9172     return;
9173
9174   /* Try to build the initializer expression.  If we can't initialize
9175      this symbol, then init will be NULL.  */
9176   init = build_default_init_expr (sym);
9177   if (init == NULL)
9178     return;
9179
9180   /* For saved variables, we don't want to add an initializer at 
9181      function entry, so we just add a static initializer.  */
9182   if (sym->attr.save || sym->ns->save_all 
9183       || gfc_option.flag_max_stack_var_size == 0)
9184     {
9185       /* Don't clobber an existing initializer!  */
9186       gcc_assert (sym->value == NULL);
9187       sym->value = init;
9188       return;
9189     }
9190
9191   build_init_assign (sym, init);
9192 }
9193
9194 /* Resolution of common features of flavors variable and procedure.  */
9195
9196 static gfc_try
9197 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9198 {
9199   /* Constraints on deferred shape variable.  */
9200   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9201     {
9202       if (sym->attr.allocatable)
9203         {
9204           if (sym->attr.dimension)
9205             {
9206               gfc_error ("Allocatable array '%s' at %L must have "
9207                          "a deferred shape", sym->name, &sym->declared_at);
9208               return FAILURE;
9209             }
9210           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9211                                    "may not be ALLOCATABLE", sym->name,
9212                                    &sym->declared_at) == FAILURE)
9213             return FAILURE;
9214         }
9215
9216       if (sym->attr.pointer && sym->attr.dimension)
9217         {
9218           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9219                      sym->name, &sym->declared_at);
9220           return FAILURE;
9221         }
9222
9223     }
9224   else
9225     {
9226       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9227           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
9228         {
9229           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9230                      sym->name, &sym->declared_at);
9231           return FAILURE;
9232          }
9233     }
9234   return SUCCESS;
9235 }
9236
9237
9238 /* Additional checks for symbols with flavor variable and derived
9239    type.  To be called from resolve_fl_variable.  */
9240
9241 static gfc_try
9242 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9243 {
9244   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9245
9246   /* Check to see if a derived type is blocked from being host
9247      associated by the presence of another class I symbol in the same
9248      namespace.  14.6.1.3 of the standard and the discussion on
9249      comp.lang.fortran.  */
9250   if (sym->ns != sym->ts.u.derived->ns
9251       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9252     {
9253       gfc_symbol *s;
9254       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9255       if (s && s->attr.flavor != FL_DERIVED)
9256         {
9257           gfc_error ("The type '%s' cannot be host associated at %L "
9258                      "because it is blocked by an incompatible object "
9259                      "of the same name declared at %L",
9260                      sym->ts.u.derived->name, &sym->declared_at,
9261                      &s->declared_at);
9262           return FAILURE;
9263         }
9264     }
9265
9266   /* 4th constraint in section 11.3: "If an object of a type for which
9267      component-initialization is specified (R429) appears in the
9268      specification-part of a module and does not have the ALLOCATABLE
9269      or POINTER attribute, the object shall have the SAVE attribute."
9270
9271      The check for initializers is performed with
9272      has_default_initializer because gfc_default_initializer generates
9273      a hidden default for allocatable components.  */
9274   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9275       && sym->ns->proc_name->attr.flavor == FL_MODULE
9276       && !sym->ns->save_all && !sym->attr.save
9277       && !sym->attr.pointer && !sym->attr.allocatable
9278       && has_default_initializer (sym->ts.u.derived)
9279       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9280                          "module variable '%s' at %L, needed due to "
9281                          "the default initialization", sym->name,
9282                          &sym->declared_at) == FAILURE)
9283     return FAILURE;
9284
9285   if (sym->ts.type == BT_CLASS)
9286     {
9287       /* C502.  */
9288       if (!gfc_type_is_extensible (sym->ts.u.derived->components->ts.u.derived))
9289         {
9290           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9291                      sym->ts.u.derived->components->ts.u.derived->name,
9292                      sym->name, &sym->declared_at);
9293           return FAILURE;
9294         }
9295
9296       /* C509.  */
9297       /* Assume that use associated symbols were checked in the module ns.  */ 
9298       if (!sym->attr.class_ok && !sym->attr.use_assoc)
9299         {
9300           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9301                      "or pointer", sym->name, &sym->declared_at);
9302           return FAILURE;
9303         }
9304     }
9305
9306   /* Assign default initializer.  */
9307   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9308       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9309     {
9310       sym->value = gfc_default_initializer (&sym->ts);
9311     }
9312
9313   return SUCCESS;
9314 }
9315
9316
9317 /* Resolve symbols with flavor variable.  */
9318
9319 static gfc_try
9320 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9321 {
9322   int no_init_flag, automatic_flag;
9323   gfc_expr *e;
9324   const char *auto_save_msg;
9325
9326   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9327                   "SAVE attribute";
9328
9329   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9330     return FAILURE;
9331
9332   /* Set this flag to check that variables are parameters of all entries.
9333      This check is effected by the call to gfc_resolve_expr through
9334      is_non_constant_shape_array.  */
9335   specification_expr = 1;
9336
9337   if (sym->ns->proc_name
9338       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9339           || sym->ns->proc_name->attr.is_main_program)
9340       && !sym->attr.use_assoc
9341       && !sym->attr.allocatable
9342       && !sym->attr.pointer
9343       && is_non_constant_shape_array (sym))
9344     {
9345       /* The shape of a main program or module array needs to be
9346          constant.  */
9347       gfc_error ("The module or main program array '%s' at %L must "
9348                  "have constant shape", sym->name, &sym->declared_at);
9349       specification_expr = 0;
9350       return FAILURE;
9351     }
9352
9353   if (sym->ts.type == BT_CHARACTER)
9354     {
9355       /* Make sure that character string variables with assumed length are
9356          dummy arguments.  */
9357       e = sym->ts.u.cl->length;
9358       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9359         {
9360           gfc_error ("Entity with assumed character length at %L must be a "
9361                      "dummy argument or a PARAMETER", &sym->declared_at);
9362           return FAILURE;
9363         }
9364
9365       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9366         {
9367           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9368           return FAILURE;
9369         }
9370
9371       if (!gfc_is_constant_expr (e)
9372           && !(e->expr_type == EXPR_VARIABLE
9373                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9374           && sym->ns->proc_name
9375           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9376               || sym->ns->proc_name->attr.is_main_program)
9377           && !sym->attr.use_assoc)
9378         {
9379           gfc_error ("'%s' at %L must have constant character length "
9380                      "in this context", sym->name, &sym->declared_at);
9381           return FAILURE;
9382         }
9383     }
9384
9385   if (sym->value == NULL && sym->attr.referenced)
9386     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9387
9388   /* Determine if the symbol may not have an initializer.  */
9389   no_init_flag = automatic_flag = 0;
9390   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9391       || sym->attr.intrinsic || sym->attr.result)
9392     no_init_flag = 1;
9393   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9394            && is_non_constant_shape_array (sym))
9395     {
9396       no_init_flag = automatic_flag = 1;
9397
9398       /* Also, they must not have the SAVE attribute.
9399          SAVE_IMPLICIT is checked below.  */
9400       if (sym->attr.save == SAVE_EXPLICIT)
9401         {
9402           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9403           return FAILURE;
9404         }
9405     }
9406
9407   /* Ensure that any initializer is simplified.  */
9408   if (sym->value)
9409     gfc_simplify_expr (sym->value, 1);
9410
9411   /* Reject illegal initializers.  */
9412   if (!sym->mark && sym->value)
9413     {
9414       if (sym->attr.allocatable)
9415         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9416                    sym->name, &sym->declared_at);
9417       else if (sym->attr.external)
9418         gfc_error ("External '%s' at %L cannot have an initializer",
9419                    sym->name, &sym->declared_at);
9420       else if (sym->attr.dummy
9421         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9422         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9423                    sym->name, &sym->declared_at);
9424       else if (sym->attr.intrinsic)
9425         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9426                    sym->name, &sym->declared_at);
9427       else if (sym->attr.result)
9428         gfc_error ("Function result '%s' at %L cannot have an initializer",
9429                    sym->name, &sym->declared_at);
9430       else if (automatic_flag)
9431         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9432                    sym->name, &sym->declared_at);
9433       else
9434         goto no_init_error;
9435       return FAILURE;
9436     }
9437
9438 no_init_error:
9439   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9440     return resolve_fl_variable_derived (sym, no_init_flag);
9441
9442   return SUCCESS;
9443 }
9444
9445
9446 /* Resolve a procedure.  */
9447
9448 static gfc_try
9449 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9450 {
9451   gfc_formal_arglist *arg;
9452
9453   if (sym->attr.function
9454       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9455     return FAILURE;
9456
9457   if (sym->ts.type == BT_CHARACTER)
9458     {
9459       gfc_charlen *cl = sym->ts.u.cl;
9460
9461       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9462              && resolve_charlen (cl) == FAILURE)
9463         return FAILURE;
9464
9465       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9466           && sym->attr.proc == PROC_ST_FUNCTION)
9467         {
9468           gfc_error ("Character-valued statement function '%s' at %L must "
9469                      "have constant length", sym->name, &sym->declared_at);
9470           return FAILURE;
9471         }
9472     }
9473
9474   /* Ensure that derived type for are not of a private type.  Internal
9475      module procedures are excluded by 2.2.3.3 - i.e., they are not
9476      externally accessible and can access all the objects accessible in
9477      the host.  */
9478   if (!(sym->ns->parent
9479         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9480       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9481     {
9482       gfc_interface *iface;
9483
9484       for (arg = sym->formal; arg; arg = arg->next)
9485         {
9486           if (arg->sym
9487               && arg->sym->ts.type == BT_DERIVED
9488               && !arg->sym->ts.u.derived->attr.use_assoc
9489               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9490                                     arg->sym->ts.u.derived->ns->default_access)
9491               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9492                                  "PRIVATE type and cannot be a dummy argument"
9493                                  " of '%s', which is PUBLIC at %L",
9494                                  arg->sym->name, sym->name, &sym->declared_at)
9495                  == FAILURE)
9496             {
9497               /* Stop this message from recurring.  */
9498               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9499               return FAILURE;
9500             }
9501         }
9502
9503       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9504          PRIVATE to the containing module.  */
9505       for (iface = sym->generic; iface; iface = iface->next)
9506         {
9507           for (arg = iface->sym->formal; arg; arg = arg->next)
9508             {
9509               if (arg->sym
9510                   && arg->sym->ts.type == BT_DERIVED
9511                   && !arg->sym->ts.u.derived->attr.use_assoc
9512                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9513                                         arg->sym->ts.u.derived->ns->default_access)
9514                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9515                                      "'%s' in PUBLIC interface '%s' at %L "
9516                                      "takes dummy arguments of '%s' which is "
9517                                      "PRIVATE", iface->sym->name, sym->name,
9518                                      &iface->sym->declared_at,
9519                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9520                 {
9521                   /* Stop this message from recurring.  */
9522                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9523                   return FAILURE;
9524                 }
9525              }
9526         }
9527
9528       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9529          PRIVATE to the containing module.  */
9530       for (iface = sym->generic; iface; iface = iface->next)
9531         {
9532           for (arg = iface->sym->formal; arg; arg = arg->next)
9533             {
9534               if (arg->sym
9535                   && arg->sym->ts.type == BT_DERIVED
9536                   && !arg->sym->ts.u.derived->attr.use_assoc
9537                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9538                                         arg->sym->ts.u.derived->ns->default_access)
9539                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9540                                      "'%s' in PUBLIC interface '%s' at %L "
9541                                      "takes dummy arguments of '%s' which is "
9542                                      "PRIVATE", iface->sym->name, sym->name,
9543                                      &iface->sym->declared_at,
9544                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9545                 {
9546                   /* Stop this message from recurring.  */
9547                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9548                   return FAILURE;
9549                 }
9550              }
9551         }
9552     }
9553
9554   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9555       && !sym->attr.proc_pointer)
9556     {
9557       gfc_error ("Function '%s' at %L cannot have an initializer",
9558                  sym->name, &sym->declared_at);
9559       return FAILURE;
9560     }
9561
9562   /* An external symbol may not have an initializer because it is taken to be
9563      a procedure. Exception: Procedure Pointers.  */
9564   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9565     {
9566       gfc_error ("External object '%s' at %L may not have an initializer",
9567                  sym->name, &sym->declared_at);
9568       return FAILURE;
9569     }
9570
9571   /* An elemental function is required to return a scalar 12.7.1  */
9572   if (sym->attr.elemental && sym->attr.function && sym->as)
9573     {
9574       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9575                  "result", sym->name, &sym->declared_at);
9576       /* Reset so that the error only occurs once.  */
9577       sym->attr.elemental = 0;
9578       return FAILURE;
9579     }
9580
9581   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9582      char-len-param shall not be array-valued, pointer-valued, recursive
9583      or pure.  ....snip... A character value of * may only be used in the
9584      following ways: (i) Dummy arg of procedure - dummy associates with
9585      actual length; (ii) To declare a named constant; or (iii) External
9586      function - but length must be declared in calling scoping unit.  */
9587   if (sym->attr.function
9588       && sym->ts.type == BT_CHARACTER
9589       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9590     {
9591       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9592           || (sym->attr.recursive) || (sym->attr.pure))
9593         {
9594           if (sym->as && sym->as->rank)
9595             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9596                        "array-valued", sym->name, &sym->declared_at);
9597
9598           if (sym->attr.pointer)
9599             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9600                        "pointer-valued", sym->name, &sym->declared_at);
9601
9602           if (sym->attr.pure)
9603             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9604                        "pure", sym->name, &sym->declared_at);
9605
9606           if (sym->attr.recursive)
9607             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9608                        "recursive", sym->name, &sym->declared_at);
9609
9610           return FAILURE;
9611         }
9612
9613       /* Appendix B.2 of the standard.  Contained functions give an
9614          error anyway.  Fixed-form is likely to be F77/legacy.  */
9615       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9616         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9617                         "CHARACTER(*) function '%s' at %L",
9618                         sym->name, &sym->declared_at);
9619     }
9620
9621   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9622     {
9623       gfc_formal_arglist *curr_arg;
9624       int has_non_interop_arg = 0;
9625
9626       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9627                              sym->common_block) == FAILURE)
9628         {
9629           /* Clear these to prevent looking at them again if there was an
9630              error.  */
9631           sym->attr.is_bind_c = 0;
9632           sym->attr.is_c_interop = 0;
9633           sym->ts.is_c_interop = 0;
9634         }
9635       else
9636         {
9637           /* So far, no errors have been found.  */
9638           sym->attr.is_c_interop = 1;
9639           sym->ts.is_c_interop = 1;
9640         }
9641       
9642       curr_arg = sym->formal;
9643       while (curr_arg != NULL)
9644         {
9645           /* Skip implicitly typed dummy args here.  */
9646           if (curr_arg->sym->attr.implicit_type == 0)
9647             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9648               /* If something is found to fail, record the fact so we
9649                  can mark the symbol for the procedure as not being
9650                  BIND(C) to try and prevent multiple errors being
9651                  reported.  */
9652               has_non_interop_arg = 1;
9653           
9654           curr_arg = curr_arg->next;
9655         }
9656
9657       /* See if any of the arguments were not interoperable and if so, clear
9658          the procedure symbol to prevent duplicate error messages.  */
9659       if (has_non_interop_arg != 0)
9660         {
9661           sym->attr.is_c_interop = 0;
9662           sym->ts.is_c_interop = 0;
9663           sym->attr.is_bind_c = 0;
9664         }
9665     }
9666   
9667   if (!sym->attr.proc_pointer)
9668     {
9669       if (sym->attr.save == SAVE_EXPLICIT)
9670         {
9671           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9672                      "in '%s' at %L", sym->name, &sym->declared_at);
9673           return FAILURE;
9674         }
9675       if (sym->attr.intent)
9676         {
9677           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9678                      "in '%s' at %L", sym->name, &sym->declared_at);
9679           return FAILURE;
9680         }
9681       if (sym->attr.subroutine && sym->attr.result)
9682         {
9683           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9684                      "in '%s' at %L", sym->name, &sym->declared_at);
9685           return FAILURE;
9686         }
9687       if (sym->attr.external && sym->attr.function
9688           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9689               || sym->attr.contained))
9690         {
9691           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9692                      "in '%s' at %L", sym->name, &sym->declared_at);
9693           return FAILURE;
9694         }
9695       if (strcmp ("ppr@", sym->name) == 0)
9696         {
9697           gfc_error ("Procedure pointer result '%s' at %L "
9698                      "is missing the pointer attribute",
9699                      sym->ns->proc_name->name, &sym->declared_at);
9700           return FAILURE;
9701         }
9702     }
9703
9704   return SUCCESS;
9705 }
9706
9707
9708 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9709    been defined and we now know their defined arguments, check that they fulfill
9710    the requirements of the standard for procedures used as finalizers.  */
9711
9712 static gfc_try
9713 gfc_resolve_finalizers (gfc_symbol* derived)
9714 {
9715   gfc_finalizer* list;
9716   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9717   gfc_try result = SUCCESS;
9718   bool seen_scalar = false;
9719
9720   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9721     return SUCCESS;
9722
9723   /* Walk over the list of finalizer-procedures, check them, and if any one
9724      does not fit in with the standard's definition, print an error and remove
9725      it from the list.  */
9726   prev_link = &derived->f2k_derived->finalizers;
9727   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9728     {
9729       gfc_symbol* arg;
9730       gfc_finalizer* i;
9731       int my_rank;
9732
9733       /* Skip this finalizer if we already resolved it.  */
9734       if (list->proc_tree)
9735         {
9736           prev_link = &(list->next);
9737           continue;
9738         }
9739
9740       /* Check this exists and is a SUBROUTINE.  */
9741       if (!list->proc_sym->attr.subroutine)
9742         {
9743           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9744                      list->proc_sym->name, &list->where);
9745           goto error;
9746         }
9747
9748       /* We should have exactly one argument.  */
9749       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9750         {
9751           gfc_error ("FINAL procedure at %L must have exactly one argument",
9752                      &list->where);
9753           goto error;
9754         }
9755       arg = list->proc_sym->formal->sym;
9756
9757       /* This argument must be of our type.  */
9758       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9759         {
9760           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9761                      &arg->declared_at, derived->name);
9762           goto error;
9763         }
9764
9765       /* It must neither be a pointer nor allocatable nor optional.  */
9766       if (arg->attr.pointer)
9767         {
9768           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9769                      &arg->declared_at);
9770           goto error;
9771         }
9772       if (arg->attr.allocatable)
9773         {
9774           gfc_error ("Argument of FINAL procedure at %L must not be"
9775                      " ALLOCATABLE", &arg->declared_at);
9776           goto error;
9777         }
9778       if (arg->attr.optional)
9779         {
9780           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9781                      &arg->declared_at);
9782           goto error;
9783         }
9784
9785       /* It must not be INTENT(OUT).  */
9786       if (arg->attr.intent == INTENT_OUT)
9787         {
9788           gfc_error ("Argument of FINAL procedure at %L must not be"
9789                      " INTENT(OUT)", &arg->declared_at);
9790           goto error;
9791         }
9792
9793       /* Warn if the procedure is non-scalar and not assumed shape.  */
9794       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9795           && arg->as->type != AS_ASSUMED_SHAPE)
9796         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9797                      " shape argument", &arg->declared_at);
9798
9799       /* Check that it does not match in kind and rank with a FINAL procedure
9800          defined earlier.  To really loop over the *earlier* declarations,
9801          we need to walk the tail of the list as new ones were pushed at the
9802          front.  */
9803       /* TODO: Handle kind parameters once they are implemented.  */
9804       my_rank = (arg->as ? arg->as->rank : 0);
9805       for (i = list->next; i; i = i->next)
9806         {
9807           /* Argument list might be empty; that is an error signalled earlier,
9808              but we nevertheless continued resolving.  */
9809           if (i->proc_sym->formal)
9810             {
9811               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9812               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9813               if (i_rank == my_rank)
9814                 {
9815                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9816                              " rank (%d) as '%s'",
9817                              list->proc_sym->name, &list->where, my_rank, 
9818                              i->proc_sym->name);
9819                   goto error;
9820                 }
9821             }
9822         }
9823
9824         /* Is this the/a scalar finalizer procedure?  */
9825         if (!arg->as || arg->as->rank == 0)
9826           seen_scalar = true;
9827
9828         /* Find the symtree for this procedure.  */
9829         gcc_assert (!list->proc_tree);
9830         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9831
9832         prev_link = &list->next;
9833         continue;
9834
9835         /* Remove wrong nodes immediately from the list so we don't risk any
9836            troubles in the future when they might fail later expectations.  */
9837 error:
9838         result = FAILURE;
9839         i = list;
9840         *prev_link = list->next;
9841         gfc_free_finalizer (i);
9842     }
9843
9844   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9845      were nodes in the list, must have been for arrays.  It is surely a good
9846      idea to have a scalar version there if there's something to finalize.  */
9847   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9848     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9849                  " defined at %L, suggest also scalar one",
9850                  derived->name, &derived->declared_at);
9851
9852   /* TODO:  Remove this error when finalization is finished.  */
9853   gfc_error ("Finalization at %L is not yet implemented",
9854              &derived->declared_at);
9855
9856   return result;
9857 }
9858
9859
9860 /* Check that it is ok for the typebound procedure proc to override the
9861    procedure old.  */
9862
9863 static gfc_try
9864 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9865 {
9866   locus where;
9867   const gfc_symbol* proc_target;
9868   const gfc_symbol* old_target;
9869   unsigned proc_pass_arg, old_pass_arg, argpos;
9870   gfc_formal_arglist* proc_formal;
9871   gfc_formal_arglist* old_formal;
9872
9873   /* This procedure should only be called for non-GENERIC proc.  */
9874   gcc_assert (!proc->n.tb->is_generic);
9875
9876   /* If the overwritten procedure is GENERIC, this is an error.  */
9877   if (old->n.tb->is_generic)
9878     {
9879       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9880                  old->name, &proc->n.tb->where);
9881       return FAILURE;
9882     }
9883
9884   where = proc->n.tb->where;
9885   proc_target = proc->n.tb->u.specific->n.sym;
9886   old_target = old->n.tb->u.specific->n.sym;
9887
9888   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9889   if (old->n.tb->non_overridable)
9890     {
9891       gfc_error ("'%s' at %L overrides a procedure binding declared"
9892                  " NON_OVERRIDABLE", proc->name, &where);
9893       return FAILURE;
9894     }
9895
9896   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9897   if (!old->n.tb->deferred && proc->n.tb->deferred)
9898     {
9899       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9900                  " non-DEFERRED binding", proc->name, &where);
9901       return FAILURE;
9902     }
9903
9904   /* If the overridden binding is PURE, the overriding must be, too.  */
9905   if (old_target->attr.pure && !proc_target->attr.pure)
9906     {
9907       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9908                  proc->name, &where);
9909       return FAILURE;
9910     }
9911
9912   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9913      is not, the overriding must not be either.  */
9914   if (old_target->attr.elemental && !proc_target->attr.elemental)
9915     {
9916       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9917                  " ELEMENTAL", proc->name, &where);
9918       return FAILURE;
9919     }
9920   if (!old_target->attr.elemental && proc_target->attr.elemental)
9921     {
9922       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9923                  " be ELEMENTAL, either", proc->name, &where);
9924       return FAILURE;
9925     }
9926
9927   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9928      SUBROUTINE.  */
9929   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9930     {
9931       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9932                  " SUBROUTINE", proc->name, &where);
9933       return FAILURE;
9934     }
9935
9936   /* If the overridden binding is a FUNCTION, the overriding must also be a
9937      FUNCTION and have the same characteristics.  */
9938   if (old_target->attr.function)
9939     {
9940       if (!proc_target->attr.function)
9941         {
9942           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9943                      " FUNCTION", proc->name, &where);
9944           return FAILURE;
9945         }
9946
9947       /* FIXME:  Do more comprehensive checking (including, for instance, the
9948          rank and array-shape).  */
9949       gcc_assert (proc_target->result && old_target->result);
9950       if (!gfc_compare_types (&proc_target->result->ts,
9951                               &old_target->result->ts))
9952         {
9953           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9954                      " matching result types", proc->name, &where);
9955           return FAILURE;
9956         }
9957     }
9958
9959   /* If the overridden binding is PUBLIC, the overriding one must not be
9960      PRIVATE.  */
9961   if (old->n.tb->access == ACCESS_PUBLIC
9962       && proc->n.tb->access == ACCESS_PRIVATE)
9963     {
9964       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9965                  " PRIVATE", proc->name, &where);
9966       return FAILURE;
9967     }
9968
9969   /* Compare the formal argument lists of both procedures.  This is also abused
9970      to find the position of the passed-object dummy arguments of both
9971      bindings as at least the overridden one might not yet be resolved and we
9972      need those positions in the check below.  */
9973   proc_pass_arg = old_pass_arg = 0;
9974   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9975     proc_pass_arg = 1;
9976   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9977     old_pass_arg = 1;
9978   argpos = 1;
9979   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9980        proc_formal && old_formal;
9981        proc_formal = proc_formal->next, old_formal = old_formal->next)
9982     {
9983       if (proc->n.tb->pass_arg
9984           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9985         proc_pass_arg = argpos;
9986       if (old->n.tb->pass_arg
9987           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9988         old_pass_arg = argpos;
9989
9990       /* Check that the names correspond.  */
9991       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9992         {
9993           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9994                      " to match the corresponding argument of the overridden"
9995                      " procedure", proc_formal->sym->name, proc->name, &where,
9996                      old_formal->sym->name);
9997           return FAILURE;
9998         }
9999
10000       /* Check that the types correspond if neither is the passed-object
10001          argument.  */
10002       /* FIXME:  Do more comprehensive testing here.  */
10003       if (proc_pass_arg != argpos && old_pass_arg != argpos
10004           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10005         {
10006           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10007                      "in respect to the overridden procedure",
10008                      proc_formal->sym->name, proc->name, &where);
10009           return FAILURE;
10010         }
10011
10012       ++argpos;
10013     }
10014   if (proc_formal || old_formal)
10015     {
10016       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10017                  " the overridden procedure", proc->name, &where);
10018       return FAILURE;
10019     }
10020
10021   /* If the overridden binding is NOPASS, the overriding one must also be
10022      NOPASS.  */
10023   if (old->n.tb->nopass && !proc->n.tb->nopass)
10024     {
10025       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10026                  " NOPASS", proc->name, &where);
10027       return FAILURE;
10028     }
10029
10030   /* If the overridden binding is PASS(x), the overriding one must also be
10031      PASS and the passed-object dummy arguments must correspond.  */
10032   if (!old->n.tb->nopass)
10033     {
10034       if (proc->n.tb->nopass)
10035         {
10036           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10037                      " PASS", proc->name, &where);
10038           return FAILURE;
10039         }
10040
10041       if (proc_pass_arg != old_pass_arg)
10042         {
10043           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10044                      " the same position as the passed-object dummy argument of"
10045                      " the overridden procedure", proc->name, &where);
10046           return FAILURE;
10047         }
10048     }
10049
10050   return SUCCESS;
10051 }
10052
10053
10054 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10055
10056 static gfc_try
10057 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10058                              const char* generic_name, locus where)
10059 {
10060   gfc_symbol* sym1;
10061   gfc_symbol* sym2;
10062
10063   gcc_assert (t1->specific && t2->specific);
10064   gcc_assert (!t1->specific->is_generic);
10065   gcc_assert (!t2->specific->is_generic);
10066
10067   sym1 = t1->specific->u.specific->n.sym;
10068   sym2 = t2->specific->u.specific->n.sym;
10069
10070   if (sym1 == sym2)
10071     return SUCCESS;
10072
10073   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10074   if (sym1->attr.subroutine != sym2->attr.subroutine
10075       || sym1->attr.function != sym2->attr.function)
10076     {
10077       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10078                  " GENERIC '%s' at %L",
10079                  sym1->name, sym2->name, generic_name, &where);
10080       return FAILURE;
10081     }
10082
10083   /* Compare the interfaces.  */
10084   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10085     {
10086       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10087                  sym1->name, sym2->name, generic_name, &where);
10088       return FAILURE;
10089     }
10090
10091   return SUCCESS;
10092 }
10093
10094
10095 /* Worker function for resolving a generic procedure binding; this is used to
10096    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10097
10098    The difference between those cases is finding possible inherited bindings
10099    that are overridden, as one has to look for them in tb_sym_root,
10100    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10101    the super-type and set p->overridden correctly.  */
10102
10103 static gfc_try
10104 resolve_tb_generic_targets (gfc_symbol* super_type,
10105                             gfc_typebound_proc* p, const char* name)
10106 {
10107   gfc_tbp_generic* target;
10108   gfc_symtree* first_target;
10109   gfc_symtree* inherited;
10110
10111   gcc_assert (p && p->is_generic);
10112
10113   /* Try to find the specific bindings for the symtrees in our target-list.  */
10114   gcc_assert (p->u.generic);
10115   for (target = p->u.generic; target; target = target->next)
10116     if (!target->specific)
10117       {
10118         gfc_typebound_proc* overridden_tbp;
10119         gfc_tbp_generic* g;
10120         const char* target_name;
10121
10122         target_name = target->specific_st->name;
10123
10124         /* Defined for this type directly.  */
10125         if (target->specific_st->n.tb)
10126           {
10127             target->specific = target->specific_st->n.tb;
10128             goto specific_found;
10129           }
10130
10131         /* Look for an inherited specific binding.  */
10132         if (super_type)
10133           {
10134             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10135                                                  true, NULL);
10136
10137             if (inherited)
10138               {
10139                 gcc_assert (inherited->n.tb);
10140                 target->specific = inherited->n.tb;
10141                 goto specific_found;
10142               }
10143           }
10144
10145         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10146                    " at %L", target_name, name, &p->where);
10147         return FAILURE;
10148
10149         /* Once we've found the specific binding, check it is not ambiguous with
10150            other specifics already found or inherited for the same GENERIC.  */
10151 specific_found:
10152         gcc_assert (target->specific);
10153
10154         /* This must really be a specific binding!  */
10155         if (target->specific->is_generic)
10156           {
10157             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10158                        " '%s' is GENERIC, too", name, &p->where, target_name);
10159             return FAILURE;
10160           }
10161
10162         /* Check those already resolved on this type directly.  */
10163         for (g = p->u.generic; g; g = g->next)
10164           if (g != target && g->specific
10165               && check_generic_tbp_ambiguity (target, g, name, p->where)
10166                   == FAILURE)
10167             return FAILURE;
10168
10169         /* Check for ambiguity with inherited specific targets.  */
10170         for (overridden_tbp = p->overridden; overridden_tbp;
10171              overridden_tbp = overridden_tbp->overridden)
10172           if (overridden_tbp->is_generic)
10173             {
10174               for (g = overridden_tbp->u.generic; g; g = g->next)
10175                 {
10176                   gcc_assert (g->specific);
10177                   if (check_generic_tbp_ambiguity (target, g,
10178                                                    name, p->where) == FAILURE)
10179                     return FAILURE;
10180                 }
10181             }
10182       }
10183
10184   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10185   if (p->overridden && !p->overridden->is_generic)
10186     {
10187       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10188                  " the same name", name, &p->where);
10189       return FAILURE;
10190     }
10191
10192   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10193      all must have the same attributes here.  */
10194   first_target = p->u.generic->specific->u.specific;
10195   gcc_assert (first_target);
10196   p->subroutine = first_target->n.sym->attr.subroutine;
10197   p->function = first_target->n.sym->attr.function;
10198
10199   return SUCCESS;
10200 }
10201
10202
10203 /* Resolve a GENERIC procedure binding for a derived type.  */
10204
10205 static gfc_try
10206 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10207 {
10208   gfc_symbol* super_type;
10209
10210   /* Find the overridden binding if any.  */
10211   st->n.tb->overridden = NULL;
10212   super_type = gfc_get_derived_super_type (derived);
10213   if (super_type)
10214     {
10215       gfc_symtree* overridden;
10216       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10217                                             true, NULL);
10218
10219       if (overridden && overridden->n.tb)
10220         st->n.tb->overridden = overridden->n.tb;
10221     }
10222
10223   /* Resolve using worker function.  */
10224   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10225 }
10226
10227
10228 /* Retrieve the target-procedure of an operator binding and do some checks in
10229    common for intrinsic and user-defined type-bound operators.  */
10230
10231 static gfc_symbol*
10232 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10233 {
10234   gfc_symbol* target_proc;
10235
10236   gcc_assert (target->specific && !target->specific->is_generic);
10237   target_proc = target->specific->u.specific->n.sym;
10238   gcc_assert (target_proc);
10239
10240   /* All operator bindings must have a passed-object dummy argument.  */
10241   if (target->specific->nopass)
10242     {
10243       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10244       return NULL;
10245     }
10246
10247   return target_proc;
10248 }
10249
10250
10251 /* Resolve a type-bound intrinsic operator.  */
10252
10253 static gfc_try
10254 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10255                                 gfc_typebound_proc* p)
10256 {
10257   gfc_symbol* super_type;
10258   gfc_tbp_generic* target;
10259   
10260   /* If there's already an error here, do nothing (but don't fail again).  */
10261   if (p->error)
10262     return SUCCESS;
10263
10264   /* Operators should always be GENERIC bindings.  */
10265   gcc_assert (p->is_generic);
10266
10267   /* Look for an overridden binding.  */
10268   super_type = gfc_get_derived_super_type (derived);
10269   if (super_type && super_type->f2k_derived)
10270     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10271                                                      op, true, NULL);
10272   else
10273     p->overridden = NULL;
10274
10275   /* Resolve general GENERIC properties using worker function.  */
10276   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10277     goto error;
10278
10279   /* Check the targets to be procedures of correct interface.  */
10280   for (target = p->u.generic; target; target = target->next)
10281     {
10282       gfc_symbol* target_proc;
10283
10284       target_proc = get_checked_tb_operator_target (target, p->where);
10285       if (!target_proc)
10286         goto error;
10287
10288       if (!gfc_check_operator_interface (target_proc, op, p->where))
10289         goto error;
10290     }
10291
10292   return SUCCESS;
10293
10294 error:
10295   p->error = 1;
10296   return FAILURE;
10297 }
10298
10299
10300 /* Resolve a type-bound user operator (tree-walker callback).  */
10301
10302 static gfc_symbol* resolve_bindings_derived;
10303 static gfc_try resolve_bindings_result;
10304
10305 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10306
10307 static void
10308 resolve_typebound_user_op (gfc_symtree* stree)
10309 {
10310   gfc_symbol* super_type;
10311   gfc_tbp_generic* target;
10312
10313   gcc_assert (stree && stree->n.tb);
10314
10315   if (stree->n.tb->error)
10316     return;
10317
10318   /* Operators should always be GENERIC bindings.  */
10319   gcc_assert (stree->n.tb->is_generic);
10320
10321   /* Find overridden procedure, if any.  */
10322   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10323   if (super_type && super_type->f2k_derived)
10324     {
10325       gfc_symtree* overridden;
10326       overridden = gfc_find_typebound_user_op (super_type, NULL,
10327                                                stree->name, true, NULL);
10328
10329       if (overridden && overridden->n.tb)
10330         stree->n.tb->overridden = overridden->n.tb;
10331     }
10332   else
10333     stree->n.tb->overridden = NULL;
10334
10335   /* Resolve basically using worker function.  */
10336   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10337         == FAILURE)
10338     goto error;
10339
10340   /* Check the targets to be functions of correct interface.  */
10341   for (target = stree->n.tb->u.generic; target; target = target->next)
10342     {
10343       gfc_symbol* target_proc;
10344
10345       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10346       if (!target_proc)
10347         goto error;
10348
10349       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10350         goto error;
10351     }
10352
10353   return;
10354
10355 error:
10356   resolve_bindings_result = FAILURE;
10357   stree->n.tb->error = 1;
10358 }
10359
10360
10361 /* Resolve the type-bound procedures for a derived type.  */
10362
10363 static void
10364 resolve_typebound_procedure (gfc_symtree* stree)
10365 {
10366   gfc_symbol* proc;
10367   locus where;
10368   gfc_symbol* me_arg;
10369   gfc_symbol* super_type;
10370   gfc_component* comp;
10371
10372   gcc_assert (stree);
10373
10374   /* Undefined specific symbol from GENERIC target definition.  */
10375   if (!stree->n.tb)
10376     return;
10377
10378   if (stree->n.tb->error)
10379     return;
10380
10381   /* If this is a GENERIC binding, use that routine.  */
10382   if (stree->n.tb->is_generic)
10383     {
10384       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10385             == FAILURE)
10386         goto error;
10387       return;
10388     }
10389
10390   /* Get the target-procedure to check it.  */
10391   gcc_assert (!stree->n.tb->is_generic);
10392   gcc_assert (stree->n.tb->u.specific);
10393   proc = stree->n.tb->u.specific->n.sym;
10394   where = stree->n.tb->where;
10395
10396   /* Default access should already be resolved from the parser.  */
10397   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10398
10399   /* It should be a module procedure or an external procedure with explicit
10400      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10401   if ((!proc->attr.subroutine && !proc->attr.function)
10402       || (proc->attr.proc != PROC_MODULE
10403           && proc->attr.if_source != IFSRC_IFBODY)
10404       || (proc->attr.abstract && !stree->n.tb->deferred))
10405     {
10406       gfc_error ("'%s' must be a module procedure or an external procedure with"
10407                  " an explicit interface at %L", proc->name, &where);
10408       goto error;
10409     }
10410   stree->n.tb->subroutine = proc->attr.subroutine;
10411   stree->n.tb->function = proc->attr.function;
10412
10413   /* Find the super-type of the current derived type.  We could do this once and
10414      store in a global if speed is needed, but as long as not I believe this is
10415      more readable and clearer.  */
10416   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10417
10418   /* If PASS, resolve and check arguments if not already resolved / loaded
10419      from a .mod file.  */
10420   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10421     {
10422       if (stree->n.tb->pass_arg)
10423         {
10424           gfc_formal_arglist* i;
10425
10426           /* If an explicit passing argument name is given, walk the arg-list
10427              and look for it.  */
10428
10429           me_arg = NULL;
10430           stree->n.tb->pass_arg_num = 1;
10431           for (i = proc->formal; i; i = i->next)
10432             {
10433               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10434                 {
10435                   me_arg = i->sym;
10436                   break;
10437                 }
10438               ++stree->n.tb->pass_arg_num;
10439             }
10440
10441           if (!me_arg)
10442             {
10443               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10444                          " argument '%s'",
10445                          proc->name, stree->n.tb->pass_arg, &where,
10446                          stree->n.tb->pass_arg);
10447               goto error;
10448             }
10449         }
10450       else
10451         {
10452           /* Otherwise, take the first one; there should in fact be at least
10453              one.  */
10454           stree->n.tb->pass_arg_num = 1;
10455           if (!proc->formal)
10456             {
10457               gfc_error ("Procedure '%s' with PASS at %L must have at"
10458                          " least one argument", proc->name, &where);
10459               goto error;
10460             }
10461           me_arg = proc->formal->sym;
10462         }
10463
10464       /* Now check that the argument-type matches and the passed-object
10465          dummy argument is generally fine.  */
10466
10467       gcc_assert (me_arg);
10468
10469       if (me_arg->ts.type != BT_CLASS)
10470         {
10471           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10472                      " at %L", proc->name, &where);
10473           goto error;
10474         }
10475
10476       if (me_arg->ts.u.derived->components->ts.u.derived
10477           != resolve_bindings_derived)
10478         {
10479           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10480                      " the derived-type '%s'", me_arg->name, proc->name,
10481                      me_arg->name, &where, resolve_bindings_derived->name);
10482           goto error;
10483         }
10484   
10485       gcc_assert (me_arg->ts.type == BT_CLASS);
10486       if (me_arg->ts.u.derived->components->as
10487           && me_arg->ts.u.derived->components->as->rank > 0)
10488         {
10489           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10490                      " scalar", proc->name, &where);
10491           goto error;
10492         }
10493       if (me_arg->ts.u.derived->components->attr.allocatable)
10494         {
10495           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10496                      " be ALLOCATABLE", proc->name, &where);
10497           goto error;
10498         }
10499       if (me_arg->ts.u.derived->components->attr.class_pointer)
10500         {
10501           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10502                      " be POINTER", proc->name, &where);
10503           goto error;
10504         }
10505     }
10506
10507   /* If we are extending some type, check that we don't override a procedure
10508      flagged NON_OVERRIDABLE.  */
10509   stree->n.tb->overridden = NULL;
10510   if (super_type)
10511     {
10512       gfc_symtree* overridden;
10513       overridden = gfc_find_typebound_proc (super_type, NULL,
10514                                             stree->name, true, NULL);
10515
10516       if (overridden && overridden->n.tb)
10517         stree->n.tb->overridden = overridden->n.tb;
10518
10519       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10520         goto error;
10521     }
10522
10523   /* See if there's a name collision with a component directly in this type.  */
10524   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10525     if (!strcmp (comp->name, stree->name))
10526       {
10527         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10528                    " '%s'",
10529                    stree->name, &where, resolve_bindings_derived->name);
10530         goto error;
10531       }
10532
10533   /* Try to find a name collision with an inherited component.  */
10534   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10535     {
10536       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10537                  " component of '%s'",
10538                  stree->name, &where, resolve_bindings_derived->name);
10539       goto error;
10540     }
10541
10542   stree->n.tb->error = 0;
10543   return;
10544
10545 error:
10546   resolve_bindings_result = FAILURE;
10547   stree->n.tb->error = 1;
10548 }
10549
10550 static gfc_try
10551 resolve_typebound_procedures (gfc_symbol* derived)
10552 {
10553   int op;
10554
10555   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10556     return SUCCESS;
10557
10558   resolve_bindings_derived = derived;
10559   resolve_bindings_result = SUCCESS;
10560
10561   if (derived->f2k_derived->tb_sym_root)
10562     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10563                           &resolve_typebound_procedure);
10564
10565   if (derived->f2k_derived->tb_uop_root)
10566     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10567                           &resolve_typebound_user_op);
10568
10569   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10570     {
10571       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10572       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10573                                                p) == FAILURE)
10574         resolve_bindings_result = FAILURE;
10575     }
10576
10577   return resolve_bindings_result;
10578 }
10579
10580
10581 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10582    to give all identical derived types the same backend_decl.  */
10583 static void
10584 add_dt_to_dt_list (gfc_symbol *derived)
10585 {
10586   gfc_dt_list *dt_list;
10587
10588   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10589     if (derived == dt_list->derived)
10590       break;
10591
10592   if (dt_list == NULL)
10593     {
10594       dt_list = gfc_get_dt_list ();
10595       dt_list->next = gfc_derived_types;
10596       dt_list->derived = derived;
10597       gfc_derived_types = dt_list;
10598     }
10599 }
10600
10601
10602 /* Ensure that a derived-type is really not abstract, meaning that every
10603    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10604
10605 static gfc_try
10606 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10607 {
10608   if (!st)
10609     return SUCCESS;
10610
10611   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10612     return FAILURE;
10613   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10614     return FAILURE;
10615
10616   if (st->n.tb && st->n.tb->deferred)
10617     {
10618       gfc_symtree* overriding;
10619       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10620       gcc_assert (overriding && overriding->n.tb);
10621       if (overriding->n.tb->deferred)
10622         {
10623           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10624                      " '%s' is DEFERRED and not overridden",
10625                      sub->name, &sub->declared_at, st->name);
10626           return FAILURE;
10627         }
10628     }
10629
10630   return SUCCESS;
10631 }
10632
10633 static gfc_try
10634 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10635 {
10636   /* The algorithm used here is to recursively travel up the ancestry of sub
10637      and for each ancestor-type, check all bindings.  If any of them is
10638      DEFERRED, look it up starting from sub and see if the found (overriding)
10639      binding is not DEFERRED.
10640      This is not the most efficient way to do this, but it should be ok and is
10641      clearer than something sophisticated.  */
10642
10643   gcc_assert (ancestor && ancestor->attr.abstract && !sub->attr.abstract);
10644
10645   /* Walk bindings of this ancestor.  */
10646   if (ancestor->f2k_derived)
10647     {
10648       gfc_try t;
10649       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10650       if (t == FAILURE)
10651         return FAILURE;
10652     }
10653
10654   /* Find next ancestor type and recurse on it.  */
10655   ancestor = gfc_get_derived_super_type (ancestor);
10656   if (ancestor)
10657     return ensure_not_abstract (sub, ancestor);
10658
10659   return SUCCESS;
10660 }
10661
10662
10663 static void resolve_symbol (gfc_symbol *sym);
10664
10665
10666 /* Resolve the components of a derived type.  */
10667
10668 static gfc_try
10669 resolve_fl_derived (gfc_symbol *sym)
10670 {
10671   gfc_symbol* super_type;
10672   gfc_component *c;
10673   int i;
10674
10675   super_type = gfc_get_derived_super_type (sym);
10676
10677   /* F2008, C432. */
10678   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
10679     {
10680       gfc_error ("As extending type '%s' at %L has a coarray component, "
10681                  "parent type '%s' shall also have one", sym->name,
10682                  &sym->declared_at, super_type->name);
10683       return FAILURE;
10684     }
10685
10686   /* Ensure the extended type gets resolved before we do.  */
10687   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10688     return FAILURE;
10689
10690   /* An ABSTRACT type must be extensible.  */
10691   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10692     {
10693       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10694                  sym->name, &sym->declared_at);
10695       return FAILURE;
10696     }
10697
10698   for (c = sym->components; c != NULL; c = c->next)
10699     {
10700       /* F2008, C442.  */
10701       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
10702           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
10703         {
10704           gfc_error ("Coarray component '%s' at %L must be allocatable with "
10705                      "deferred shape", c->name, &c->loc);
10706           return FAILURE;
10707         }
10708
10709       /* F2008, C443.  */
10710       if (c->attr.codimension && c->ts.type == BT_DERIVED
10711           && c->ts.u.derived->ts.is_iso_c)
10712         {
10713           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
10714                      "shall not be a coarray", c->name, &c->loc);
10715           return FAILURE;
10716         }
10717
10718       /* F2008, C444.  */
10719       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
10720           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
10721               || c->attr.allocatable))
10722         {
10723           gfc_error ("Component '%s' at %L with coarray component "
10724                      "shall be a nonpointer, nonallocatable scalar",
10725                      c->name, &c->loc);
10726           return FAILURE;
10727         }
10728
10729       if (c->attr.proc_pointer && c->ts.interface)
10730         {
10731           if (c->ts.interface->attr.procedure)
10732             gfc_error ("Interface '%s', used by procedure pointer component "
10733                        "'%s' at %L, is declared in a later PROCEDURE statement",
10734                        c->ts.interface->name, c->name, &c->loc);
10735
10736           /* Get the attributes from the interface (now resolved).  */
10737           if (c->ts.interface->attr.if_source
10738               || c->ts.interface->attr.intrinsic)
10739             {
10740               gfc_symbol *ifc = c->ts.interface;
10741
10742               if (ifc->formal && !ifc->formal_ns)
10743                 resolve_symbol (ifc);
10744
10745               if (ifc->attr.intrinsic)
10746                 resolve_intrinsic (ifc, &ifc->declared_at);
10747
10748               if (ifc->result)
10749                 {
10750                   c->ts = ifc->result->ts;
10751                   c->attr.allocatable = ifc->result->attr.allocatable;
10752                   c->attr.pointer = ifc->result->attr.pointer;
10753                   c->attr.dimension = ifc->result->attr.dimension;
10754                   c->as = gfc_copy_array_spec (ifc->result->as);
10755                 }
10756               else
10757                 {   
10758                   c->ts = ifc->ts;
10759                   c->attr.allocatable = ifc->attr.allocatable;
10760                   c->attr.pointer = ifc->attr.pointer;
10761                   c->attr.dimension = ifc->attr.dimension;
10762                   c->as = gfc_copy_array_spec (ifc->as);
10763                 }
10764               c->ts.interface = ifc;
10765               c->attr.function = ifc->attr.function;
10766               c->attr.subroutine = ifc->attr.subroutine;
10767               gfc_copy_formal_args_ppc (c, ifc);
10768
10769               c->attr.pure = ifc->attr.pure;
10770               c->attr.elemental = ifc->attr.elemental;
10771               c->attr.recursive = ifc->attr.recursive;
10772               c->attr.always_explicit = ifc->attr.always_explicit;
10773               c->attr.ext_attr |= ifc->attr.ext_attr;
10774               /* Replace symbols in array spec.  */
10775               if (c->as)
10776                 {
10777                   int i;
10778                   for (i = 0; i < c->as->rank; i++)
10779                     {
10780                       gfc_expr_replace_comp (c->as->lower[i], c);
10781                       gfc_expr_replace_comp (c->as->upper[i], c);
10782                     }
10783                 }
10784               /* Copy char length.  */
10785               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10786                 {
10787                   c->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10788                   gfc_expr_replace_comp (c->ts.u.cl->length, c);
10789                 }
10790             }
10791           else if (c->ts.interface->name[0] != '\0')
10792             {
10793               gfc_error ("Interface '%s' of procedure pointer component "
10794                          "'%s' at %L must be explicit", c->ts.interface->name,
10795                          c->name, &c->loc);
10796               return FAILURE;
10797             }
10798         }
10799       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10800         {
10801           /* Since PPCs are not implicitly typed, a PPC without an explicit
10802              interface must be a subroutine.  */
10803           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10804         }
10805
10806       /* Procedure pointer components: Check PASS arg.  */
10807       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0)
10808         {
10809           gfc_symbol* me_arg;
10810
10811           if (c->tb->pass_arg)
10812             {
10813               gfc_formal_arglist* i;
10814
10815               /* If an explicit passing argument name is given, walk the arg-list
10816                 and look for it.  */
10817
10818               me_arg = NULL;
10819               c->tb->pass_arg_num = 1;
10820               for (i = c->formal; i; i = i->next)
10821                 {
10822                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10823                     {
10824                       me_arg = i->sym;
10825                       break;
10826                     }
10827                   c->tb->pass_arg_num++;
10828                 }
10829
10830               if (!me_arg)
10831                 {
10832                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10833                              "at %L has no argument '%s'", c->name,
10834                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10835                   c->tb->error = 1;
10836                   return FAILURE;
10837                 }
10838             }
10839           else
10840             {
10841               /* Otherwise, take the first one; there should in fact be at least
10842                 one.  */
10843               c->tb->pass_arg_num = 1;
10844               if (!c->formal)
10845                 {
10846                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10847                              "must have at least one argument",
10848                              c->name, &c->loc);
10849                   c->tb->error = 1;
10850                   return FAILURE;
10851                 }
10852               me_arg = c->formal->sym;
10853             }
10854
10855           /* Now check that the argument-type matches.  */
10856           gcc_assert (me_arg);
10857           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10858               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10859               || (me_arg->ts.type == BT_CLASS
10860                   && me_arg->ts.u.derived->components->ts.u.derived != sym))
10861             {
10862               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10863                          " the derived type '%s'", me_arg->name, c->name,
10864                          me_arg->name, &c->loc, sym->name);
10865               c->tb->error = 1;
10866               return FAILURE;
10867             }
10868
10869           /* Check for C453.  */
10870           if (me_arg->attr.dimension)
10871             {
10872               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10873                          "must be scalar", me_arg->name, c->name, me_arg->name,
10874                          &c->loc);
10875               c->tb->error = 1;
10876               return FAILURE;
10877             }
10878
10879           if (me_arg->attr.pointer)
10880             {
10881               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10882                          "may not have the POINTER attribute", me_arg->name,
10883                          c->name, me_arg->name, &c->loc);
10884               c->tb->error = 1;
10885               return FAILURE;
10886             }
10887
10888           if (me_arg->attr.allocatable)
10889             {
10890               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10891                          "may not be ALLOCATABLE", me_arg->name, c->name,
10892                          me_arg->name, &c->loc);
10893               c->tb->error = 1;
10894               return FAILURE;
10895             }
10896
10897           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10898             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10899                        " at %L", c->name, &c->loc);
10900
10901         }
10902
10903       /* Check type-spec if this is not the parent-type component.  */
10904       if ((!sym->attr.extension || c != sym->components)
10905           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10906         return FAILURE;
10907
10908       /* If this type is an extension, set the accessibility of the parent
10909          component.  */
10910       if (super_type && c == sym->components
10911           && strcmp (super_type->name, c->name) == 0)
10912         c->attr.access = super_type->attr.access;
10913       
10914       /* If this type is an extension, see if this component has the same name
10915          as an inherited type-bound procedure.  */
10916       if (super_type
10917           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10918         {
10919           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10920                      " inherited type-bound procedure",
10921                      c->name, sym->name, &c->loc);
10922           return FAILURE;
10923         }
10924
10925       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10926         {
10927          if (c->ts.u.cl->length == NULL
10928              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10929              || !gfc_is_constant_expr (c->ts.u.cl->length))
10930            {
10931              gfc_error ("Character length of component '%s' needs to "
10932                         "be a constant specification expression at %L",
10933                         c->name,
10934                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10935              return FAILURE;
10936            }
10937         }
10938
10939       if (c->ts.type == BT_DERIVED
10940           && sym->component_access != ACCESS_PRIVATE
10941           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10942           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10943           && !c->ts.u.derived->attr.use_assoc
10944           && !gfc_check_access (c->ts.u.derived->attr.access,
10945                                 c->ts.u.derived->ns->default_access)
10946           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10947                              "is a PRIVATE type and cannot be a component of "
10948                              "'%s', which is PUBLIC at %L", c->name,
10949                              sym->name, &sym->declared_at) == FAILURE)
10950         return FAILURE;
10951
10952       if (sym->attr.sequence)
10953         {
10954           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10955             {
10956               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10957                          "not have the SEQUENCE attribute",
10958                          c->ts.u.derived->name, &sym->declared_at);
10959               return FAILURE;
10960             }
10961         }
10962
10963       if (c->ts.type == BT_DERIVED && c->attr.pointer
10964           && c->ts.u.derived->components == NULL
10965           && !c->ts.u.derived->attr.zero_comp)
10966         {
10967           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10968                      "that has not been declared", c->name, sym->name,
10969                      &c->loc);
10970           return FAILURE;
10971         }
10972
10973       /* C437.  */
10974       if (c->ts.type == BT_CLASS
10975           && !(c->ts.u.derived->components->attr.pointer
10976                || c->ts.u.derived->components->attr.allocatable))
10977         {
10978           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10979                      "or pointer", c->name, &c->loc);
10980           return FAILURE;
10981         }
10982
10983       /* Ensure that all the derived type components are put on the
10984          derived type list; even in formal namespaces, where derived type
10985          pointer components might not have been declared.  */
10986       if (c->ts.type == BT_DERIVED
10987             && c->ts.u.derived
10988             && c->ts.u.derived->components
10989             && c->attr.pointer
10990             && sym != c->ts.u.derived)
10991         add_dt_to_dt_list (c->ts.u.derived);
10992
10993       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10994           || c->as == NULL)
10995         continue;
10996
10997       for (i = 0; i < c->as->rank; i++)
10998         {
10999           if (c->as->lower[i] == NULL
11000               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
11001               || !gfc_is_constant_expr (c->as->lower[i])
11002               || c->as->upper[i] == NULL
11003               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
11004               || !gfc_is_constant_expr (c->as->upper[i]))
11005             {
11006               gfc_error ("Component '%s' of '%s' at %L must have "
11007                          "constant array bounds",
11008                          c->name, sym->name, &c->loc);
11009               return FAILURE;
11010             }
11011         }
11012     }
11013
11014   /* Resolve the type-bound procedures.  */
11015   if (resolve_typebound_procedures (sym) == FAILURE)
11016     return FAILURE;
11017
11018   /* Resolve the finalizer procedures.  */
11019   if (gfc_resolve_finalizers (sym) == FAILURE)
11020     return FAILURE;
11021
11022   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11023      all DEFERRED bindings are overridden.  */
11024   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11025       && ensure_not_abstract (sym, super_type) == FAILURE)
11026     return FAILURE;
11027
11028   /* Add derived type to the derived type list.  */
11029   add_dt_to_dt_list (sym);
11030
11031   return SUCCESS;
11032 }
11033
11034
11035 static gfc_try
11036 resolve_fl_namelist (gfc_symbol *sym)
11037 {
11038   gfc_namelist *nl;
11039   gfc_symbol *nlsym;
11040
11041   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11042   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11043     {
11044       for (nl = sym->namelist; nl; nl = nl->next)
11045         {
11046           if (!nl->sym->attr.use_assoc
11047               && !is_sym_host_assoc (nl->sym, sym->ns)
11048               && !gfc_check_access(nl->sym->attr.access,
11049                                 nl->sym->ns->default_access))
11050             {
11051               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11052                          "cannot be member of PUBLIC namelist '%s' at %L",
11053                          nl->sym->name, sym->name, &sym->declared_at);
11054               return FAILURE;
11055             }
11056
11057           /* Types with private components that came here by USE-association.  */
11058           if (nl->sym->ts.type == BT_DERIVED
11059               && derived_inaccessible (nl->sym->ts.u.derived))
11060             {
11061               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11062                          "components and cannot be member of namelist '%s' at %L",
11063                          nl->sym->name, sym->name, &sym->declared_at);
11064               return FAILURE;
11065             }
11066
11067           /* Types with private components that are defined in the same module.  */
11068           if (nl->sym->ts.type == BT_DERIVED
11069               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11070               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11071                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11072                                         nl->sym->ns->default_access))
11073             {
11074               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11075                          "cannot be a member of PUBLIC namelist '%s' at %L",
11076                          nl->sym->name, sym->name, &sym->declared_at);
11077               return FAILURE;
11078             }
11079         }
11080     }
11081
11082   for (nl = sym->namelist; nl; nl = nl->next)
11083     {
11084       /* Reject namelist arrays of assumed shape.  */
11085       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11086           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11087                              "must not have assumed shape in namelist "
11088                              "'%s' at %L", nl->sym->name, sym->name,
11089                              &sym->declared_at) == FAILURE)
11090             return FAILURE;
11091
11092       /* Reject namelist arrays that are not constant shape.  */
11093       if (is_non_constant_shape_array (nl->sym))
11094         {
11095           gfc_error ("NAMELIST array object '%s' must have constant "
11096                      "shape in namelist '%s' at %L", nl->sym->name,
11097                      sym->name, &sym->declared_at);
11098           return FAILURE;
11099         }
11100
11101       /* Namelist objects cannot have allocatable or pointer components.  */
11102       if (nl->sym->ts.type != BT_DERIVED)
11103         continue;
11104
11105       if (nl->sym->ts.u.derived->attr.alloc_comp)
11106         {
11107           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11108                      "have ALLOCATABLE components",
11109                      nl->sym->name, sym->name, &sym->declared_at);
11110           return FAILURE;
11111         }
11112
11113       if (nl->sym->ts.u.derived->attr.pointer_comp)
11114         {
11115           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11116                      "have POINTER components", 
11117                      nl->sym->name, sym->name, &sym->declared_at);
11118           return FAILURE;
11119         }
11120     }
11121
11122
11123   /* 14.1.2 A module or internal procedure represent local entities
11124      of the same type as a namelist member and so are not allowed.  */
11125   for (nl = sym->namelist; nl; nl = nl->next)
11126     {
11127       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11128         continue;
11129
11130       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11131         if ((nl->sym == sym->ns->proc_name)
11132                ||
11133             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11134           continue;
11135
11136       nlsym = NULL;
11137       if (nl->sym && nl->sym->name)
11138         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11139       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11140         {
11141           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11142                      "attribute in '%s' at %L", nlsym->name,
11143                      &sym->declared_at);
11144           return FAILURE;
11145         }
11146     }
11147
11148   return SUCCESS;
11149 }
11150
11151
11152 static gfc_try
11153 resolve_fl_parameter (gfc_symbol *sym)
11154 {
11155   /* A parameter array's shape needs to be constant.  */
11156   if (sym->as != NULL 
11157       && (sym->as->type == AS_DEFERRED
11158           || is_non_constant_shape_array (sym)))
11159     {
11160       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11161                  "or of deferred shape", sym->name, &sym->declared_at);
11162       return FAILURE;
11163     }
11164
11165   /* Make sure a parameter that has been implicitly typed still
11166      matches the implicit type, since PARAMETER statements can precede
11167      IMPLICIT statements.  */
11168   if (sym->attr.implicit_type
11169       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11170                                                              sym->ns)))
11171     {
11172       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11173                  "later IMPLICIT type", sym->name, &sym->declared_at);
11174       return FAILURE;
11175     }
11176
11177   /* Make sure the types of derived parameters are consistent.  This
11178      type checking is deferred until resolution because the type may
11179      refer to a derived type from the host.  */
11180   if (sym->ts.type == BT_DERIVED
11181       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11182     {
11183       gfc_error ("Incompatible derived type in PARAMETER at %L",
11184                  &sym->value->where);
11185       return FAILURE;
11186     }
11187   return SUCCESS;
11188 }
11189
11190
11191 /* Do anything necessary to resolve a symbol.  Right now, we just
11192    assume that an otherwise unknown symbol is a variable.  This sort
11193    of thing commonly happens for symbols in module.  */
11194
11195 static void
11196 resolve_symbol (gfc_symbol *sym)
11197 {
11198   int check_constant, mp_flag;
11199   gfc_symtree *symtree;
11200   gfc_symtree *this_symtree;
11201   gfc_namespace *ns;
11202   gfc_component *c;
11203
11204   if (sym->attr.flavor == FL_UNKNOWN)
11205     {
11206
11207     /* If we find that a flavorless symbol is an interface in one of the
11208        parent namespaces, find its symtree in this namespace, free the
11209        symbol and set the symtree to point to the interface symbol.  */
11210       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11211         {
11212           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11213           if (symtree && symtree->n.sym->generic)
11214             {
11215               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11216                                                sym->name);
11217               sym->refs--;
11218               if (!sym->refs)
11219                 gfc_free_symbol (sym);
11220               symtree->n.sym->refs++;
11221               this_symtree->n.sym = symtree->n.sym;
11222               return;
11223             }
11224         }
11225
11226       /* Otherwise give it a flavor according to such attributes as
11227          it has.  */
11228       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11229         sym->attr.flavor = FL_VARIABLE;
11230       else
11231         {
11232           sym->attr.flavor = FL_PROCEDURE;
11233           if (sym->attr.dimension)
11234             sym->attr.function = 1;
11235         }
11236     }
11237
11238   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11239     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11240
11241   if (sym->attr.procedure && sym->ts.interface
11242       && sym->attr.if_source != IFSRC_DECL)
11243     {
11244       if (sym->ts.interface == sym)
11245         {
11246           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
11247                      "interface", sym->name, &sym->declared_at);
11248           return;
11249         }
11250       if (sym->ts.interface->attr.procedure)
11251         {
11252           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
11253                      " in a later PROCEDURE statement", sym->ts.interface->name,
11254                      sym->name,&sym->declared_at);
11255           return;
11256         }
11257
11258       /* Get the attributes from the interface (now resolved).  */
11259       if (sym->ts.interface->attr.if_source
11260           || sym->ts.interface->attr.intrinsic)
11261         {
11262           gfc_symbol *ifc = sym->ts.interface;
11263           resolve_symbol (ifc);
11264
11265           if (ifc->attr.intrinsic)
11266             resolve_intrinsic (ifc, &ifc->declared_at);
11267
11268           if (ifc->result)
11269             sym->ts = ifc->result->ts;
11270           else   
11271             sym->ts = ifc->ts;
11272           sym->ts.interface = ifc;
11273           sym->attr.function = ifc->attr.function;
11274           sym->attr.subroutine = ifc->attr.subroutine;
11275           gfc_copy_formal_args (sym, ifc);
11276
11277           sym->attr.allocatable = ifc->attr.allocatable;
11278           sym->attr.pointer = ifc->attr.pointer;
11279           sym->attr.pure = ifc->attr.pure;
11280           sym->attr.elemental = ifc->attr.elemental;
11281           sym->attr.dimension = ifc->attr.dimension;
11282           sym->attr.recursive = ifc->attr.recursive;
11283           sym->attr.always_explicit = ifc->attr.always_explicit;
11284           sym->attr.ext_attr |= ifc->attr.ext_attr;
11285           /* Copy array spec.  */
11286           sym->as = gfc_copy_array_spec (ifc->as);
11287           if (sym->as)
11288             {
11289               int i;
11290               for (i = 0; i < sym->as->rank; i++)
11291                 {
11292                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
11293                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
11294                 }
11295             }
11296           /* Copy char length.  */
11297           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11298             {
11299               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11300               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
11301             }
11302         }
11303       else if (sym->ts.interface->name[0] != '\0')
11304         {
11305           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
11306                     sym->ts.interface->name, sym->name, &sym->declared_at);
11307           return;
11308         }
11309     }
11310
11311   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11312     return;
11313
11314   /* Symbols that are module procedures with results (functions) have
11315      the types and array specification copied for type checking in
11316      procedures that call them, as well as for saving to a module
11317      file.  These symbols can't stand the scrutiny that their results
11318      can.  */
11319   mp_flag = (sym->result != NULL && sym->result != sym);
11320
11321
11322   /* Make sure that the intrinsic is consistent with its internal 
11323      representation. This needs to be done before assigning a default 
11324      type to avoid spurious warnings.  */
11325   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11326       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11327     return;
11328
11329   /* Assign default type to symbols that need one and don't have one.  */
11330   if (sym->ts.type == BT_UNKNOWN)
11331     {
11332       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11333         gfc_set_default_type (sym, 1, NULL);
11334
11335       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11336           && !sym->attr.function && !sym->attr.subroutine
11337           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11338         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11339
11340       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11341         {
11342           /* The specific case of an external procedure should emit an error
11343              in the case that there is no implicit type.  */
11344           if (!mp_flag)
11345             gfc_set_default_type (sym, sym->attr.external, NULL);
11346           else
11347             {
11348               /* Result may be in another namespace.  */
11349               resolve_symbol (sym->result);
11350
11351               if (!sym->result->attr.proc_pointer)
11352                 {
11353                   sym->ts = sym->result->ts;
11354                   sym->as = gfc_copy_array_spec (sym->result->as);
11355                   sym->attr.dimension = sym->result->attr.dimension;
11356                   sym->attr.pointer = sym->result->attr.pointer;
11357                   sym->attr.allocatable = sym->result->attr.allocatable;
11358                 }
11359             }
11360         }
11361     }
11362
11363   /* Assumed size arrays and assumed shape arrays must be dummy
11364      arguments.  */
11365
11366   if (sym->as != NULL
11367       && ((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11368           || sym->as->type == AS_ASSUMED_SHAPE)
11369       && sym->attr.dummy == 0)
11370     {
11371       if (sym->as->type == AS_ASSUMED_SIZE)
11372         gfc_error ("Assumed size array at %L must be a dummy argument",
11373                    &sym->declared_at);
11374       else
11375         gfc_error ("Assumed shape array at %L must be a dummy argument",
11376                    &sym->declared_at);
11377       return;
11378     }
11379
11380   /* Make sure symbols with known intent or optional are really dummy
11381      variable.  Because of ENTRY statement, this has to be deferred
11382      until resolution time.  */
11383
11384   if (!sym->attr.dummy
11385       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11386     {
11387       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11388       return;
11389     }
11390
11391   if (sym->attr.value && !sym->attr.dummy)
11392     {
11393       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11394                  "it is not a dummy argument", sym->name, &sym->declared_at);
11395       return;
11396     }
11397
11398   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11399     {
11400       gfc_charlen *cl = sym->ts.u.cl;
11401       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11402         {
11403           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11404                      "attribute must have constant length",
11405                      sym->name, &sym->declared_at);
11406           return;
11407         }
11408
11409       if (sym->ts.is_c_interop
11410           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11411         {
11412           gfc_error ("C interoperable character dummy variable '%s' at %L "
11413                      "with VALUE attribute must have length one",
11414                      sym->name, &sym->declared_at);
11415           return;
11416         }
11417     }
11418
11419   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11420      do this for something that was implicitly typed because that is handled
11421      in gfc_set_default_type.  Handle dummy arguments and procedure
11422      definitions separately.  Also, anything that is use associated is not
11423      handled here but instead is handled in the module it is declared in.
11424      Finally, derived type definitions are allowed to be BIND(C) since that
11425      only implies that they're interoperable, and they are checked fully for
11426      interoperability when a variable is declared of that type.  */
11427   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11428       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11429       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11430     {
11431       gfc_try t = SUCCESS;
11432       
11433       /* First, make sure the variable is declared at the
11434          module-level scope (J3/04-007, Section 15.3).  */
11435       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11436           sym->attr.in_common == 0)
11437         {
11438           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11439                      "is neither a COMMON block nor declared at the "
11440                      "module level scope", sym->name, &(sym->declared_at));
11441           t = FAILURE;
11442         }
11443       else if (sym->common_head != NULL)
11444         {
11445           t = verify_com_block_vars_c_interop (sym->common_head);
11446         }
11447       else
11448         {
11449           /* If type() declaration, we need to verify that the components
11450              of the given type are all C interoperable, etc.  */
11451           if (sym->ts.type == BT_DERIVED &&
11452               sym->ts.u.derived->attr.is_c_interop != 1)
11453             {
11454               /* Make sure the user marked the derived type as BIND(C).  If
11455                  not, call the verify routine.  This could print an error
11456                  for the derived type more than once if multiple variables
11457                  of that type are declared.  */
11458               if (sym->ts.u.derived->attr.is_bind_c != 1)
11459                 verify_bind_c_derived_type (sym->ts.u.derived);
11460               t = FAILURE;
11461             }
11462           
11463           /* Verify the variable itself as C interoperable if it
11464              is BIND(C).  It is not possible for this to succeed if
11465              the verify_bind_c_derived_type failed, so don't have to handle
11466              any error returned by verify_bind_c_derived_type.  */
11467           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11468                                  sym->common_block);
11469         }
11470
11471       if (t == FAILURE)
11472         {
11473           /* clear the is_bind_c flag to prevent reporting errors more than
11474              once if something failed.  */
11475           sym->attr.is_bind_c = 0;
11476           return;
11477         }
11478     }
11479
11480   /* If a derived type symbol has reached this point, without its
11481      type being declared, we have an error.  Notice that most
11482      conditions that produce undefined derived types have already
11483      been dealt with.  However, the likes of:
11484      implicit type(t) (t) ..... call foo (t) will get us here if
11485      the type is not declared in the scope of the implicit
11486      statement. Change the type to BT_UNKNOWN, both because it is so
11487      and to prevent an ICE.  */
11488   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11489       && !sym->ts.u.derived->attr.zero_comp)
11490     {
11491       gfc_error ("The derived type '%s' at %L is of type '%s', "
11492                  "which has not been defined", sym->name,
11493                   &sym->declared_at, sym->ts.u.derived->name);
11494       sym->ts.type = BT_UNKNOWN;
11495       return;
11496     }
11497
11498   /* Make sure that the derived type has been resolved and that the
11499      derived type is visible in the symbol's namespace, if it is a
11500      module function and is not PRIVATE.  */
11501   if (sym->ts.type == BT_DERIVED
11502         && sym->ts.u.derived->attr.use_assoc
11503         && sym->ns->proc_name
11504         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11505     {
11506       gfc_symbol *ds;
11507
11508       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11509         return;
11510
11511       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11512       if (!ds && sym->attr.function
11513             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11514         {
11515           symtree = gfc_new_symtree (&sym->ns->sym_root,
11516                                      sym->ts.u.derived->name);
11517           symtree->n.sym = sym->ts.u.derived;
11518           sym->ts.u.derived->refs++;
11519         }
11520     }
11521
11522   /* Unless the derived-type declaration is use associated, Fortran 95
11523      does not allow public entries of private derived types.
11524      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11525      161 in 95-006r3.  */
11526   if (sym->ts.type == BT_DERIVED
11527       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11528       && !sym->ts.u.derived->attr.use_assoc
11529       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11530       && !gfc_check_access (sym->ts.u.derived->attr.access,
11531                             sym->ts.u.derived->ns->default_access)
11532       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11533                          "of PRIVATE derived type '%s'",
11534                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11535                          : "variable", sym->name, &sym->declared_at,
11536                          sym->ts.u.derived->name) == FAILURE)
11537     return;
11538
11539   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11540      default initialization is defined (5.1.2.4.4).  */
11541   if (sym->ts.type == BT_DERIVED
11542       && sym->attr.dummy
11543       && sym->attr.intent == INTENT_OUT
11544       && sym->as
11545       && sym->as->type == AS_ASSUMED_SIZE)
11546     {
11547       for (c = sym->ts.u.derived->components; c; c = c->next)
11548         {
11549           if (c->initializer)
11550             {
11551               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11552                          "ASSUMED SIZE and so cannot have a default initializer",
11553                          sym->name, &sym->declared_at);
11554               return;
11555             }
11556         }
11557     }
11558
11559   /* F2008, C526.  */
11560   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11561        || sym->attr.codimension)
11562       && sym->attr.result)
11563     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
11564                "a coarray component", sym->name, &sym->declared_at);
11565
11566   /* F2008, C524.  */
11567   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
11568       && sym->ts.u.derived->ts.is_iso_c)
11569     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11570                "shall not be a coarray", sym->name, &sym->declared_at);
11571
11572   /* F2008, C525.  */
11573   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
11574       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
11575           || sym->attr.allocatable))
11576     gfc_error ("Variable '%s' at %L with coarray component "
11577                "shall be a nonpointer, nonallocatable scalar",
11578                sym->name, &sym->declared_at);
11579
11580   /* F2008, C526.  The function-result case was handled above.  */
11581   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11582        || sym->attr.codimension)
11583       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
11584            || sym->ns->proc_name->attr.flavor == FL_MODULE
11585            || sym->ns->proc_name->attr.is_main_program
11586            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
11587     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
11588                "component and is not ALLOCATABLE, SAVE nor a "
11589                "dummy argument", sym->name, &sym->declared_at);
11590   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
11591   else if (sym->attr.codimension && !sym->attr.allocatable
11592       && sym->as && sym->as->cotype == AS_DEFERRED)
11593     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
11594                 "deferred shape", sym->name, &sym->declared_at);
11595   else if (sym->attr.codimension && sym->attr.allocatable
11596       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
11597     gfc_error ("Allocatable coarray variable '%s' at %L must have "
11598                "deferred shape", sym->name, &sym->declared_at);
11599
11600
11601   /* F2008, C541.  */
11602   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11603        || (sym->attr.codimension && sym->attr.allocatable))
11604       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
11605     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
11606                "allocatable coarray or have coarray components",
11607                sym->name, &sym->declared_at);
11608
11609   if (sym->attr.codimension && sym->attr.dummy
11610       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
11611     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
11612                "procedure '%s'", sym->name, &sym->declared_at,
11613                sym->ns->proc_name->name);
11614
11615   switch (sym->attr.flavor)
11616     {
11617     case FL_VARIABLE:
11618       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11619         return;
11620       break;
11621
11622     case FL_PROCEDURE:
11623       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11624         return;
11625       break;
11626
11627     case FL_NAMELIST:
11628       if (resolve_fl_namelist (sym) == FAILURE)
11629         return;
11630       break;
11631
11632     case FL_PARAMETER:
11633       if (resolve_fl_parameter (sym) == FAILURE)
11634         return;
11635       break;
11636
11637     default:
11638       break;
11639     }
11640
11641   /* Resolve array specifier. Check as well some constraints
11642      on COMMON blocks.  */
11643
11644   check_constant = sym->attr.in_common && !sym->attr.pointer;
11645
11646   /* Set the formal_arg_flag so that check_conflict will not throw
11647      an error for host associated variables in the specification
11648      expression for an array_valued function.  */
11649   if (sym->attr.function && sym->as)
11650     formal_arg_flag = 1;
11651
11652   gfc_resolve_array_spec (sym->as, check_constant);
11653
11654   formal_arg_flag = 0;
11655
11656   /* Resolve formal namespaces.  */
11657   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11658       && !sym->attr.contained && !sym->attr.intrinsic)
11659     gfc_resolve (sym->formal_ns);
11660
11661   /* Make sure the formal namespace is present.  */
11662   if (sym->formal && !sym->formal_ns)
11663     {
11664       gfc_formal_arglist *formal = sym->formal;
11665       while (formal && !formal->sym)
11666         formal = formal->next;
11667
11668       if (formal)
11669         {
11670           sym->formal_ns = formal->sym->ns;
11671           sym->formal_ns->refs++;
11672         }
11673     }
11674
11675   /* Check threadprivate restrictions.  */
11676   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11677       && (!sym->attr.in_common
11678           && sym->module == NULL
11679           && (sym->ns->proc_name == NULL
11680               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11681     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11682
11683   /* If we have come this far we can apply default-initializers, as
11684      described in 14.7.5, to those variables that have not already
11685      been assigned one.  */
11686   if (sym->ts.type == BT_DERIVED
11687       && sym->attr.referenced
11688       && sym->ns == gfc_current_ns
11689       && !sym->value
11690       && !sym->attr.allocatable
11691       && !sym->attr.alloc_comp)
11692     {
11693       symbol_attribute *a = &sym->attr;
11694
11695       if ((!a->save && !a->dummy && !a->pointer
11696            && !a->in_common && !a->use_assoc
11697            && !(a->function && sym != sym->result))
11698           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11699         apply_default_init (sym);
11700     }
11701
11702   /* If this symbol has a type-spec, check it.  */
11703   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11704       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11705     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11706           == FAILURE)
11707       return;
11708 }
11709
11710
11711 /************* Resolve DATA statements *************/
11712
11713 static struct
11714 {
11715   gfc_data_value *vnode;
11716   mpz_t left;
11717 }
11718 values;
11719
11720
11721 /* Advance the values structure to point to the next value in the data list.  */
11722
11723 static gfc_try
11724 next_data_value (void)
11725 {
11726   while (mpz_cmp_ui (values.left, 0) == 0)
11727     {
11728
11729       if (values.vnode->next == NULL)
11730         return FAILURE;
11731
11732       values.vnode = values.vnode->next;
11733       mpz_set (values.left, values.vnode->repeat);
11734     }
11735
11736   return SUCCESS;
11737 }
11738
11739
11740 static gfc_try
11741 check_data_variable (gfc_data_variable *var, locus *where)
11742 {
11743   gfc_expr *e;
11744   mpz_t size;
11745   mpz_t offset;
11746   gfc_try t;
11747   ar_type mark = AR_UNKNOWN;
11748   int i;
11749   mpz_t section_index[GFC_MAX_DIMENSIONS];
11750   gfc_ref *ref;
11751   gfc_array_ref *ar;
11752   gfc_symbol *sym;
11753   int has_pointer;
11754
11755   if (gfc_resolve_expr (var->expr) == FAILURE)
11756     return FAILURE;
11757
11758   ar = NULL;
11759   mpz_init_set_si (offset, 0);
11760   e = var->expr;
11761
11762   if (e->expr_type != EXPR_VARIABLE)
11763     gfc_internal_error ("check_data_variable(): Bad expression");
11764
11765   sym = e->symtree->n.sym;
11766
11767   if (sym->ns->is_block_data && !sym->attr.in_common)
11768     {
11769       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11770                  sym->name, &sym->declared_at);
11771     }
11772
11773   if (e->ref == NULL && sym->as)
11774     {
11775       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11776                  " declaration", sym->name, where);
11777       return FAILURE;
11778     }
11779
11780   has_pointer = sym->attr.pointer;
11781
11782   for (ref = e->ref; ref; ref = ref->next)
11783     {
11784       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11785         has_pointer = 1;
11786
11787       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
11788         {
11789           gfc_error ("DATA element '%s' at %L cannot have a coindex",
11790                      sym->name, where);
11791           return FAILURE;
11792         }
11793
11794       if (has_pointer
11795             && ref->type == REF_ARRAY
11796             && ref->u.ar.type != AR_FULL)
11797           {
11798             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11799                         "be a full array", sym->name, where);
11800             return FAILURE;
11801           }
11802     }
11803
11804   if (e->rank == 0 || has_pointer)
11805     {
11806       mpz_init_set_ui (size, 1);
11807       ref = NULL;
11808     }
11809   else
11810     {
11811       ref = e->ref;
11812
11813       /* Find the array section reference.  */
11814       for (ref = e->ref; ref; ref = ref->next)
11815         {
11816           if (ref->type != REF_ARRAY)
11817             continue;
11818           if (ref->u.ar.type == AR_ELEMENT)
11819             continue;
11820           break;
11821         }
11822       gcc_assert (ref);
11823
11824       /* Set marks according to the reference pattern.  */
11825       switch (ref->u.ar.type)
11826         {
11827         case AR_FULL:
11828           mark = AR_FULL;
11829           break;
11830
11831         case AR_SECTION:
11832           ar = &ref->u.ar;
11833           /* Get the start position of array section.  */
11834           gfc_get_section_index (ar, section_index, &offset);
11835           mark = AR_SECTION;
11836           break;
11837
11838         default:
11839           gcc_unreachable ();
11840         }
11841
11842       if (gfc_array_size (e, &size) == FAILURE)
11843         {
11844           gfc_error ("Nonconstant array section at %L in DATA statement",
11845                      &e->where);
11846           mpz_clear (offset);
11847           return FAILURE;
11848         }
11849     }
11850
11851   t = SUCCESS;
11852
11853   while (mpz_cmp_ui (size, 0) > 0)
11854     {
11855       if (next_data_value () == FAILURE)
11856         {
11857           gfc_error ("DATA statement at %L has more variables than values",
11858                      where);
11859           t = FAILURE;
11860           break;
11861         }
11862
11863       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
11864       if (t == FAILURE)
11865         break;
11866
11867       /* If we have more than one element left in the repeat count,
11868          and we have more than one element left in the target variable,
11869          then create a range assignment.  */
11870       /* FIXME: Only done for full arrays for now, since array sections
11871          seem tricky.  */
11872       if (mark == AR_FULL && ref && ref->next == NULL
11873           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
11874         {
11875           mpz_t range;
11876
11877           if (mpz_cmp (size, values.left) >= 0)
11878             {
11879               mpz_init_set (range, values.left);
11880               mpz_sub (size, size, values.left);
11881               mpz_set_ui (values.left, 0);
11882             }
11883           else
11884             {
11885               mpz_init_set (range, size);
11886               mpz_sub (values.left, values.left, size);
11887               mpz_set_ui (size, 0);
11888             }
11889
11890           gfc_assign_data_value_range (var->expr, values.vnode->expr,
11891                                        offset, range);
11892
11893           mpz_add (offset, offset, range);
11894           mpz_clear (range);
11895         }
11896
11897       /* Assign initial value to symbol.  */
11898       else
11899         {
11900           mpz_sub_ui (values.left, values.left, 1);
11901           mpz_sub_ui (size, size, 1);
11902
11903           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11904           if (t == FAILURE)
11905             break;
11906
11907           if (mark == AR_FULL)
11908             mpz_add_ui (offset, offset, 1);
11909
11910           /* Modify the array section indexes and recalculate the offset
11911              for next element.  */
11912           else if (mark == AR_SECTION)
11913             gfc_advance_section (section_index, ar, &offset);
11914         }
11915     }
11916
11917   if (mark == AR_SECTION)
11918     {
11919       for (i = 0; i < ar->dimen; i++)
11920         mpz_clear (section_index[i]);
11921     }
11922
11923   mpz_clear (size);
11924   mpz_clear (offset);
11925
11926   return t;
11927 }
11928
11929
11930 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11931
11932 /* Iterate over a list of elements in a DATA statement.  */
11933
11934 static gfc_try
11935 traverse_data_list (gfc_data_variable *var, locus *where)
11936 {
11937   mpz_t trip;
11938   iterator_stack frame;
11939   gfc_expr *e, *start, *end, *step;
11940   gfc_try retval = SUCCESS;
11941
11942   mpz_init (frame.value);
11943
11944   start = gfc_copy_expr (var->iter.start);
11945   end = gfc_copy_expr (var->iter.end);
11946   step = gfc_copy_expr (var->iter.step);
11947
11948   if (gfc_simplify_expr (start, 1) == FAILURE
11949       || start->expr_type != EXPR_CONSTANT)
11950     {
11951       gfc_error ("iterator start at %L does not simplify", &start->where);
11952       retval = FAILURE;
11953       goto cleanup;
11954     }
11955   if (gfc_simplify_expr (end, 1) == FAILURE
11956       || end->expr_type != EXPR_CONSTANT)
11957     {
11958       gfc_error ("iterator end at %L does not simplify", &end->where);
11959       retval = FAILURE;
11960       goto cleanup;
11961     }
11962   if (gfc_simplify_expr (step, 1) == FAILURE
11963       || step->expr_type != EXPR_CONSTANT)
11964     {
11965       gfc_error ("iterator step at %L does not simplify", &step->where);
11966       retval = FAILURE;
11967       goto cleanup;
11968     }
11969
11970   mpz_init_set (trip, end->value.integer);
11971   mpz_sub (trip, trip, start->value.integer);
11972   mpz_add (trip, trip, step->value.integer);
11973
11974   mpz_div (trip, trip, step->value.integer);
11975
11976   mpz_set (frame.value, start->value.integer);
11977
11978   frame.prev = iter_stack;
11979   frame.variable = var->iter.var->symtree;
11980   iter_stack = &frame;
11981
11982   while (mpz_cmp_ui (trip, 0) > 0)
11983     {
11984       if (traverse_data_var (var->list, where) == FAILURE)
11985         {
11986           mpz_clear (trip);
11987           retval = FAILURE;
11988           goto cleanup;
11989         }
11990
11991       e = gfc_copy_expr (var->expr);
11992       if (gfc_simplify_expr (e, 1) == FAILURE)
11993         {
11994           gfc_free_expr (e);
11995           mpz_clear (trip);
11996           retval = FAILURE;
11997           goto cleanup;
11998         }
11999
12000       mpz_add (frame.value, frame.value, step->value.integer);
12001
12002       mpz_sub_ui (trip, trip, 1);
12003     }
12004
12005   mpz_clear (trip);
12006 cleanup:
12007   mpz_clear (frame.value);
12008
12009   gfc_free_expr (start);
12010   gfc_free_expr (end);
12011   gfc_free_expr (step);
12012
12013   iter_stack = frame.prev;
12014   return retval;
12015 }
12016
12017
12018 /* Type resolve variables in the variable list of a DATA statement.  */
12019
12020 static gfc_try
12021 traverse_data_var (gfc_data_variable *var, locus *where)
12022 {
12023   gfc_try t;
12024
12025   for (; var; var = var->next)
12026     {
12027       if (var->expr == NULL)
12028         t = traverse_data_list (var, where);
12029       else
12030         t = check_data_variable (var, where);
12031
12032       if (t == FAILURE)
12033         return FAILURE;
12034     }
12035
12036   return SUCCESS;
12037 }
12038
12039
12040 /* Resolve the expressions and iterators associated with a data statement.
12041    This is separate from the assignment checking because data lists should
12042    only be resolved once.  */
12043
12044 static gfc_try
12045 resolve_data_variables (gfc_data_variable *d)
12046 {
12047   for (; d; d = d->next)
12048     {
12049       if (d->list == NULL)
12050         {
12051           if (gfc_resolve_expr (d->expr) == FAILURE)
12052             return FAILURE;
12053         }
12054       else
12055         {
12056           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12057             return FAILURE;
12058
12059           if (resolve_data_variables (d->list) == FAILURE)
12060             return FAILURE;
12061         }
12062     }
12063
12064   return SUCCESS;
12065 }
12066
12067
12068 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12069    the value list into static variables, and then recursively traversing the
12070    variables list, expanding iterators and such.  */
12071
12072 static void
12073 resolve_data (gfc_data *d)
12074 {
12075
12076   if (resolve_data_variables (d->var) == FAILURE)
12077     return;
12078
12079   values.vnode = d->value;
12080   if (d->value == NULL)
12081     mpz_set_ui (values.left, 0);
12082   else
12083     mpz_set (values.left, d->value->repeat);
12084
12085   if (traverse_data_var (d->var, &d->where) == FAILURE)
12086     return;
12087
12088   /* At this point, we better not have any values left.  */
12089
12090   if (next_data_value () == SUCCESS)
12091     gfc_error ("DATA statement at %L has more values than variables",
12092                &d->where);
12093 }
12094
12095
12096 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12097    accessed by host or use association, is a dummy argument to a pure function,
12098    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12099    is storage associated with any such variable, shall not be used in the
12100    following contexts: (clients of this function).  */
12101
12102 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12103    procedure.  Returns zero if assignment is OK, nonzero if there is a
12104    problem.  */
12105 int
12106 gfc_impure_variable (gfc_symbol *sym)
12107 {
12108   gfc_symbol *proc;
12109   gfc_namespace *ns;
12110
12111   if (sym->attr.use_assoc || sym->attr.in_common)
12112     return 1;
12113
12114   /* Check if the symbol's ns is inside the pure procedure.  */
12115   for (ns = gfc_current_ns; ns; ns = ns->parent)
12116     {
12117       if (ns == sym->ns)
12118         break;
12119       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12120         return 1;
12121     }
12122
12123   proc = sym->ns->proc_name;
12124   if (sym->attr.dummy && gfc_pure (proc)
12125         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12126                 ||
12127              proc->attr.function))
12128     return 1;
12129
12130   /* TODO: Sort out what can be storage associated, if anything, and include
12131      it here.  In principle equivalences should be scanned but it does not
12132      seem to be possible to storage associate an impure variable this way.  */
12133   return 0;
12134 }
12135
12136
12137 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12138    current namespace is inside a pure procedure.  */
12139
12140 int
12141 gfc_pure (gfc_symbol *sym)
12142 {
12143   symbol_attribute attr;
12144   gfc_namespace *ns;
12145
12146   if (sym == NULL)
12147     {
12148       /* Check if the current namespace or one of its parents
12149         belongs to a pure procedure.  */
12150       for (ns = gfc_current_ns; ns; ns = ns->parent)
12151         {
12152           sym = ns->proc_name;
12153           if (sym == NULL)
12154             return 0;
12155           attr = sym->attr;
12156           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
12157             return 1;
12158         }
12159       return 0;
12160     }
12161
12162   attr = sym->attr;
12163
12164   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
12165 }
12166
12167
12168 /* Test whether the current procedure is elemental or not.  */
12169
12170 int
12171 gfc_elemental (gfc_symbol *sym)
12172 {
12173   symbol_attribute attr;
12174
12175   if (sym == NULL)
12176     sym = gfc_current_ns->proc_name;
12177   if (sym == NULL)
12178     return 0;
12179   attr = sym->attr;
12180
12181   return attr.flavor == FL_PROCEDURE && attr.elemental;
12182 }
12183
12184
12185 /* Warn about unused labels.  */
12186
12187 static void
12188 warn_unused_fortran_label (gfc_st_label *label)
12189 {
12190   if (label == NULL)
12191     return;
12192
12193   warn_unused_fortran_label (label->left);
12194
12195   if (label->defined == ST_LABEL_UNKNOWN)
12196     return;
12197
12198   switch (label->referenced)
12199     {
12200     case ST_LABEL_UNKNOWN:
12201       gfc_warning ("Label %d at %L defined but not used", label->value,
12202                    &label->where);
12203       break;
12204
12205     case ST_LABEL_BAD_TARGET:
12206       gfc_warning ("Label %d at %L defined but cannot be used",
12207                    label->value, &label->where);
12208       break;
12209
12210     default:
12211       break;
12212     }
12213
12214   warn_unused_fortran_label (label->right);
12215 }
12216
12217
12218 /* Returns the sequence type of a symbol or sequence.  */
12219
12220 static seq_type
12221 sequence_type (gfc_typespec ts)
12222 {
12223   seq_type result;
12224   gfc_component *c;
12225
12226   switch (ts.type)
12227   {
12228     case BT_DERIVED:
12229
12230       if (ts.u.derived->components == NULL)
12231         return SEQ_NONDEFAULT;
12232
12233       result = sequence_type (ts.u.derived->components->ts);
12234       for (c = ts.u.derived->components->next; c; c = c->next)
12235         if (sequence_type (c->ts) != result)
12236           return SEQ_MIXED;
12237
12238       return result;
12239
12240     case BT_CHARACTER:
12241       if (ts.kind != gfc_default_character_kind)
12242           return SEQ_NONDEFAULT;
12243
12244       return SEQ_CHARACTER;
12245
12246     case BT_INTEGER:
12247       if (ts.kind != gfc_default_integer_kind)
12248           return SEQ_NONDEFAULT;
12249
12250       return SEQ_NUMERIC;
12251
12252     case BT_REAL:
12253       if (!(ts.kind == gfc_default_real_kind
12254             || ts.kind == gfc_default_double_kind))
12255           return SEQ_NONDEFAULT;
12256
12257       return SEQ_NUMERIC;
12258
12259     case BT_COMPLEX:
12260       if (ts.kind != gfc_default_complex_kind)
12261           return SEQ_NONDEFAULT;
12262
12263       return SEQ_NUMERIC;
12264
12265     case BT_LOGICAL:
12266       if (ts.kind != gfc_default_logical_kind)
12267           return SEQ_NONDEFAULT;
12268
12269       return SEQ_NUMERIC;
12270
12271     default:
12272       return SEQ_NONDEFAULT;
12273   }
12274 }
12275
12276
12277 /* Resolve derived type EQUIVALENCE object.  */
12278
12279 static gfc_try
12280 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12281 {
12282   gfc_component *c = derived->components;
12283
12284   if (!derived)
12285     return SUCCESS;
12286
12287   /* Shall not be an object of nonsequence derived type.  */
12288   if (!derived->attr.sequence)
12289     {
12290       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12291                  "attribute to be an EQUIVALENCE object", sym->name,
12292                  &e->where);
12293       return FAILURE;
12294     }
12295
12296   /* Shall not have allocatable components.  */
12297   if (derived->attr.alloc_comp)
12298     {
12299       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12300                  "components to be an EQUIVALENCE object",sym->name,
12301                  &e->where);
12302       return FAILURE;
12303     }
12304
12305   if (sym->attr.in_common && has_default_initializer (sym->ts.u.derived))
12306     {
12307       gfc_error ("Derived type variable '%s' at %L with default "
12308                  "initialization cannot be in EQUIVALENCE with a variable "
12309                  "in COMMON", sym->name, &e->where);
12310       return FAILURE;
12311     }
12312
12313   for (; c ; c = c->next)
12314     {
12315       if (c->ts.type == BT_DERIVED
12316           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12317         return FAILURE;
12318
12319       /* Shall not be an object of sequence derived type containing a pointer
12320          in the structure.  */
12321       if (c->attr.pointer)
12322         {
12323           gfc_error ("Derived type variable '%s' at %L with pointer "
12324                      "component(s) cannot be an EQUIVALENCE object",
12325                      sym->name, &e->where);
12326           return FAILURE;
12327         }
12328     }
12329   return SUCCESS;
12330 }
12331
12332
12333 /* Resolve equivalence object. 
12334    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12335    an allocatable array, an object of nonsequence derived type, an object of
12336    sequence derived type containing a pointer at any level of component
12337    selection, an automatic object, a function name, an entry name, a result
12338    name, a named constant, a structure component, or a subobject of any of
12339    the preceding objects.  A substring shall not have length zero.  A
12340    derived type shall not have components with default initialization nor
12341    shall two objects of an equivalence group be initialized.
12342    Either all or none of the objects shall have an protected attribute.
12343    The simple constraints are done in symbol.c(check_conflict) and the rest
12344    are implemented here.  */
12345
12346 static void
12347 resolve_equivalence (gfc_equiv *eq)
12348 {
12349   gfc_symbol *sym;
12350   gfc_symbol *first_sym;
12351   gfc_expr *e;
12352   gfc_ref *r;
12353   locus *last_where = NULL;
12354   seq_type eq_type, last_eq_type;
12355   gfc_typespec *last_ts;
12356   int object, cnt_protected;
12357   const char *msg;
12358
12359   last_ts = &eq->expr->symtree->n.sym->ts;
12360
12361   first_sym = eq->expr->symtree->n.sym;
12362
12363   cnt_protected = 0;
12364
12365   for (object = 1; eq; eq = eq->eq, object++)
12366     {
12367       e = eq->expr;
12368
12369       e->ts = e->symtree->n.sym->ts;
12370       /* match_varspec might not know yet if it is seeing
12371          array reference or substring reference, as it doesn't
12372          know the types.  */
12373       if (e->ref && e->ref->type == REF_ARRAY)
12374         {
12375           gfc_ref *ref = e->ref;
12376           sym = e->symtree->n.sym;
12377
12378           if (sym->attr.dimension)
12379             {
12380               ref->u.ar.as = sym->as;
12381               ref = ref->next;
12382             }
12383
12384           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12385           if (e->ts.type == BT_CHARACTER
12386               && ref
12387               && ref->type == REF_ARRAY
12388               && ref->u.ar.dimen == 1
12389               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12390               && ref->u.ar.stride[0] == NULL)
12391             {
12392               gfc_expr *start = ref->u.ar.start[0];
12393               gfc_expr *end = ref->u.ar.end[0];
12394               void *mem = NULL;
12395
12396               /* Optimize away the (:) reference.  */
12397               if (start == NULL && end == NULL)
12398                 {
12399                   if (e->ref == ref)
12400                     e->ref = ref->next;
12401                   else
12402                     e->ref->next = ref->next;
12403                   mem = ref;
12404                 }
12405               else
12406                 {
12407                   ref->type = REF_SUBSTRING;
12408                   if (start == NULL)
12409                     start = gfc_get_int_expr (gfc_default_integer_kind,
12410                                               NULL, 1);
12411                   ref->u.ss.start = start;
12412                   if (end == NULL && e->ts.u.cl)
12413                     end = gfc_copy_expr (e->ts.u.cl->length);
12414                   ref->u.ss.end = end;
12415                   ref->u.ss.length = e->ts.u.cl;
12416                   e->ts.u.cl = NULL;
12417                 }
12418               ref = ref->next;
12419               gfc_free (mem);
12420             }
12421
12422           /* Any further ref is an error.  */
12423           if (ref)
12424             {
12425               gcc_assert (ref->type == REF_ARRAY);
12426               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12427                          &ref->u.ar.where);
12428               continue;
12429             }
12430         }
12431
12432       if (gfc_resolve_expr (e) == FAILURE)
12433         continue;
12434
12435       sym = e->symtree->n.sym;
12436
12437       if (sym->attr.is_protected)
12438         cnt_protected++;
12439       if (cnt_protected > 0 && cnt_protected != object)
12440         {
12441               gfc_error ("Either all or none of the objects in the "
12442                          "EQUIVALENCE set at %L shall have the "
12443                          "PROTECTED attribute",
12444                          &e->where);
12445               break;
12446         }
12447
12448       /* Shall not equivalence common block variables in a PURE procedure.  */
12449       if (sym->ns->proc_name
12450           && sym->ns->proc_name->attr.pure
12451           && sym->attr.in_common)
12452         {
12453           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12454                      "object in the pure procedure '%s'",
12455                      sym->name, &e->where, sym->ns->proc_name->name);
12456           break;
12457         }
12458
12459       /* Shall not be a named constant.  */
12460       if (e->expr_type == EXPR_CONSTANT)
12461         {
12462           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12463                      "object", sym->name, &e->where);
12464           continue;
12465         }
12466
12467       if (e->ts.type == BT_DERIVED
12468           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12469         continue;
12470
12471       /* Check that the types correspond correctly:
12472          Note 5.28:
12473          A numeric sequence structure may be equivalenced to another sequence
12474          structure, an object of default integer type, default real type, double
12475          precision real type, default logical type such that components of the
12476          structure ultimately only become associated to objects of the same
12477          kind. A character sequence structure may be equivalenced to an object
12478          of default character kind or another character sequence structure.
12479          Other objects may be equivalenced only to objects of the same type and
12480          kind parameters.  */
12481
12482       /* Identical types are unconditionally OK.  */
12483       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12484         goto identical_types;
12485
12486       last_eq_type = sequence_type (*last_ts);
12487       eq_type = sequence_type (sym->ts);
12488
12489       /* Since the pair of objects is not of the same type, mixed or
12490          non-default sequences can be rejected.  */
12491
12492       msg = "Sequence %s with mixed components in EQUIVALENCE "
12493             "statement at %L with different type objects";
12494       if ((object ==2
12495            && last_eq_type == SEQ_MIXED
12496            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12497               == FAILURE)
12498           || (eq_type == SEQ_MIXED
12499               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12500                                  &e->where) == FAILURE))
12501         continue;
12502
12503       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12504             "statement at %L with objects of different type";
12505       if ((object ==2
12506            && last_eq_type == SEQ_NONDEFAULT
12507            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12508                               last_where) == FAILURE)
12509           || (eq_type == SEQ_NONDEFAULT
12510               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12511                                  &e->where) == FAILURE))
12512         continue;
12513
12514       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12515            "EQUIVALENCE statement at %L";
12516       if (last_eq_type == SEQ_CHARACTER
12517           && eq_type != SEQ_CHARACTER
12518           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12519                              &e->where) == FAILURE)
12520                 continue;
12521
12522       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12523            "EQUIVALENCE statement at %L";
12524       if (last_eq_type == SEQ_NUMERIC
12525           && eq_type != SEQ_NUMERIC
12526           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12527                              &e->where) == FAILURE)
12528                 continue;
12529
12530   identical_types:
12531       last_ts =&sym->ts;
12532       last_where = &e->where;
12533
12534       if (!e->ref)
12535         continue;
12536
12537       /* Shall not be an automatic array.  */
12538       if (e->ref->type == REF_ARRAY
12539           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12540         {
12541           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12542                      "an EQUIVALENCE object", sym->name, &e->where);
12543           continue;
12544         }
12545
12546       r = e->ref;
12547       while (r)
12548         {
12549           /* Shall not be a structure component.  */
12550           if (r->type == REF_COMPONENT)
12551             {
12552               gfc_error ("Structure component '%s' at %L cannot be an "
12553                          "EQUIVALENCE object",
12554                          r->u.c.component->name, &e->where);
12555               break;
12556             }
12557
12558           /* A substring shall not have length zero.  */
12559           if (r->type == REF_SUBSTRING)
12560             {
12561               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12562                 {
12563                   gfc_error ("Substring at %L has length zero",
12564                              &r->u.ss.start->where);
12565                   break;
12566                 }
12567             }
12568           r = r->next;
12569         }
12570     }
12571 }
12572
12573
12574 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12575
12576 static void
12577 resolve_fntype (gfc_namespace *ns)
12578 {
12579   gfc_entry_list *el;
12580   gfc_symbol *sym;
12581
12582   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12583     return;
12584
12585   /* If there are any entries, ns->proc_name is the entry master
12586      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12587   if (ns->entries)
12588     sym = ns->entries->sym;
12589   else
12590     sym = ns->proc_name;
12591   if (sym->result == sym
12592       && sym->ts.type == BT_UNKNOWN
12593       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12594       && !sym->attr.untyped)
12595     {
12596       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12597                  sym->name, &sym->declared_at);
12598       sym->attr.untyped = 1;
12599     }
12600
12601   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12602       && !sym->attr.contained
12603       && !gfc_check_access (sym->ts.u.derived->attr.access,
12604                             sym->ts.u.derived->ns->default_access)
12605       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12606     {
12607       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12608                       "%L of PRIVATE type '%s'", sym->name,
12609                       &sym->declared_at, sym->ts.u.derived->name);
12610     }
12611
12612     if (ns->entries)
12613     for (el = ns->entries->next; el; el = el->next)
12614       {
12615         if (el->sym->result == el->sym
12616             && el->sym->ts.type == BT_UNKNOWN
12617             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12618             && !el->sym->attr.untyped)
12619           {
12620             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12621                        el->sym->name, &el->sym->declared_at);
12622             el->sym->attr.untyped = 1;
12623           }
12624       }
12625 }
12626
12627
12628 /* 12.3.2.1.1 Defined operators.  */
12629
12630 static gfc_try
12631 check_uop_procedure (gfc_symbol *sym, locus where)
12632 {
12633   gfc_formal_arglist *formal;
12634
12635   if (!sym->attr.function)
12636     {
12637       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12638                  sym->name, &where);
12639       return FAILURE;
12640     }
12641
12642   if (sym->ts.type == BT_CHARACTER
12643       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12644       && !(sym->result && sym->result->ts.u.cl
12645            && sym->result->ts.u.cl->length))
12646     {
12647       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12648                  "character length", sym->name, &where);
12649       return FAILURE;
12650     }
12651
12652   formal = sym->formal;
12653   if (!formal || !formal->sym)
12654     {
12655       gfc_error ("User operator procedure '%s' at %L must have at least "
12656                  "one argument", sym->name, &where);
12657       return FAILURE;
12658     }
12659
12660   if (formal->sym->attr.intent != INTENT_IN)
12661     {
12662       gfc_error ("First argument of operator interface at %L must be "
12663                  "INTENT(IN)", &where);
12664       return FAILURE;
12665     }
12666
12667   if (formal->sym->attr.optional)
12668     {
12669       gfc_error ("First argument of operator interface at %L cannot be "
12670                  "optional", &where);
12671       return FAILURE;
12672     }
12673
12674   formal = formal->next;
12675   if (!formal || !formal->sym)
12676     return SUCCESS;
12677
12678   if (formal->sym->attr.intent != INTENT_IN)
12679     {
12680       gfc_error ("Second argument of operator interface at %L must be "
12681                  "INTENT(IN)", &where);
12682       return FAILURE;
12683     }
12684
12685   if (formal->sym->attr.optional)
12686     {
12687       gfc_error ("Second argument of operator interface at %L cannot be "
12688                  "optional", &where);
12689       return FAILURE;
12690     }
12691
12692   if (formal->next)
12693     {
12694       gfc_error ("Operator interface at %L must have, at most, two "
12695                  "arguments", &where);
12696       return FAILURE;
12697     }
12698
12699   return SUCCESS;
12700 }
12701
12702 static void
12703 gfc_resolve_uops (gfc_symtree *symtree)
12704 {
12705   gfc_interface *itr;
12706
12707   if (symtree == NULL)
12708     return;
12709
12710   gfc_resolve_uops (symtree->left);
12711   gfc_resolve_uops (symtree->right);
12712
12713   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12714     check_uop_procedure (itr->sym, itr->sym->declared_at);
12715 }
12716
12717
12718 /* Examine all of the expressions associated with a program unit,
12719    assign types to all intermediate expressions, make sure that all
12720    assignments are to compatible types and figure out which names
12721    refer to which functions or subroutines.  It doesn't check code
12722    block, which is handled by resolve_code.  */
12723
12724 static void
12725 resolve_types (gfc_namespace *ns)
12726 {
12727   gfc_namespace *n;
12728   gfc_charlen *cl;
12729   gfc_data *d;
12730   gfc_equiv *eq;
12731   gfc_namespace* old_ns = gfc_current_ns;
12732
12733   /* Check that all IMPLICIT types are ok.  */
12734   if (!ns->seen_implicit_none)
12735     {
12736       unsigned letter;
12737       for (letter = 0; letter != GFC_LETTERS; ++letter)
12738         if (ns->set_flag[letter]
12739             && resolve_typespec_used (&ns->default_type[letter],
12740                                       &ns->implicit_loc[letter],
12741                                       NULL) == FAILURE)
12742           return;
12743     }
12744
12745   gfc_current_ns = ns;
12746
12747   resolve_entries (ns);
12748
12749   resolve_common_vars (ns->blank_common.head, false);
12750   resolve_common_blocks (ns->common_root);
12751
12752   resolve_contained_functions (ns);
12753
12754   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12755
12756   for (cl = ns->cl_list; cl; cl = cl->next)
12757     resolve_charlen (cl);
12758
12759   gfc_traverse_ns (ns, resolve_symbol);
12760
12761   resolve_fntype (ns);
12762
12763   for (n = ns->contained; n; n = n->sibling)
12764     {
12765       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12766         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12767                    "also be PURE", n->proc_name->name,
12768                    &n->proc_name->declared_at);
12769
12770       resolve_types (n);
12771     }
12772
12773   forall_flag = 0;
12774   gfc_check_interfaces (ns);
12775
12776   gfc_traverse_ns (ns, resolve_values);
12777
12778   if (ns->save_all)
12779     gfc_save_all (ns);
12780
12781   iter_stack = NULL;
12782   for (d = ns->data; d; d = d->next)
12783     resolve_data (d);
12784
12785   iter_stack = NULL;
12786   gfc_traverse_ns (ns, gfc_formalize_init_value);
12787
12788   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12789
12790   if (ns->common_root != NULL)
12791     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12792
12793   for (eq = ns->equiv; eq; eq = eq->next)
12794     resolve_equivalence (eq);
12795
12796   /* Warn about unused labels.  */
12797   if (warn_unused_label)
12798     warn_unused_fortran_label (ns->st_labels);
12799
12800   gfc_resolve_uops (ns->uop_root);
12801
12802   gfc_current_ns = old_ns;
12803 }
12804
12805
12806 /* Call resolve_code recursively.  */
12807
12808 static void
12809 resolve_codes (gfc_namespace *ns)
12810 {
12811   gfc_namespace *n;
12812   bitmap_obstack old_obstack;
12813
12814   for (n = ns->contained; n; n = n->sibling)
12815     resolve_codes (n);
12816
12817   gfc_current_ns = ns;
12818
12819   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
12820   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
12821     cs_base = NULL;
12822
12823   /* Set to an out of range value.  */
12824   current_entry_id = -1;
12825
12826   old_obstack = labels_obstack;
12827   bitmap_obstack_initialize (&labels_obstack);
12828
12829   resolve_code (ns->code, ns);
12830
12831   bitmap_obstack_release (&labels_obstack);
12832   labels_obstack = old_obstack;
12833 }
12834
12835
12836 /* This function is called after a complete program unit has been compiled.
12837    Its purpose is to examine all of the expressions associated with a program
12838    unit, assign types to all intermediate expressions, make sure that all
12839    assignments are to compatible types and figure out which names refer to
12840    which functions or subroutines.  */
12841
12842 void
12843 gfc_resolve (gfc_namespace *ns)
12844 {
12845   gfc_namespace *old_ns;
12846   code_stack *old_cs_base;
12847
12848   if (ns->resolved)
12849     return;
12850
12851   ns->resolved = -1;
12852   old_ns = gfc_current_ns;
12853   old_cs_base = cs_base;
12854
12855   resolve_types (ns);
12856   resolve_codes (ns);
12857
12858   gfc_current_ns = old_ns;
12859   cs_base = old_cs_base;
12860   ns->resolved = 1;
12861 }