OSDN Git Service

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